OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_mat13.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_mat13 (lsubmodel, mtag, unitab, ipm, pm, mat_id, titr, matparam)

Function/Subroutine Documentation

◆ hm_read_mat13()

subroutine hm_read_mat13 ( type(submodel_data), dimension(*), intent(in) lsubmodel,
type(mlaw_tag_), intent(inout) mtag,
type (unit_type_), intent(in) unitab,
integer, dimension(npropmi), intent(inout) ipm,
intent(inout) pm,
integer, intent(in) mat_id,
character(len=nchartitle), intent(in) titr,
type(matparam_struct_), intent(inout) matparam )

Definition at line 37 of file hm_read_mat13.F.

39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE unitab_mod
43 USE elbuftag_mod
44 USE message_mod
45 USE submodel_mod
46 USE matparam_def_mod
48C-----------------------------------------------
49C I m p l i c i t T y p e s
50C-----------------------------------------------
51#include "implicit_f.inc"
52C-----------------------------------------------
53C C o m m o n B l o c k s
54C-----------------------------------------------
55#include "units_c.inc"
56#include "param_c.inc"
57C-----------------------------------------------
58C D u m m y A r g u m e n t s
59C-----------------------------------------------
60 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
61 INTEGER, INTENT(IN) :: MAT_ID
62 CHARACTER(LEN=NCHARTITLE) ,INTENT(IN) :: TITR
63 TYPE(SUBMODEL_DATA), DIMENSION(*),INTENT(IN) :: LSUBMODEL
64 TYPE(MLAW_TAG_), INTENT(INOUT) :: MTAG
65 INTEGER, DIMENSION(NPROPMI) ,INTENT(INOUT) :: IPM
66 my_real, DIMENSION(NPROPM) ,INTENT(INOUT) :: pm
67 TYPE(MATPARAM_STRUCT_) ,INTENT(INOUT) :: MATPARAM
68C-----------------------------------------------
69C L o c a l V a r i a b l e s
70C-----------------------------------------------
72 . young, anu, g, c0, c1, e0, e1mn2, en1n2, sdsp,
73 . rho0, rhor
74 LOGICAL :: IS_ENCRYPTED, IS_AVAILABLE
75C-----------------------------------------------
76C S o u r c e L i n e s
77C-----------------------------------------------
78
79 is_encrypted = .false.
80 is_available = .false.
81
82C Check input encryption
83 CALL hm_option_is_encrypted(is_encrypted)
84C Initial and reference density
85 CALL hm_get_floatv('MAT_RHO' ,rho0, is_available, lsubmodel, unitab)
86 CALL hm_get_floatv('Refer_Rho' ,rhor, is_available, lsubmodel, unitab)
87 IF (rhor == zero) THEN
88 rhor = rho0
89 ENDIF
90 pm(1) = rhor
91 pm(89) = rho0
92C Get input values
93 CALL hm_get_floatv('MAT_E', young, is_available, lsubmodel, unitab)
94 CALL hm_get_floatv('MAT_NU', anu, is_available, lsubmodel, unitab)
95
96 IF (young <= zero) THEN
97 CALL ancmsg(msgid=683,
98 . msgtype=msgerror,
99 . anmode=aninfo,
100 . i1=mat_id,
101 . c1=titr)
102 ENDIF
103 IF(anu==half)anu=zep499
104
105 g=young/(two*(one+anu))
106 c1=young/(three*(one-two*anu))
107 e1mn2=young/(one-anu**2)
108 en1n2=anu*e1mn2
109 sdsp =sqrt(young/max(pm(1),em20))
110C
111 pm(20)=young
112 pm(21)=anu
113 pm(22)=g
114 pm(24)=e1mn2
115 pm(27)=sdsp
116 pm(32)=c1
117c-----------------
118 CALL init_mat_keyword(matparam,"TOTAL")
119 IF (anu > 0.49) THEN
120 CALL init_mat_keyword(matparam,"INCOMPRESSIBLE")
121 ELSE
122 CALL init_mat_keyword(matparam,"COMPRESSIBLE")
123 END IF
124
125 ! Properties compatibility
126 CALL init_mat_keyword(matparam,"SOLID_ALL")
127 CALL init_mat_keyword(matparam,"SHELL_ALL")
128 CALL init_mat_keyword(matparam,"BEAM_ALL")
129 CALL init_mat_keyword(matparam,"TRUSS")
130 CALL init_mat_keyword(matparam,"SPRING_ALL")
131 CALL init_mat_keyword(matparam,"SPH")
132
133c-----------------
134C--------------------------------
135C
136 WRITE(iout,800)trim(titr),mat_id,13
137 WRITE(iout,1000)
138 IF(is_encrypted)THEN
139 WRITE(iout,'(5X,A,//)')'CONFIDENTIAL DATA'
140 ELSE
141 WRITE(iout, 850)rho0,rhor
142 WRITE(iout,1300)young,anu,g
143 ENDIF
144C-----------
145 RETURN
146 800 FORMAT(/
147 & 5x,a,/,
148 & 5x,'MATERIAL NUMBER. . . . . . . . . . . . =',i10/,
149 & 5x,'MATERIAL LAW . . . . . . . . . . . . . =',i10/)
150 850 FORMAT(
151 & 5x,'INITIAL DENSITY . . . . . . . . . . . .=',1pg20.13/,
152 & 5x,'REFERENCE DENSITY . . . . . . . . . . .=',1pg20.13/)
153 1000 FORMAT(
154 & 5x,' RIGID LAW ',/,
155 & 5x,' --------- ')
156 1300 FORMAT(
157 & 5x,'YOUNG MODULUS . . . . . . . . . . . . .=',e12.4/,
158 & 5x,'POISSON RATIO . . . . . . . . . . . . .=',e12.4/,
159 & 5x,'SHEAR MODULUS . . . . . . . . . . . . .=',e12.4//)
160C-----------
161 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