OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_prop19.F File Reference
#include "implicit_f.inc"
#include "units_c.inc"
#include "com04_c.inc"
#include "param_c.inc"
#include "scr17_c.inc"
#include "drape_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine hm_read_prop19 (ig, igtyp, istack, geo, igeo, pm, ipm, unitab, idrapeid, lsubmodel)

Function/Subroutine Documentation

◆ hm_read_prop19()

subroutine hm_read_prop19 ( integer, intent(in) ig,
integer, intent(in) igtyp,
integer, intent(in) istack,
dimension(npropg), intent(inout) geo,
integer, dimension(npropgi), intent(inout) igeo,
dimension(npropm,*), intent(in) pm,
integer, dimension(npropmi,*), intent(in) ipm,
type (unit_type_), intent(in) unitab,
integer, dimension(*), intent(in) idrapeid,
type(submodel_data), dimension(nsubmod), intent(in) lsubmodel )

Definition at line 39 of file hm_read_prop19.F.

41C-----------------------------------------------
42C M o d u l e s
43C-----------------------------------------------
44 USE unitab_mod
45 USE message_mod
46 USE submodel_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 "com04_c.inc"
57#include "param_c.inc"
58#include "scr17_c.inc"
59#include "drape_c.inc"
60C-----------------------------------------------
61C D u m m y A r g u m e n t s
62C-----------------------------------------------
63 TYPE (UNIT_TYPE_), INTENT(IN) ::UNITAB
64 INTEGER, INTENT(INOUT) :: IGEO(NPROPGI)
65 INTEGER, INTENT(IN) :: IPM(NPROPMI,*), IDRAPEID(*), IG, IGTYP, ISTACK
66 my_real, INTENT(INOUT) :: geo(npropg)
67 my_real, INTENT(IN) :: pm(npropm,*)
68 TYPE(SUBMODEL_DATA), DIMENSION(NSUBMOD), INTENT(IN) :: LSUBMODEL
69C-----------------------------------------------
70C L o c a l V a r i a b l e s
71C-----------------------------------------------
72 INTEGER :: IMID, J, DRAPE_ID, ID
73 my_real :: thickt, fac_gen, pun
74 CHARACTER(LEN = NCHARTITLE) :: TITR, TITR1, IDTITL
75 LOGICAL :: IS_AVAILABLE, IS_ENCRYPTED, LFOUND
76C-------------------------------------------------
77C B e g i n n i n g o f S u b r o u t i n e
78C-------------------------------------------------
79 pun = 0.1
80 igeo(1) = ig
81 igeo(11) = igtyp
82 geo(12) = igtyp + pun
83
84 is_available = .false.
85 is_encrypted = .false.
86! encryption flag
87 CALL hm_option_is_encrypted(is_encrypted)
88! Line 1
89 CALL hm_get_intv('material', imid, is_available, lsubmodel)
90 CALL hm_get_floatv('thickness1', geo(1), is_available, lsubmodel, unitab)
91 CALL hm_get_floatv('orientangle', geo(2), is_available, lsubmodel, unitab)
92 CALL hm_get_intv('grsh4n_ID', igeo(40), is_available, lsubmodel)
93 CALL hm_get_intv('grsh3n_ID', igeo(41), is_available, lsubmodel)
94 CALL hm_get_intv('integrationpoints', igeo(4), is_available, lsubmodel)
95 CALL hm_get_floatv('orientangle2', geo(212), is_available, lsubmodel, unitab)
96! Line 2
97 CALL hm_get_intv('table', drape_id, is_available, lsubmodel)
98
99 IF (igeo(4) <= 0) igeo(4) = 1 ! default value
100 igeo(44) = igeo(4) ! Used with drape for OUPT
101 IF (geo(212) == zero) THEN
102 CALL hm_get_floatv_dim('orientangle2',fac_gen, is_available, lsubmodel, unitab)
103 geo(212) = ninty * fac_gen ! default value
104 ENDIF
105
106 IF (is_encrypted) THEN
107 WRITE(iout, 1000) ig
108 ELSE
109 WRITE(iout, 2000) ig, imid, geo(1), geo(2), igeo(40), igeo(41), igeo(4),
110 . geo(212), drape_id
111 ENDIF
112
113 geo(2) = geo(2) * pi / hundred80
114 geo(212) = geo(212) * pi / hundred80
115 igeo(48) = 0
116
117! ********************************************************* !
118! Check for layer materials compatibility moved to "lecgeo"
119! ********************************************************* !
120 lfound = .false.
121 DO j=1,nummat-1
122 IF (ipm(1,j) == imid) THEN
123 igeo(101) = j
124 lfound = .true.
125 EXIT
126 ENDIF
127 ENDDO
128 IF (.NOT. lfound) THEN
129 CALL fretitl2(titr, igeo(npropgi-ltitr+1), ltitr)
130 IF (istack == 0) THEN
131 CALL ancmsg(msgid = 31, msgtype = msgerror, anmode = aninfo_blind_2,
132 . i1 = ig, c1 = titr, i2 = imid)
133 ELSE
134 CALL ancmsg(msgid = 1151, msgtype = msgerror, anmode = aninfo_blind_2,
135 . i1 = ig, c1 = titr, i2 = imid)
136 ENDIF
137 igeo(101) = 1
138 ELSE
139! *********************************** !
140! check for right drape id definition
141! *********************************** !
142 IF (ndrape > 0 .OR. drape_id > 0) THEN
143 lfound = .false.
144 DO j=1,ndrape
145 IF (drape_id > 0 .AND. drape_id == idrapeid(j)) THEN
146 igeo(48) = drape_id
147 lfound = .true.
148 EXIT
149 ENDIF
150 ENDDO
151 IF (.NOT. lfound) THEN
152 IF (drape_id > 0)THEN
153 CALL fretitl2(titr, igeo(npropgi-ltitr+1), ltitr)
154 CALL ancmsg(msgid = 1153, msgtype = msgerror, anmode = aninfo,
155 . i1 = ig, c1 = titr, i2 = drape_id)
156 ENDIF
157 ENDIF
158 ENDIF
159 ENDIF
160 IF (igeo(4) > 10) THEN
161 CALL ancmsg(msgid = 788, msgtype = msgerror, anmode = aninfo,
162 . i1 = ig, c1 = idtitl)
163 CALL arret(2)
164 ENDIF
165 RETURN
166 1000 FORMAT(
167 & 5x,' LAYER SHELL PROPERTY SET'/,
168 & 5x,'------------------------------------'/,
169 & 5x,'PROPERTY SET NUMBER . . . . . . . . . .=',i10/,
170 & 5x,'CONFIDENTIAL DATA'//)
171 2000 FORMAT(
172 & 5x,'LAYER PROPERTY SET ',/,
173 & 5x,'PROPERTY SET NUMBER . . . . . . . . . . . . . . =',i10/,
174 & 5x,'MATERIAL NUMBER . . . . . . . . . . . . . . . . =',i10/,
175 & 5x,'LAYER THICKNESS . . . . . . . . . . . . . . . . =',1pg20.13/,
176 & 5x,'INCREMENTAL ANGLE (DIR 1,PROJ(DIR 1 / SHELL). . =',1pg20.13/,
177 & 5x,'SHELL 4-nodes GROUP IDENTIFIER. . . . . . . . . =',i10/,
178 & 5x,'SHELL 3-nodes GROUP IDENTIFIER. . . . . . . . . =',i10/,
179 & 5x,'NUMBER OF INTEGRATION POINTS THROUGH LAYER. . . =',i10/,
180 & 5x,'ORTHOTROPY ANGLE BETWEEN (DIR 1,DIR 2). . . . . =',1pg20.13/,
181 & 5x,'DRAPE IDENTIFIER . . . . . . . . . . . . . . . =',i10/)
#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_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_is_encrypted(is_encrypted)
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
subroutine fretitl2(titr, iasc, l)
Definition freform.F:804
subroutine arret(nn)
Definition arret.F:87