OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_mat115.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_mat115 ../starter/source/materials/mat/mat115/hm_read_mat115.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_intv ../starter/source/devtools/hm_reader/hm_get_intv.F
31!|| hm_option_is_encrypted ../starter/source/devtools/hm_reader/hm_option_is_encrypted.F
32!|| init_mat_keyword ../starter/source/materials/mat/init_mat_keyword.F
33!||--- uses -----------------------------------------------------
34!|| elbuftag_mod ../starter/share/modules1/elbuftag_mod.F
35!|| message_mod ../starter/share/message_module/message_mod.F
36!|| submodel_mod ../starter/share/modules1/submodel_mod.F
37!||====================================================================
38 SUBROUTINE hm_read_mat115(
39 . UPARAM ,MAXUPARAM,NUPARAM ,NUVAR ,NTABL ,
40 . MTAG ,PARMAT ,UNITAB ,PM ,LSUBMODEL,
41 . ISRATE ,MAT_ID ,TITR ,ITABLE ,MAXTABL ,
42 . NVARTMP ,MATPARAM )
43C-----------------------------------------------
44C M o d u l e s
45C-----------------------------------------------
46 USE unitab_mod
47 USE message_mod
48 USE submodel_mod
49 USE elbuftag_mod
50 USE matparam_def_mod
52C-----------------------------------------------
53C I m p l i c i t T y p e sXM
54C-----------------------------------------------
55#include "implicit_f.inc"
56C-----------------------------------------------
57C C o m m o n B l o c k s
58C-----------------------------------------------
59#include "com04_c.inc"
60#include "units_c.inc"
61#include "param_c.inc"
62C-----------------------------------------------
63C D u m m y A r g u m e n t s
64C-----------------------------------------------
65 TYPE (UNIT_TYPE_),INTENT(IN) :: UNITAB
66 INTEGER, INTENT(IN) :: MAT_ID,MAXUPARAM,MAXTABL
67 my_real, DIMENSION(NPROPM) ,INTENT(INOUT) :: PM
68 CHARACTER(LEN=NCHARTITLE) ,INTENT(IN) :: TITR
69 INTEGER, INTENT(INOUT) :: ISRATE,ITABLE(MAXTABL)
70 INTEGER, INTENT(INOUT) :: NUPARAM,NUVAR,NTABL,NVARTMP
71 my_real, DIMENSION(MAXUPARAM) ,INTENT(INOUT) :: uparam
72 my_real, DIMENSION(100),INTENT(INOUT) :: parmat
73 TYPE(submodel_data), DIMENSION(*),INTENT(IN) :: LSUBMODEL
74 TYPE(mlaw_tag_), INTENT(INOUT) :: MTAG
75 TYPE(matparam_struct_) ,INTENT(INOUT) :: MATPARAM
76C-----------------------------------------------
77C L o c a l V a r i a b l e s
78C-----------------------------------------------
79 INTEGER I, J, K, ILAW, Ivflag, NANGLE, INFO, Icrit, TAB_YLD, Ismooth,
80 . TAB_TEMP,ITER,Ires,Istat
81C REAL
82 my_real
83 . rho0,young,nu,alpha,gamma,epsd,alpha2,beta,sigp,cfail,pfail,
84 . g,g2,lam,bulk,nnu,nnu1,rhof0,sigp_c0,sigp_c1,sigp_n,alpha2_c0,
85 . alpha2_c1,alpha2_n,gamma_c0,gamma_c1,gamma_n,beta_c0,beta_c1,beta_n
86C
87 LOGICAL :: IS_AVAILABLE,IS_ENCRYPTED
88C=======================================================================
89 IS_ENCRYPTED = .false.
90 is_available = .false.
91 ilaw = 115
92c------------------------------------------
93 CALL hm_option_is_encrypted(is_encrypted)
94c------------------------------------------
95c
96card1 - Density
97 CALL hm_get_floatv('MAT_RHO' ,rho0 ,is_available, lsubmodel, unitab)
98card2 - Elasticity
99 CALL hm_get_floatv('MAT_E' ,young ,is_available, lsubmodel, unitab)
100 CALL hm_get_floatv('MAT_NU' ,nu ,is_available, lsubmodel, unitab)
101 CALL hm_get_intv ('MAT_IRES' ,ires ,is_available, lsubmodel)
102 CALL hm_get_intv ('MAT_ISTAT' ,istat ,is_available, lsubmodel)
103c
104 ! Constant parameter
105 IF (istat == 0) THEN
106card3
107 CALL hm_get_floatv('MAT_ALPHA' ,alpha ,is_available, lsubmodel, unitab)
108 CALL hm_get_floatv('MAT_CFAIL' ,cfail ,is_available, lsubmodel, unitab)
109 CALL hm_get_floatv('MAT_PFAIL' ,pfail ,is_available, lsubmodel, unitab)
110card4
111 CALL hm_get_floatv('MAT_SIGP' ,sigp ,is_available, lsubmodel, unitab)
112 CALL hm_get_floatv('mat_gamma' ,GAMMA ,IS_AVAILABLE, LSUBMODEL, UNITAB)
113 CALL HM_GET_FLOATV('mat_epsd' ,EPSD ,IS_AVAILABLE, LSUBMODEL, UNITAB)
114 CALL HM_GET_FLOATV('mat_alpha2',ALPHA2 ,IS_AVAILABLE, LSUBMODEL, UNITAB)
115 CALL HM_GET_FLOATV('mat_beta' ,BETA ,IS_AVAILABLE, LSUBMODEL, UNITAB)
116c
117 ! Statistical variation parameter
118 ELSE
119card3
120 CALL HM_GET_FLOATV('mat_alpha' ,ALPHA ,IS_AVAILABLE, LSUBMODEL, UNITAB)
121 CALL HM_GET_FLOATV('mat_cfail' ,CFAIL ,IS_AVAILABLE, LSUBMODEL, UNITAB)
122 CALL HM_GET_FLOATV('mat_pfail' ,PFAIL ,IS_AVAILABLE, LSUBMODEL, UNITAB)
123 CALL HM_GET_FLOATV('mat_rhof0' ,RHOF0 ,IS_AVAILABLE, LSUBMODEL, UNITAB)
124
125 CALL HM_GET_FLOATV('mat_sigp_c0' ,SIGP_C0 ,IS_AVAILABLE, LSUBMODEL, UNITAB)
126 CALL HM_GET_FLOATV('mat_sigp_c1' ,SIGP_C1 ,IS_AVAILABLE, LSUBMODEL, UNITAB)
127 CALL HM_GET_FLOATV('mat_sigp_n' ,SIGP_N ,IS_AVAILABLE, LSUBMODEL, UNITAB)
128
129 CALL HM_GET_FLOATV('mat_alpha2_c0' ,ALPHA2_C0 ,IS_AVAILABLE, LSUBMODEL, UNITAB)
130 CALL HM_GET_FLOATV('mat_alpha2_c1' ,ALPHA2_C1 ,IS_AVAILABLE, LSUBMODEL, UNITAB)
131 CALL HM_GET_FLOATV('mat_alpha2_n' ,ALPHA2_N ,IS_AVAILABLE, LSUBMODEL, UNITAB)
132
133 CALL HM_GET_FLOATV('mat_gamma_c0' ,GAMMA_C0 ,IS_AVAILABLE, LSUBMODEL, UNITAB)
134 CALL HM_GET_FLOATV('mat_gamma_c1' ,GAMMA_C1 ,IS_AVAILABLE, LSUBMODEL, UNITAB)
135 CALL HM_GET_FLOATV('mat_gamma_n' ,GAMMA_N ,IS_AVAILABLE, LSUBMODEL, UNITAB)
136
137 CALL HM_GET_FLOATV('mat_beta_c0' ,BETA_C0 ,IS_AVAILABLE, LSUBMODEL, UNITAB)
138 CALL HM_GET_FLOATV('mat_beta_c1' ,BETA_C1 ,IS_AVAILABLE, LSUBMODEL, UNITAB)
139 CALL HM_GET_FLOATV('mat_beta_n' ,BETA_N ,IS_AVAILABLE, LSUBMODEL, UNITAB)
140
141 ENDIF
142c
143c---------------------
144c Default values
145c---------------------
146 ! Density
147.OR. IF ((Ires == 0)(Ires > 2)) Ires = 2
148 ! Poisson's ratio
149 IF (nu < zero .OR. nu >= half) THEN
150 CALL ancmsg(msgid=49,
151 . msgtype=msgerror,
152 . anmode=aninfo_blind_2,
153 . r1=nu,
154 . i1=mat_id,
155 . c1=titr)
156 ENDIF
157 ! Elasticity parameter
158 g2 = young / (one + nu)
159 g = half * g2
160 lam = g2 * nu /(one - two*nu)
161 bulk = third * young / (one - nu*two)
162 nnu = nu / (one - nu)
163 nnu1 = one - nnu
164 ! Plastic data initialization
165 IF (istat == 0) THEN
166 ! Initial yield stress
167 IF (sigp == zero) sigp = infinity
168 IF (sigp < zero) THEN
169 CALL ancmsg(msgid=1901,
170 . msgtype=msgerror,
171 . anmode=aninfo_blind_2,
172 . r1=sigp,
173 . i1=mat_id,
174 . c1=titr)
175 ENDIF
176 ! Densification strain
177 IF (epsd == zero) epsd = infinity
178 IF (epsd < zero) THEN
179 CALL ancmsg(msgid=1900,
180 . msgtype=msgerror,
181 . anmode=aninfo_blind_2,
182 . r1=epsd,
183 . i1=mat_id,
184 . c1=titr)
185 ENDIF
186 ! Beta parameter
187 IF (beta == zero) beta = one
188 ENDIF
189 ! Yield function shape parameter
190 IF ((alpha < zero).OR.(alpha > sqrt(4.5d0))) THEN
191 CALL ancmsg(msgid=1897,
192 . msgtype=msgerror,
193 . anmode=aninfo_blind_2,
194 . r1=alpha,
195 . i1=mat_id,
196 . c1=titr)
197 ENDIF
198 ! Tensile volumetric strain at failure
199 IF (cfail < zero) THEN
200 CALL ancmsg(msgid=1898,
201 . msgtype=msgerror,
202 . anmode=aninfo_blind_2,
203 . r1=cfail,
204 . i1=mat_id,
205 . c1=titr)
206 ENDIF
207 ! Maximum principal strain at failure
208 IF (pfail < zero) THEN
209 CALL ancmsg(msgid=1899,
210 . msgtype=msgerror,
211 . anmode=aninfo_blind_2,
212 . r1=pfail,
213 . i1=mat_id,
214 . c1=titr)
215 ENDIF
216 ! Check for /PERTURB/PART/SOLID card
217 IF (istat == 1) THEN
218 ! Warning if no cards are detected
219 IF (nperturb == 0) THEN
220 CALL ancmsg(msgid=1916,
221 . msgtype=msgwarning,
222 . anmode=aninfo_blind_2,
223 . i1=mat_id,
224 . c1=titr)
225 ENDIF
226 ENDIF
227c
228c--------------------------
229c Filling buffer tables
230c--------------------------
231 ! Number of material parameter
232 IF (istat == 0) THEN
233 nuparam = 20
234 ELSE
235 nuparam = 28
236 ENDIF
237 ! Number of function and temp variable
238 ntabl = 0
239 nvartmp = 0
240 ! Number of user variable
241 IF (ires == 1) THEN
242 IF (cfail > zero) THEN
243 nuvar = 2
244 ELSE
245 nuvar = 1
246 ENDIF
247 ELSE
248 IF (cfail > zero) THEN
249 nuvar = 1
250 ELSE
251 nuvar = 0
252 ENDIF
253 ENDIF
254c
255 ! Material parameters
256 uparam(1) = young ! Young modulus
257 uparam(2) = bulk ! Bulk modulus
258 uparam(3) = g ! Shear modulus
259 uparam(4) = g2 ! 2*Shear modulus
260 uparam(5) = lam ! Lambda (Hook)
261 uparam(6) = nu ! Poisson ratio
262 uparam(7) = nnu
263 uparam(8) = nnu1
264 uparam(11) = ires ! Choice of the return mapping algorithm
265 uparam(12) = istat ! Choice of the statistical variation
266 uparam(13) = alpha ! Yield function shape parameter
267 uparam(14) = cfail ! Tensile volumic strain at failure
268 uparam(15) = pfail ! Principal stress at failure
269 IF (istat == 0) THEN
270 uparam(16) = gamma ! Yield stress parameter
271 uparam(17) = epsd ! Densification strain
272 uparam(18) = alpha2 ! Yield stress parameter
273 uparam(19) = beta ! Yield stress parameter
274 uparam(20) = sigp ! Initial yield stress
275 ELSE
276 uparam(16) = rhof0 ! Yield stress parameter
277 uparam(17) = sigp_c0 ! Densification strain
278 uparam(18) = sigp_c1 ! Yield stress parameter
279 uparam(19) = sigp_n ! Yield stress parameter
280 uparam(20) = alpha2_c0 ! Initial yield stress
281 uparam(21) = alpha2_c1 ! Tensile volumic strain at failure
282 uparam(22) = alpha2_n ! Principal stress at failure
283 uparam(23) = gamma_c0 ! Initial yield stress
284 uparam(24) = gamma_c1 ! Tensile volumic strain at failure
285 uparam(25) = gamma_n ! Principal stress at failure
286 uparam(26) = beta_c0 ! Initial yield stress
287 uparam(27) = beta_c1 ! Tensile volumic strain at failure
288 uparam(28) = beta_n ! Principal stress at failure
289 ENDIF
290c
291 ! PARMAT table
292 parmat(1) = bulk
293 parmat(2) = young
294 parmat(3) = nu
295 parmat(4) = zero
296 parmat(5) = zero
297 israte = 0
298c
299 ! PM table
300 pm(1) = rho0
301 pm(89) = rho0
302 pm(27) = sqrt((bulk + four_over_3*g)/rho0) ! sound speed estimation
303 pm(100)= bulk
304c
305 ! MTAG variable activation
306 mtag%G_PLA = 1
307 mtag%L_PLA = 1
308 mtag%L_SEQ = 1
309 mtag%G_SEQ = 1
310 mtag%L_RHO = 2
311 mtag%G_RHO = 2
312c
313 CALL init_mat_keyword(matparam ,"COMPRESSIBLE")
314 CALL init_mat_keyword(matparam ,"INCREMENTAL" )
315 CALL init_mat_keyword(matparam ,"LARGE_STRAIN")
316 CALL init_mat_keyword(matparam ,"HOOK")
317c
318 ! Properties compatibility
319 CALL init_mat_keyword(matparam,"SOLID_ISOTROPIC")
320c
321c--------------------------
322c Parameters printout
323c--------------------------
324 WRITE(iout,1000) trim(titr),mat_id,ilaw
325 WRITE(iout,1100)
326 IF (is_encrypted) THEN
327 WRITE(iout,'(5X,A,//)')'CONFIDENTIAL DATA'
328 ELSE
329 WRITE(iout,1200) rho0
330 WRITE(iout,1300) young,nu
331 WRITE(iout,1350) ires
332 WRITE(iout,1375) istat
333 IF (istat == 0) THEN
334 WRITE(iout,1400) alpha,gamma,epsd,alpha2,beta,sigp,cfail,pfail
335 ELSE
336 WRITE(iout,1450) alpha,rhof0,sigp_c0,sigp_c1,sigp_n,alpha2_c0,
337 . alpha2_c1,alpha2_n,gamma_c0,gamma_c1,gamma_n,
338 . beta_c0,beta_c1,beta_n,cfail,pfail
339 ENDIF
340 ENDIF
341c-----------------------------------------------------------------------
342 1000 FORMAT(/
343 & 5x,a,/,
344 & 5x,'MATERIAL NUMBER. . . . . . . . . . . . =',i10/,
345 & 5x,'MATERIAL LAW . . . . . . . . . . . . . =',i10/)
346 1100 FORMAT
347 &(5x,'MATERIAL MODEL : DESHPANDE AND FLECK FOAM',/,
348 & 5x,'-----------------------------------------',/)
349 1200 FORMAT(
350 & 5x,'INITIAL DENSITY . . . . . . . . . . . .=',1pg20.13/)
351 1300 FORMAT(
352 & 5x,'YOUNG MODULUS . . . . . . . . . . . . .=',1pg20.13/
353 & 5x,'POISSON RATIO . . . . . . . . . . . . .=',1pg20.13/)
354 1350 FORMAT(
355 & 5x,'RETURN MAPPING ALGORITHM FLAG . . . . .=',i3/
356 & 5x,' IRES=1 NICE EXPLICIT'/
357 & 5x,' IRES=2 NEWTON-ITERATION IMPLICIT (CUTTING PLANE)'/)
358 1375 FORMAT(
359 & 5x,'STATISTICAL VARIATION FLAG . . . . . .=',i3/)
360 1400 FORMAT(
361 & 5x,'YIELD SURFACE SHAPE PARAMETER ALPHA . .=',1pg20.13/
362 & 5x,'LINEAR HARDENING MODULUS GAMMA . . . .=',1pg20.13/
363 & 5x,'DENSIFICATION STRAIN EPSD . . . . . . .=',1pg20.13/
364 & 5x,'NON-LINEAR HARDENING MODULUS ALPHA2 . .=',1pg20.13/
365 & 5x,'NON-LINEAR HARDENING EXPONENT BETA . .=',1pg20.13/
366 & 5x,'INITIAL YIELD STRESS SIGP . . . . . . .=',1pg20.13/
367 & 5x,'TENSILE VOLUMETRIC STRAIN AT FAILURE .=',1pg20.13/
368 & 5x,'MAX. PRINCIPAL STRESS AT FAILURE . . .=',1pg20.13/)
369 1450 FORMAT(
370 & 5x,'YIELD SURFACE SHAPE PARAMETER ALPHA . .=',1pg20.13/
371 & 5x,'DENSITY OF BASE MATERIAL . . . . . . .=',1pg20.13/
372 & 5x,'INITIAL YIELD STRESS PARAM. SIGP_C0 . .=',1pg20.13/
373 & 5x,'INITIAL YIELD STRESS PARAM. SIGP_C1 . .=',1pg20.13/
374 & 5x,'INITIAL YIELD STRESS EXPO. SIGP_N . .=',1pg20.13/
375 & 5x,'NON-LINEAR HARDENING PARAM. ALPHA2_C0 .=',1pg20.13/
376 & 5x,'NON-LINEAR HARDENING PARAM. ALPHA2_C1 .=',1pg20.13/
377 & 5x,'NON-LINEAR HARDENING EXPO. ALPHA2_N .=',1pg20.13/
378 & 5x,'LINEAR HARDENING PARAM. GAMMA_C0 . . .=',1pg20.13/
379 & 5x,'LINEAR HARDENING PARAM. GAMMA_C1 . . .=',1pg20.13/
380 & 5x,'LINEAR HARDENING PARAM. GAMMA_N . . . .=',1pg20.13/
381 & 5x,'NON-LINEAR HARDENING EXPO. BETA_C0 . .=',1pg20.13/
382 & 5x,'NON-LINEAR HARDENING EXPO. BETA_C1 . .=',1pg20.13/
383 & 5x,'NON-LINEAR HARDENING EXPO. BETA_N . .=',1pg20.13/
384 & 5x,'TENSILE VOLUMETRIC STRAIN AT FAILURE .=',1pg20.13/
385 & 5x,'MAX. PRINCIPAL STRESS AT FAILURE . . .=',1pg20.13/)
386c-----------------------------------------------------------------------
387 RETURN
388 END
#define alpha2
Definition eval.h:48
#define alpha
Definition eval.h:35
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_is_encrypted(is_encrypted)
subroutine hm_read_mat115(uparam, maxuparam, nuparam, nuvar, ntabl, mtag, parmat, unitab, pm, lsubmodel, israte, mat_id, titr, itable, maxtabl, nvartmp, matparam)
subroutine init_mat_keyword(matparam, keyword)
integer, parameter nchartitle
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