OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_mat72.F File Reference
#include "implicit_f.inc"
#include "units_c.inc"
#include "param_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine hm_read_mat72 (uparam, maxuparam, nuparam, israte, imatvis, nuvar, ifunc, maxfunc, nfunc, parmat, unitab, mat_id, titr, mtag, lsubmodel, pm, matparam)

Function/Subroutine Documentation

◆ hm_read_mat72()

subroutine hm_read_mat72 ( dimension(maxuparam), intent(inout) uparam,
integer, intent(inout) maxuparam,
integer, intent(inout) nuparam,
integer, intent(inout) israte,
integer, intent(inout) imatvis,
integer, intent(inout) nuvar,
integer, dimension(maxfunc), intent(inout) ifunc,
integer, intent(inout) maxfunc,
integer, intent(inout) nfunc,
dimension(100), intent(inout) parmat,
type (unit_type_), intent(in) unitab,
integer, intent(in) mat_id,
character(len=nchartitle), intent(in) titr,
type(mlaw_tag_), intent(inout) mtag,
type(submodel_data), dimension(*), intent(in) lsubmodel,
dimension(npropm), intent(inout) pm,
type(matparam_struct_), intent(inout) matparam )

Definition at line 37 of file hm_read_mat72.F.

41C-----------------------------------------------
42C D e s c r i p t i o n
43C-----------------------------------------------
44C READ MAT LAW43 WITH HM READER ( TO BE COMPLETED )
45C
46C DUMMY ARGUMENTS DESCRIPTION:
47C ===================
48C
49C NAME DESCRIPTION
50C
51C PM MATERIAL ARRAY(REAL)
52C UNITAB UNITS ARRAY
53C MAT_ID MATERIAL ID(INTEGER)
54C TITR MATERIAL TITLE
55C LSUBMODEL SUBMODEL STRUCTURE
56C
57C-----------------------------------------------
58C M o d u l e s
59C-----------------------------------------------
60 USE unitab_mod
61 USE elbuftag_mod
62 USE message_mod
63 USE submodel_mod
64 USE matparam_def_mod
66C-----------------------------------------------
67C I m p l i c i t T y p e s
68C-----------------------------------------------
69#include "implicit_f.inc"
70C-----------------------------------------------
71C C o m m o n B l o c k s
72C-----------------------------------------------
73#include "units_c.inc"
74#include "param_c.inc"
75C-----------------------------------------------
76C D u m m y A r g u m e n t s
77C-----------------------------------------------
78 TYPE (UNIT_TYPE_),INTENT(IN) :: UNITAB
79 my_real, INTENT(INOUT) :: pm(npropm),parmat(100),uparam(maxuparam)
80 INTEGER, INTENT(INOUT) :: ISRATE,IFUNC(MAXFUNC),NFUNC,MAXFUNC,MAXUPARAM,NUPARAM, NUVAR,IMATVIS
81 TYPE(MLAW_TAG_),INTENT(INOUT) :: MTAG
82 INTEGER,INTENT(IN) :: MAT_ID
83 CHARACTER(LEN=NCHARTITLE) ,INTENT(IN) :: TITR
84 TYPE(SUBMODEL_DATA),INTENT(IN) :: LSUBMODEL(*)
85 TYPE(MATPARAM_STRUCT_) ,INTENT(INOUT) :: MATPARAM
86C-----------------------------------------------
87C L o c a l V a r i a b l e s
88C-----------------------------------------------
89 my_real
90 . rho0,rhor,
91 . e,nu,g,g2,c11,a1,a2,lamhook,
92 . cp,eps0,sigy,exp,
93 . ff,gg,hh,nn,ll,mm,
94 . c1,c2,c3,dc,mexp
95 INTEGER ILAW
96 LOGICAL :: IS_AVAILABLE,IS_ENCRYPTED
97C=======================================================================
98C-----------------------------------------------
99C S o u r c e L i n e s
100C-----------------------------------------------
101 is_encrypted = .false.
102 is_available = .false.
103 ilaw = 72
104C
105c------------------------------------------
106 CALL hm_option_is_encrypted(is_encrypted)
107c------------------------------------------
108c
109card1 - Density
110 CALL hm_get_floatv('MAT_RHO' ,rho0 ,is_available, lsubmodel, unitab)
111card2 - Isotropic elastic parameters
112 CALL hm_get_floatv('MAT_E' ,e ,is_available, lsubmodel, unitab)
113 CALL hm_get_floatv('MAT_NU' ,nu ,is_available, lsubmodel, unitab)
114card3 - Hardening parameter + Hill yield criterion parameters
115 CALL hm_get_floatv('SIGMA_r' ,sigy ,is_available, lsubmodel, unitab)
116 CALL hm_get_floatv('Epsilon_0' ,eps0 ,is_available, lsubmodel, unitab)
117 CALL hm_get_floatv('MAT_n1_t' ,exp ,is_available, lsubmodel, unitab)
118 CALL hm_get_floatv('MAT_F' ,ff ,is_available, lsubmodel, unitab)
119 CALL hm_get_floatv('MAT_G0' ,gg ,is_available, lsubmodel, unitab)
120card4 - Hill yield criterion parameters
121 CALL hm_get_floatv('MAT_HARD' ,hh ,is_available, lsubmodel, unitab)
122 CALL hm_get_floatv('MAT_N' ,nn ,is_available, lsubmodel, unitab)
123 CALL hm_get_floatv('MAT_Lamda' ,ll ,is_available, lsubmodel, unitab)
124 CALL hm_get_floatv('MAT_M' ,mm ,is_available, lsubmodel, unitab)
125card5 - Modified Mohr Coulomb failure criterion parameter
126 CALL hm_get_floatv('MAT_C1' ,c1 ,is_available, lsubmodel, unitab)
127 CALL hm_get_floatv('MAT_C2' ,c2 ,is_available, lsubmodel, unitab)
128 CALL hm_get_floatv('MAT_C3' ,c3 ,is_available, lsubmodel, unitab)
129 CALL hm_get_floatv('MAT_MUE1' ,mexp ,is_available, lsubmodel, unitab)
130 CALL hm_get_floatv('MAT_Dc' ,dc ,is_available, lsubmodel, unitab)
131C
132 !========== DEFAULT VALUES=============!
133C
134 ! Poisson's ratio
135 IF (nu < zero .OR. nu >= half) THEN
136 CALL ancmsg(msgid=49,
137 . msgtype=msgerror,
138 . anmode=aninfo_blind_2,
139 . r1=nu,
140 . i1=mat_id,
141 . c1=titr)
142 ENDIF
143 ! Critical damage
144 IF (dc == zero) dc = one
145 ! Error message, DC < 1
146 IF (dc < one) THEN
147 CALL ancmsg(msgid=1894,
148 . msgtype=msgerror,
149 . anmode=aninfo_blind_2,
150 . r1=dc,
151 . i1=mat_id,
152 . c1=titr)
153 ENDIF
154 ! Test for HILL coefficient
155 IF ((ff<zero).OR.(gg<zero).OR.(hh<zero).OR.
156 . (ll<zero).OR.(mm<zero).OR.(nn<zero)) THEN
157 CALL ancmsg(msgid=1895,
158 . msgtype=msgerror,
159 . anmode=aninfo_blind_2,
160 . i1=mat_id,
161 . c1=titr)
162 ENDIF
163 ! Hardening exponent
164 IF (exp == zero) exp = one
165 ! Failure criterion exponent
166 IF (mexp == zero) mexp = one
167 ! Initial yield stress
168 IF (sigy == zero) sigy = infinity
169 IF (c2 == zero) c2 = sigy
170 ! Make sure initial plastic strain is strictly positive
171 IF (eps0 < zero) THEN
172 CALL ancmsg(msgid=2080,
173 . msgtype=msgwarning,
174 . anmode=aninfo_blind_1,
175 . i1=mat_id,
176 . c1=titr)
177 ENDIF
178 eps0 = max(eps0,em20)
179C
180 ! Elastic parameters
181 ! -> 3D isotropic elastic matrix components
182 a1 = e*(one-nu) /((one + nu)*(one - two*nu))
183 a2 = a1*nu/(one - nu)
184 ! -> Bulk modulus
185 c11 = e/three/(one - two*nu)
186 ! -> Shear modulus
187 g = half*e/( one + nu)
188 g2 = two*g
189 ! -> Hooke's lambda parameter
190 lamhook = g2 * nu /(one - two*nu)
191C
192 ! PM table
193 rhor = rho0
194 pm(1) = rhor
195 pm(89) = rho0
196C
197 ! PARMAT table
198 parmat(1) = c11
199 parmat(2) = e
200 parmat(3) = nu
201 parmat(4) = zero
202 parmat(5) = zero
203 parmat(16) = 2
204 parmat(17) = two*g/(c11+four_over_3*g)
205C
206 ! MTAG variable activation
207 mtag%G_SEQ = 1
208 mtag%L_SEQ = 1
209 mtag%G_PLA = 1
210 mtag%L_PLA = 1
211 mtag%G_DMG = 1
212 mtag%L_DMG = 1
213C
214 ! MATPARAM parameters
215 CALL init_mat_keyword(matparam,"ELASTO_PLASTIC")
216 CALL init_mat_keyword(matparam,"INCREMENTAL" )
217 CALL init_mat_keyword(matparam,"LARGE_STRAIN" )
218 CALL init_mat_keyword(matparam,"HOOK")
219 CALL init_mat_keyword(matparam,"ORTHOTROPIC")
220C
221 ! Properties compatibility
222 CALL init_mat_keyword(matparam,"SHELL_ORTHOTROPIC")
223 CALL init_mat_keyword(matparam,"SOLID_ORTHOTROPIC")
224 CALL init_mat_keyword(matparam,"SPH")
225C
226 ! No viscosity, no strain-rate filtering
227 israte = 0
228 imatvis = 0
229C
230c--------------------------
231c Filling buffer tables
232c--------------------------
233 ! Number of material parameter
234 nuparam = 24
235 ! Number of user variable
236 nuvar = 1
237c
238 ! Filling the parameter table
239 ! -> Elastic parameters
240 uparam(1) = e
241 uparam(2) = nu
242 uparam(3) = g
243 uparam(4) = g2
244 ! -> Plane stress isotropic elastic matrix components (for shells)
245 uparam(5) = e/(one - nu*nu)
246 uparam(6) = nu*uparam(4)
247 ! -> 3D isotropic elastic matrix components (for solids)
248 uparam(7) = a1
249 uparam(8) = a2
250 ! -> Bulk modulus
251 uparam(9) = c11
252 ! -> Hooke's lambda parameter
253 uparam(10) = lamhook
254 ! -> Hardening parameters
255 uparam(11) = sigy
256 uparam(12) = eps0
257 uparam(13) = exp
258 ! -> Yield criterion parameters
259 uparam(14) = ff
260 uparam(15) = gg
261 uparam(16) = hh
262 uparam(17) = nn
263 uparam(18) = ll
264 uparam(19) = mm
265 ! -> Failure criterion parameters
266 uparam(20) = c1
267 uparam(21) = c2
268 uparam(22) = c3
269 uparam(23) = mexp
270 uparam(24) = dc
271C
272c--------------------------
273c Parameters printout
274c--------------------------
275 WRITE(iout,1001) trim(titr),mat_id,ilaw
276 WRITE(iout,1000)
277 IF(is_encrypted )THEN
278 WRITE(iout,'(5X,A,//)')'CONFIDENTIAL DATA'
279 ELSE
280 WRITE(iout,1002) rho0
281 WRITE(iout,1300) e,nu
282 WRITE(iout,1400) sigy,exp,eps0
283 WRITE(iout,1600) ff,gg,hh,nn,ll,mm
284 WRITE(iout,1700) c1,c2,c3,mexp,dc
285 ENDIF
286C.....ERRORS
287C---+----1----+----2----+----3----+----4----+----5----+----6----+----7--
288C
289 RETURN
290 1000 FORMAT(
291 & 5x,' HILL ANISOTROPIC PLASTICITY + MODIFIED MOHR COULOMB '/,
292 & 5x,' --------------------------------------------------- '//)
293 1001 FORMAT(
294 & 5x,a,/,
295 & 5x,'MATERIAL NUMBER . . . . . . . . . . . .=',i10/,
296 & 5x,'MATERIAL LAW. . . . . . . . . . . . . .=',i10/)
297 1002 FORMAT(
298 & 5x,'INITIAL DENSITY . . . . . . . . . . . .=',1pg20.13/)
299 1300 FORMAT(
300 & 5x,'YOUNG MODULUS . . . . . . . . . . . . .=',1pg20.13/,
301 & 5x,'POISSON RATIO . . . . . . . . . . . . .=',1pg20.13//)
302 1400 FORMAT(
303 & 5x,'INITIAL YIELD STRESS SIGY . . . . . . .=',1pg20.13/,
304 & 5x,'HARDENING EXPONENT N . . . . . . . . .=',1pg20.13/,
305 & 5x,'INITIAL PLASTIC STRAIN. . . . . . . . .=',1pg20.13//)
306 1600 FORMAT(
307 & 5x,'HILL MATERIAL PARAMETER F . . . . . . .=',1pg20.13/,
308 & 5x,'HILL MATERIAL PARAMETER G . . . . . . .=',1pg20.13/,
309 & 5x,'HILL MATERIAL PARAMETER H . . . . . . .=',1pg20.13/,
310 & 5x,'HILL MATERIAL PARAMETER N . . . . . . .=',1pg20.13/,
311 & 5x,'HILL MATERIAL PARAMETER L . . . . . . .=',1pg20.13/,
312 & 5x,'HILL MATERIAL PARAMETER M . . . . . . .=',1pg20.13/)
313 1700 FORMAT(
314 & 5x,'FAILURE PARAMETER C1. . . . . . . . . .=',1pg20.13/,
315 & 5x,'FAILURE PARAMETER C2. . . . . . . . . .=',1pg20.13/,
316 & 5x,'FAILURE PARAMETER C3. . . . . . . . . .=',1pg20.13/,
317 & 5x,'DAMAGE EXPOSANT M . . . . . . . . . . .=',1pg20.13/,
318 & 5x,'CRITICAL DAMAGE DC .. . . . . . . . . .=',1pg20.13/)
319 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
subroutine hm_option_is_encrypted(is_encrypted)
subroutine init_mat_keyword(matparam, keyword)
#define max(a, b)
Definition macros.h:21
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