OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_mat26.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| hm_read_mat26 ../starter/source/materials/mat/mat026/hm_read_mat26.F
25!||--- called by ------------------------------------------------------
26!|| hm_read_mat ../starter/source/materials/mat/hm_read_mat.F90
27!||--- calls -----------------------------------------------------
28!|| ancmsg ../starter/source/output/message/message.F
29!|| hm_get_floatv ../starter/source/devtools/hm_reader/hm_get_floatv.F
30!|| hm_get_floatv_dim ../starter/source/devtools/hm_reader/hm_get_floatv_dim.F
31!|| hm_get_string ../starter/source/devtools/hm_reader/hm_get_string.F
32!|| hm_option_is_encrypted ../starter/source/devtools/hm_reader/hm_option_is_encrypted.f
33!|| init_mat_keyword ../starter/source/materials/mat/init_mat_keyword.F
34!|| mrdse2 ../starter/source/materials/mat/mat026/mrdse2.F
35!|| mrdse3 ../starter/source/materials/mat/mat026/mrdse3.F
36!||--- uses -----------------------------------------------------
37!|| elbuftag_mod ../starter/share/modules1/elbuftag_mod.F
38!|| message_mod ../starter/share/message_module/message_mod.F
39!|| submodel_mod ../starter/share/modules1/submodel_mod.F
40!||====================================================================
41 SUBROUTINE hm_read_mat26(
42 . MTAG ,PM ,MAT_ID ,TITR ,IPM ,
43 . JTHE ,BUFMAT ,MFI ,IDF ,LSUBMODEL,
44 . UNITAB ,MATPARAM)
45C-----------------------------------------------
46C M o d u l e s
47C-----------------------------------------------
48 USE elbuftag_mod
49 USE message_mod
50 USE submodel_mod
51 USE matparam_def_mod
52 USE unitab_mod
54C-----------------------------------------------
55C I m p l i c i t T y p e s
56C-----------------------------------------------
57#include "implicit_f.inc"
58C-----------------------------------------------
59C C o m m o n B l o c k s
60C-----------------------------------------------
61#include "param_c.inc"
62#include "scr17_c.inc"
63#include "units_c.inc"
64C-----------------------------------------------
65C D u m m y A r g u m e n t s
66C-----------------------------------------------
67 INTEGER, INTENT(INOUT) :: JTHE,MFI,IDF
68 CHARACTER(LEN=NCHARTITLE) ,INTENT(IN) :: TITR
69 INTEGER, INTENT(IN) :: MAT_ID
70 INTEGER, DIMENSION(NPROPMI) ,INTENT(INOUT) :: IPM
71 my_real, DIMENSION(NPROPM) ,INTENT(INOUT) :: pm
72 TYPE(unit_type_), INTENT(IN) :: UNITAB
73 TYPE(submodel_data), DIMENSION(NSUBMOD),INTENT(IN) :: LSUBMODEL
74 TYPE(mlaw_tag_), INTENT(INOUT) :: MTAG
75 my_real ,DIMENSION(*), INTENT(INOUT) :: bufmat
76 TYPE(matparam_struct_) ,INTENT(INOUT) :: MATPARAM
77C-----------------------------------------------
78C L o c a l V a r i a b l e s
79C-----------------------------------------------
80 INTEGER I1, MAT, NR, NT, IDR, IDT, IDP, IDE, IDQ,ILAW
81 my_real
82 . YOUNG, ANU, CA, CB, CN, EPSM, SIGM, E0, CC, EPS0, CM, TMELT,
83 . tmax, g, c1, rho, unit, status, form, xnr, xnt, t0, p0, dpdr,
84 . xkl, xlamb, atom, sig, xkmax, rho0, dydz,rhor,eps0_unit
85
86 CHARACTER(ncharline) :: FILE, VIDE
87!
88 LOGICAL :: IS_AVAILABLE,IS_ENCRYPTED
89C=======================================================================
90 ilaw = 26
91 is_encrypted = .false.
92 is_available = .false.
93!-----------------------
94 CALL hm_option_is_encrypted(is_encrypted)
95!-----------------------
96 vide=
97 .' '
98! LINE 1
99 CALL hm_get_floatv('MAT_RHO' ,rho0 ,is_available, lsubmodel, unitab)
100 CALL hm_get_floatv('Refer_Rho' ,rhor ,is_available, lsubmodel, unitab)
101! LINE 2
102 CALL hm_get_floatv('MAT_E' ,young ,is_available, lsubmodel, unitab)
103 CALL hm_get_floatv('MAT_NU' ,anu ,is_available, lsubmodel, unitab)
104! LINE 3
105 CALL hm_get_floatv('MAT_SIGY' ,ca ,is_available, lsubmodel, unitab)
106 CALL hm_get_floatv('MAT_BETA' ,cb ,is_available, lsubmodel, unitab)
107 CALL hm_get_floatv('MAT_HARD' ,cn ,is_available, lsubmodel, unitab)
108 CALL hm_get_floatv('MAT_EPS' ,epsm ,is_available, lsubmodel, unitab)
109 CALL hm_get_floatv('MAT_SIG' ,sigm ,is_available, lsubmodel, unitab)
110! LINE 4
111 CALL hm_get_floatv('MAT_E0' ,e0 ,is_available, lsubmodel, unitab)
112! LINE 5
113 CALL hm_get_string('SSAM301' ,file ,ncharline ,is_available)
114! LINE 6
115 CALL hm_get_floatv('MAT_SRC' ,cc ,is_available, lsubmodel, unitab)
116 CALL hm_get_floatv('MAT_SRP' ,eps0 ,is_available, lsubmodel, unitab)
117 CALL hm_get_floatv('MAT_M' ,cm ,is_available, lsubmodel, unitab)
118 CALL hm_get_floatv('MAT_TMELT' ,tmelt ,is_available, lsubmodel, unitab)
119 CALL hm_get_floatv('MAT_TMAX' ,tmax ,is_available, lsubmodel, unitab)
120! DEFAULT UNITS
121 CALL hm_get_floatv_dim('MAT_SRP' ,eps0_unit ,is_available, lsubmodel, unitab)
122!
123 IF (cn == zero .OR. cn == one) cn = onep0001
124 IF (epsm == zero) epsm = infinity
125 IF (sigm == zero) sigm = infinity
126 IF (cc == zero) eps0 = one*eps0_unit
127 IF (cm == zero) cm = one ! dimensionless
128 IF (tmelt == zero)tmelt = infinity
129 IF (tmax == zero) tmax = infinity
130!
131 g=young/(two*(one+anu))
132 c1=young/(three*(one-two*anu))
133 IF (rhor == zero) rhor=rho0
134 pm(1) = rhor
135 pm(89)= rho0
136 pm(20)= young
137 pm(21)= anu
138 pm(22)= g
139 pm(23)= e0
140 pm(31)= zero
141 pm(32)= c1
142 pm(38)= ca
143 pm(39)= cb
144 pm(40)= cn
145 pm(41)= epsm
146 pm(42)= sigm
147 pm(43)= cc
148 pm(44)= eps0
149 pm(45)= cm
150 pm(46)= tmelt
151 pm(47)= tmax
152 pm(80)= tmelt
153C--------------------------------------
154C SESAME
155C--------------------------------------
156!-------------
157! SESAM301
158!-------------
159C
160 IF(len(trim(file))==0)THEN
161 CALL ancmsg(msgid=19,msgtype=msgerror,anmode=aninfo,i1=mat_id,c1='MATERIAL',c2='MATERIAL',c3=titr,c4=trim(file))
162 ELSE
163 OPEN(unit=31,file=file,status='OLD',form='FORMATTED',err=998)
164 ENDIF
165C
166 READ(31,*) i1,mat
167 READ(31,'(2E15.0)') xnr,xnt
168 rewind(31)
169 nr = nint(xnr)
170 nt = nint(xnt)
171 pm(25)=nr
172 pm(26)=nt
173 pm(27)=idf
174 idr = idf
175 idt = idr + nr
176 idp = idt + nt
177 ide = idp + nr * nt
178 idf = ide + nr * nt
179 mfi = mfi + idf - idr
180C
181 bufmat(idr:idf-1) = zero
182C
183 CALL mrdse2(bufmat(idr),nr,
184 + bufmat(idt),nt,bufmat(idp),bufmat(ide))
185 CLOSE(31)
186 pm(25)=nr
187 pm(26)=nt
188C
189 CALL mintp_re(bufmat(idr),nr,
190 + bufmat(idt),nt,bufmat(ide),rho0,t0,e0/rho0,dydz)
191 CALL mintp_rt(bufmat(idr),nr,
192 + bufmat(idt),nt,bufmat(idp),rho0,t0,p0,dpdr)
193C
194 WRITE(iout,1100) trim(titr),mat_id,ilaw
195 WRITE(iout,1000)
196 IF (is_encrypted) THEN
197 WRITE(iout,'(5X,A,//)')'CONFIDENTIAL DATA'
198 ELSE
199 WRITE(iout,1200) rho0,rhor
200 WRITE(iout,1300) young,anu,g
201 WRITE(iout,1400) ca,cb,cn,epsm,sigm
202 WRITE(iout,1500) file(1:len(trim(file))),p0,t0,e0
203 WRITE(iout,1600) cc,eps0,cm,tmelt,tmax
204 ENDIF
205C
206 IF (eps0 == zero) THEN
207 CALL ancmsg(msgid=298,
208 . msgtype=msgerror,
209 . anmode=aninfo,
210 . i1=26,
211 . i2=mat_id,
212 . c1=titr)
213 ENDIF
214C
215 sig = zero
216 xkmax = infinity
217 file = vide
218!-------------
219! SESAM504
220!-------------
221! LINE 7
222 CALL hm_get_string('SSAM504' ,file ,ncharline ,is_available)
223! LINE 8
224 CALL hm_get_floatv('K_Lor' ,xkl ,is_available, lsubmodel, unitab)
225 CALL hm_get_floatv('MAT_Lamda' ,xlamb ,is_available, lsubmodel, unitab)
226 CALL hm_get_floatv('MAT_A' ,atom ,is_available, lsubmodel, unitab)
227 CALL hm_get_floatv('MAT_K' ,xkmax ,is_available, lsubmodel, unitab)
228!
229 IF (file /= vide) jthe = 1
230 IF (xkmax ==zero) xkmax = infinity
231!
232 IF (jthe /= 0) THEN
233 IF(len(trim(file))==0)THEN
234 CALL ancmsg(msgid=19,msgtype=msgerror,anmode=aninfo,i1=mat_id,c1='MATERIAL',c2='MATERIAL',c3=titr,c4=trim(file))
235 ELSE
236 OPEN(unit=31,file=file,status='OLD',form='FORMATTED',err=998)
237 ENDIF
238 READ(31,*) i1,mat
239 READ(31,'(2E15.0)') xnr,xnt
240 rewind(31)
241 nr = nint(xnr)
242 nt = nint(xnt)
243 pm(28)=nr
244 pm(29)=nt
245 pm(30)=idf
246 idr = idf
247 idt = idr + nr
248 idq = idt + nt
249 idf = idq + nr * nt
250 mfi = mfi + idf - idr
251C
252 bufmat(idr:idf-1) = zero
253C
254 CALL mrdse3(bufmat(idr),nr,bufmat(idt),nt,bufmat(idq))
255 CLOSE(31)
256 pm(35)=xkl
257 pm(36)=xlamb
258 pm(37)=atom
259!
260!! PM(69)=INFINITY
261!
262!! WRITE(IOUT,1700) TRIM(FILE),XKL,XLAMB,ATOM,XKMAX
263 WRITE(iout,1700) file(1:len(trim(file))),xkl,xlamb,atom,xkmax
264 ENDIF ! IF (JTHE /= 0)
265!-------------
266! SESAM502
267!-------------
268! LINE 9
269 CALL hm_get_string('SSAM502' ,file ,ncharline ,is_available)
270! LINE 10
271 CALL hm_get_floatv('Sigma_k' ,sig ,is_available, lsubmodel, unitab)
272!
273 IF (sig > zero) THEN
274 IF(len(trim(file))==0)THEN
275 CALL ancmsg(msgid=19,msgtype=msgerror,anmode=aninfo,i1=mat_id,c1='MATERIAL',c2='MATERIAL',c3=titr,c4=trim(file))
276 ELSE
277 OPEN(unit=31,file=file,status='OLD',form='FORMATTED',err=998)
278 ENDIF
279 READ(31,*)i1,mat
280 READ(31,'(2E15.0)')xnr,xnt
281 rewind(31)
282 nr = nint(xnr)
283 nt = nint(xnt)
284 pm(48)=nr
285 pm(49)=nt
286 pm(50)=idf
287 idr = idf
288 idt = idr + nr
289 idq = idt + nt
290 idf = idq + nr * nt
291 mfi = mfi + idf - idr
292C
293 bufmat(idr:idf-1) = zero
294C
295 CALL mrdse3(bufmat(idr),nr,bufmat(idt),nt,bufmat(idq))
296 CLOSE(31)
297 ENDIF
298!! IF (JTHE /= 0 .AND. .not. IS_ENCRYPTED) WRITE(IOUT,1800)TRIM(FILE),SIG
299 IF (jthe /= 0 .AND. .not. is_encrypted) WRITE(iout,1800)file(1:len(trim(file))),sig
300C
301 pm(51)=sig
302 pm(52)=xkmax
303!
304!----------------------
305 jthe = 0 !
306!----------------------
307!
308c
309C---- Definition des variables internes (stockage elementaire)
310c
311 mtag%G_PLA = 1
312 mtag%G_TEMP = 1
313 mtag%G_EPSD = 1
314c
315 mtag%L_PLA = 1
316 mtag%L_TEMP = 1
317 mtag%L_EPSD = 1
318 mtag%L_SSP = 1
319 mtag%L_Z = 1 ! taux ionisation
320c
321 ! MATPARAM keywords
322 CALL init_mat_keyword(matparam,"INCOMPRESSIBLE")
323
324 ! EOS/Thermo keyword for pressure treatment in elements
325 CALL init_mat_keyword(matparam,"HYDRO_EOS")
326
327c
328 ! Properties compatibility
329 CALL init_mat_keyword(matparam,"SOLID_ISOTROPIC")
330c-----------
331 RETURN
332c-----------
333 998 CONTINUE
334 CALL ancmsg(msgid=19,
335 . msgtype=msgerror,
336 . anmode=aninfo,
337 . i1=mat_id,
338 . c1='MATERIAL',
339 . c2='MATERIAL',
340 . c3=titr,
341 . c4=trim(file))
342 RETURN
343c-----------
344 1000 FORMAT(
345 & 5x,40h johnson cook - sesame law ,/,
346 & 5x,40h ----------------------- ,//)
347 1100 FORMAT(
348 & 5x,a,/,
349 & 5x,'MATERIAL NUMBER . . . . . . . . . . . .=',i10/,
350 & 5x,'MATERIAL LAW. . . . . . . . . . . . . .=',i10/)
351 1200 FORMAT(
352 & 5x,'INITIAL DENSITY . . . . . . . . . . . .=',1pg20.13/,
353 & 5x,'REFERENCE DENSITY . . . . . . . . . . .=',1pg20.13/)
354 1300 FORMAT(
355 & 5x,40hyoung'S MODULUS . . . . . . . . . . . .=,E12.4/,
356 & 5X,40HPOISSON's ratio . . . . . . . . . . . .=,e12.4/,
357 & 5x,40hshear modulus . . . . . . . . . . . . .=,e12.4//)
358 1400 FORMAT(
359 & 5x,40hyield coefficient ca. . . . . . . . . .=,e12.4/,
360 & 5x,40hyield coefficient cb. . . . . . . . . .=,e12.4/,
361 & 5x,40hyield coefficient cn. . . . . . . . . .=,e12.4/,
362 & 5x,40heps-max . . . . . . . . . . . . . . . .=,e12.4/,
363 & 5x,40hsig-max . . . . . . . . . . . . . . . .=,e12.4//)
364 1500 FORMAT(
365 & 5x,'SESAME EOS TABLE :',a/,
366 & 5x,40hinitial pressure. . . . . . . . . . . .=,e12.4/,
367 & 5x,40hinitial temperature . . . . . . . . . .=,e12.4/,
368 & 5x,40hinitial internal energy per unit volume=,e12.4//)
369 1600 FORMAT(
370 & 5x,40hstrain rate coefficient cc. . . . . . .=,e12.4/,
371 & 5x,40hreference strain rate . . . . . . . . .=,e12.4/,
372 & 5x,40htemperature exponent. . . . . . . . . .=,e12.4/,
373 & 5x,40hmelting temperature degree k. . . . . .=,e12.4/,
374 & 5x,40htheta-max . . . . . . . . . . . . . . .=,e12.4//)
375 1700 FORMAT(
376 & 5x,'ELECTRON THERMAL CONDUCTIVITY',/,
377 & 5x,'-----------------------------',/,
378 & 5x,'SESAME IONIZATION TABLE :',a/,
379 & 5x,40hlorentz conductivity coefficient. . . .=,e12.4/,
380 & 5x,40hlambda coefficient. . . . . . . . . . .=,e12.4/,
381 & 5x,40hatomic weight . . . . . . . . . . . . .=,e12.4/,
382 & 5x,40hmaximum conductivity. . . . . . . . . .=,e12.4//)
383 1800 FORMAT(
384 & 5x,'RADIATION',/,
385 & 5x,'---------',/,
386 & 5x,'SESAME ROSSELAND OPACITY TABLE :',a/,
387 & 5x,40hstefan-boltzmann constant . . . . . . .=,e12.4//)
388c-----------
389 RETURN
390 END
391c-----------
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
subroutine hm_get_floatv_dim(name, dim_fac, is_available, lsubmodel, unitab)
subroutine hm_get_string(name, sval, size, is_available)
subroutine hm_option_is_encrypted(is_encrypted)
subroutine hm_read_mat26(mtag, pm, mat_id, titr, ipm, jthe, bufmat, mfi, idf, lsubmodel, unitab, matparam)
subroutine init_mat_keyword(matparam, keyword)
#define max(a, b)
Definition macros.h:21
subroutine mintp_re(xx, nx, yy, ny, zz, x, y, z, dydz)
Definition mintp_re.F:34
subroutine mintp_rt(xx, nx, yy, ny, zz, x, y, z, dzdx)
Definition mintp_rt.F:35
subroutine mrdse2(rr, nr, tt, nt, pp, ee)
Definition mrdse2.F:31
subroutine mrdse3(rr, nr, tt, nt, qq)
Definition mrdse3.F:31
integer, parameter nchartitle
integer, parameter ncharline
subroutine sesame(iflag, nel, pm, off, eint, rho, rho0, espe, dvol, mat, pnew, dpdm, dpde, theta, bufmat)
Definition sesame.F:35
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889
program starter
Definition starter.F:39