OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_mat18.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_mat18 (nuparam, nuvar, nfunc, mat_id, titr, unitab, lsubmodel, mtag, pm, ipm, jthe, matparam)

Function/Subroutine Documentation

◆ hm_read_mat18()

subroutine hm_read_mat18 ( integer, intent(inout) nuparam,
integer, intent(inout) nuvar,
integer, intent(inout) nfunc,
integer, intent(in) mat_id,
character(len=nchartitle), intent(in) titr,
type(unit_type_), intent(in) unitab,
type(submodel_data), dimension(nsubmod), intent(in) lsubmodel,
type(mlaw_tag_), intent(inout) mtag,
dimension(npropm), intent(inout) pm,
integer, dimension(npropmi), intent(inout) ipm,
integer, intent(inout) jthe,
type(matparam_struct_), intent(inout) matparam )

Definition at line 37 of file hm_read_mat18.F.

41C-----------------------------------------------
42C M o d u l e s
43C-----------------------------------------------
44 USE elbuftag_mod
45 USE message_mod
46 USE submodel_mod
47 USE matparam_def_mod
48 USE unitab_mod
50C-----------------------------------------------
51C ROUTINE DESCRIPTION :
52C ===================
53C READ MAT LAW18 WITH HM READER
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 "units_c.inc"
62#include "param_c.inc"
63C-----------------------------------------------
64C D u m m y A r g u m e n t s
65C-----------------------------------------------
66 CHARACTER(LEN=NCHARTITLE) ,INTENT(IN) :: TITR
67 TYPE(SUBMODEL_DATA), DIMENSION(NSUBMOD),INTENT(IN) :: LSUBMODEL
68 TYPE(UNIT_TYPE_), INTENT(in) :: UNITAB
69 INTEGER, INTENT(IN) :: MAT_ID
70 INTEGER, INTENT(INOUT) :: IPM(NPROPMI)
71 my_real, INTENT(INOUT) :: pm(npropm)
72 INTEGER, INTENT(INOUT) :: NUPARAM,NUVAR,NFUNC,JTHE
73 TYPE(MLAW_TAG_) ,INTENT(INOUT) :: MTAG
74 TYPE(MATPARAM_STRUCT_) ,INTENT(INOUT) :: MATPARAM
75C-----------------------------------------------
76C L o c a l V a r i a b l e s
77C-----------------------------------------------
78 LOGICAL :: IS_AVAILABLE,IS_ENCRYPTED
79 INTEGER :: ILAW,ITF,ISPH,IAS
80 my_real :: rhor,rho0,t0,sph,as,bs,e0,timescal,tscal,escal,kscal
81C=======================================================================
82 is_encrypted = .false.
83 is_available = .false.
84 ilaw = 18
85 jthe = 1
86c--------------------------------------------------
87c Check crypting option
88c--------------------------------------------------
89c
90 CALL hm_option_is_encrypted(is_encrypted)
91c
92c--------------------------------------------------
93c Read input Parameters
94c--------------------------------------------------
95 CALL hm_get_floatv('MAT_RHO' ,rho0 ,is_available, lsubmodel, unitab)
96 CALL hm_get_floatv('Refer_Rho' ,rhor ,is_available, lsubmodel, unitab)
97c
98 CALL hm_get_floatv('mat_spheat',SPH ,IS_AVAILABLE, LSUBMODEL, UNITAB)
99 CALL HM_GET_FLOATV('mat_a' ,AS ,IS_AVAILABLE, LSUBMODEL, UNITAB)
100 CALL HM_GET_FLOATV('mat_b' ,BS ,IS_AVAILABLE, LSUBMODEL, UNITAB)
101c
102 CALL HM_GET_INTV ('xt_fun' ,ITF ,IS_AVAILABLE, LSUBMODEL)
103 CALL HM_GET_FLOATV('mat_t0' ,T0 ,IS_AVAILABLE, LSUBMODEL, UNITAB)
104 CALL HM_GET_FLOATV('scale' ,TIMESCAL ,IS_AVAILABLE, LSUBMODEL, UNITAB)
105c
106 CALL HM_GET_INTV ('fun_a1' ,ISPH ,IS_AVAILABLE, LSUBMODEL)
107 CALL HM_GET_INTV ('fun_a2' ,IAS ,IS_AVAILABLE, LSUBMODEL)
108 CALL HM_GET_FLOATV('fscale11' ,TSCAL ,IS_AVAILABLE, LSUBMODEL, UNITAB)
109 CALL HM_GET_FLOATV('fscale22' ,ESCAL ,IS_AVAILABLE, LSUBMODEL, UNITAB)
110 CALL HM_GET_FLOATV('fscale33' ,KSCAL ,IS_AVAILABLE, LSUBMODEL, UNITAB)
111c--------------------------------------------------
112c DEFAULT VALUES
113c--------------------------------------------------
114c
115 IF (TIMESCAL == ZERO) THEN
116 TIMESCAL = ONE
117 ENDIF
118 IF (TSCAL == ZERO) THEN
119 TSCAL = ONE
120 ENDIF
121 IF (ESCAL == ZERO) THEN
122 ESCAL = ONE
123 ENDIF
124 IF (KSCAL == ZERO) THEN
125 KSCAL = ONE
126 ENDIF
127 TIMESCAL = ONE / TIMESCAL
128 ESCAL = ONE / ESCAL
129 IF (T0 == ZERO) T0 = THREE100
130 E0 = T0*SPH
131c
132c------------------
133 NFUNC = 0
134 NUPARAM = 0
135 NUVAR = 0
136c------------------
137c
138 IPM(10)= 3 ! Nfunc
139 IPM(11)= ITF
140 IPM(12)= ISPH
141 IPM(13)= IAS
142c
143 PM(23) = E0
144 PM(41) = TIMESCAL
145 PM(42) = TSCAL
146 PM(43) = ESCAL
147 PM(44) = KSCAL
148 PM(71) = JTHE+EM01
149 PM(72) = ZERO
150 PM(69) = SPH
151 PM(75) = AS
152 PM(76) = BS
153 PM(79) = T0
154 PM(80) = INFINITY
155c---
156 PM(1) = RHOR
157 PM(89) = RHO0
158c--------------------------
159c
160c---- Definition des variables internes (stockage elementaire)
161c
162 MTAG%G_TEMP = 1
163 MTAG%G_DELTAX = 1
164 MTAG%L_TEMP = 1
165 MTAG%L_DELTAX = 1
166
167 ! MATPARM keywords
168
169 ! EOS/Thermo keyword for pressure treatment in elements
170 CALL INIT_MAT_KEYWORD(MATPARAM,"HYDRO_EOS")
171
172 CALL INIT_MAT_KEYWORD(MATPARAM,"INCOMPRESSIBLE")
173
174 ! Properties compatibility
175 CALL INIT_MAT_KEYWORD(MATPARAM,"SOLID_ORTHOTROPIC")
176c--------------------------------------------------
177c Starter output
178c--------------------------------------------------
179 WRITE(IOUT,1000) TRIM(TITR),MAT_ID,ILAW
180 WRITE(IOUT,1100)
181 IF (IS_ENCRYPTED) THEN
182 WRITE(IOUT,'(5x,a,//)')'confidential data'
183 ELSE
184 WRITE(IOUT,1200) RHO0,RHOR
185 IF (ITF > 0) WRITE(IOUT,1300) ITF
186 WRITE(IOUT,1400) T0,SPH,AS,BS,ISPH,IAS
187 ENDIF
188c-----------------------------------------------------------------------
189 1000 FORMAT(/
190 & 5X,A,/,
191 & 5X,'material number. . . . . . . . . . . . . . .=',I10/,
192 & 5X,'material law . . . . . . . . . . . . . . . .=',I10/)
193 1100 FORMAT(
194 & 5X,' thermal material ',/,
195 & 5X,'-------------------- ',/)
196 1200 FORMAT(
197 & 5X,'initial density . . . . . . . . . . . . . .=',1PG20.13/,
198 & 5X,'reference density. . . . . . . . . . . . . .=',1PG20.13/)
199 1300 FORMAT(
200 & 5X,'temperature load curve . . . . . . . . . . .=',I10/)
201 1400 FORMAT(
202 & 5X,'t0 . . . . . . . . . . . . . . . . . . . . .=',1PG20.13/,
203 & 5X,'specific heat. . . . . . . . . . . . . . . .=',1PG20.13/,
204 & 5X,'as . . . . . . . . . . . . . . . . . . . . .=',1PG20.13/,
205 & 5X,'bs . . . . . . . . . . . . . . . . . . . . .=',1PG20.13/,
206 & 5X,'conductivity curve number. . . . . . . . . .=',I10/,
207 & 5X,'temperature versus energy curve number . . .=',I10/)
208c--------------------------------------------------
209 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)
integer, parameter nchartitle