OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
lcgeo19.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 lcgeo19 (geo, igeo, pm, ipm, unitab, iunit, istack, idrapeid, lsubmodel)

Function/Subroutine Documentation

◆ lcgeo19()

subroutine lcgeo19 ( geo,
integer, dimension(npropgi) igeo,
pm,
integer, dimension(npropmi,*) ipm,
type (unit_type_), intent(in) unitab,
integer iunit,
integer istack,
integer, dimension(*) idrapeid,
type(submodel_data), dimension(nsubmod), intent(in) lsubmodel )

Definition at line 37 of file lcgeo19.F.

39 USE unitab_mod
40 USE message_mod
41 USE submodel_mod
43C-----------------------------------------------
44C I m p l i c i t T y p e s
45C-----------------------------------------------
46#include "implicit_f.inc"
47C-----------------------------------------------
48C C o m m o n B l o c k s
49C-----------------------------------------------
50#include "units_c.inc"
51#include "com04_c.inc"
52#include "param_c.inc"
53#include "scr17_c.inc"
54#include "drape_c.inc"
55C-----------------------------------------------
56C D u m m y A r g u m e n t s
57C-----------------------------------------------
58 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
59 INTEGER IGEO(NPROPGI),IPM(NPROPMI,*),ISTACK,IDRAPEID(*),IUNIT
61 . geo(npropg), pm(npropm,*)
62 TYPE(SUBMODEL_DATA), DIMENSION(NSUBMOD), INTENT(IN) :: LSUBMODEL
63C-----------------------------------------------
64C L o c a l V a r i a b l e s
65C-----------------------------------------------
66 CHARACTER ISS*3
67 INTEGER IPMAT,IMID,MLAWLY1, IG,J,JREC
69 . thickt
70 INTEGER ISH3N,DRAPE_ID
71 INTEGER ID
72 CHARACTER(LEN=NCHARTITLE)::TITR,TITR1
73 LOGICAL :: IS_AVAILABLE, IS_ENCRYPTED
74 LOGICAL :: FOUND
75
76
77 is_encrypted = .false.
78 is_available = .false.
79
80 CALL hm_option_is_encrypted(is_encrypted)
81
82 ish3n = igeo(18)
83 CALL hm_get_intv('mat_ID', imid, is_available, lsubmodel)
84 CALL hm_get_floatv('t', geo(1), is_available, lsubmodel, unitab)
85 CALL hm_get_floatv('delta_phi', geo(2), is_available, lsubmodel, unitab)
86 CALL hm_get_intv('grsh4n_ID', igeo(40), is_available, lsubmodel)
87 CALL hm_get_intv('grsh3n_ID', igeo(41), is_available, lsubmodel)
88 CALL hm_get_intv('Npt_ply', igeo(4), is_available, lsubmodel)
89 CALL hm_get_floatv('alpha_i', geo(212), is_available, lsubmodel, unitab)
90
91 CALL hm_get_intv('drape_ID', drape_id, is_available, lsubmodel)
92 CALL hm_get_intv('def_orth', igeo(49), is_available, lsubmodel)
93
94 ig = igeo(1)
95 IF (igeo(4) <= 0) igeo(4) = 1
96 IF (geo(212) == zero) geo(212) = ninty
97 IF (is_encrypted) THEN
98 WRITE(iout,1000)ig
99 1000 FORMAT(
100 & 5x,' LAYER SHELL PROPERTY SET'/,
101 & 5x,'------------------------------------'/,
102 & 5x,'PROPERTY SET NUMBER . . . . . . . . . .=',i10/,
103 & 5x,'CONFIDENTIAL DATA'//)
104 ELSE
105 WRITE(iout,2000)ig,imid,geo(1),geo(2),igeo(40),igeo(41),igeo(4),
106 . geo(212),drape_id,igeo(49)
107 ENDIF
108 geo(2)=geo(2)*pi/hundred80
109 geo(212)=geo(212)*pi/hundred80
110 igeo(48) = 0 ! keeped for DRAPE IDENTIFICATION NUMBER
111C ------------------------------------
112C
113C check for layer materials compatibility moved to "lecgeo"
114C
115 found = .false.
116 IF(imid > 0) THEN
117 DO j=1,nummat
118 IF (ipm(1,j) == imid) THEN
119 igeo(101) = j
120 found = .true.
121 EXIT
122 ENDIF
123 ENDDO
124 ENDIF
125 IF (.NOT. found) THEN
126 CALL fretitl2(titr,igeo(npropgi-ltitr+1),ltitr)
127 IF(istack == 0) THEN
128 CALL ancmsg(msgid=31,
129 . msgtype=msgerror,
130 . anmode=aninfo_blind_2,
131 . i1=ig,
132 . c1=titr,
133 . i2=imid)
134 ELSE
135 CALL ancmsg(msgid=1151,
136 . msgtype=msgerror,
137 . anmode=aninfo_blind_2,
138 . i1=ig,
139 . c1=titr,
140 . i2=imid)
141
142 ENDIF
143 igeo(101) = 1
144 ENDIF
145C
146C check for wright drape id definition
147C
148 IF (ndrape > 0 .OR. drape_id > 0) THEN
149 found = .false.
150 DO j=1,ndrape
151 IF (drape_id > 0 .AND. drape_id == idrapeid(j)) THEN
152 igeo(48) = drape_id
153 found = .true.
154 EXIT
155 ENDIF
156 ENDDO
157 IF (.NOT. found) THEN
158 IF (drape_id > 0)THEN
159 CALL fretitl2(titr,igeo(npropgi-ltitr+1),ltitr)
160 CALL ancmsg(msgid=1153,
161 . msgtype=msgerror,
162 . anmode=aninfo,
163 . i1=ig,
164 . c1=titr,
165 . i2=drape_id)
166 ENDIF
167 ENDIF
168 ENDIF ! IF (NDRAPE > 0)
169c-----------
170 RETURN
171c-----------
172 2000 FORMAT(/,
173 & 5x,'PLY PROPERTY SET ',/,
174 & 5x,'PROPERTY SET NUMBER . . . . . . . . . . . . . .=',i10/,
175 & 5x,'MATERIAL NUMBER . . . . . . . . . . . . . . . .=',i10/,
176 & 5x,'LAYER THICKNESS . . . . . . . . . . . . . . . .=',1pg20.13/,
177 & 5x,'INCREMENTAL ANGLE (DIR 1,PROJ(DIR 1 / SHELL). . .=',1pg20.13/,
178 & 5x,'SHELL 4-nodes GROUP IDENTIFIER. . . . . . . . .=',i10/,
179 & 5x,'SHELL 3-nodes GROUP IDENTIFIER. . . . . . . . .=',i10/,
180 & 5x,'NUMBER OF INTEGRATION POINTS THROUGH LAYER. . .=',i10/,
181 & 5x,'ORTHOTROPY ANGLE BETWEEN (DIR 1,DIR 2). . . . . =',1pg20.13/,
182 & 5x,'DRAPE IDENTIFIER . . . . . . . . . . . . . . .=',i10/,
183 & 5x,'DEF_ORTH FLAG . . . . . . . . . . . . . . . . . =',i10/)
#define my_real
Definition cppsort.cpp:32
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)
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