42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
71 USE reader_old_mod , ONLY : line
72 USE user_id_mod , ONLY : id_limit
73
74
75
76
77
78
79
80
81#include "implicit_f.inc"
82
83
84
85#include "analyse_name.inc"
86
87
88
89#include "scr17_c.inc"
90#include "com04_c.inc"
91#include "units_c.inc"
92#include "scr03_c.inc"
93#include "param_c.inc"
94#include "titr_c.inc"
95#include "remesh_c.inc"
96
97
98
99
100 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
101 INTEGER,INTENT(IN)::ITAB(*)
102 INTEGER,INTENT(IN)::ITABM1(*)
103 INTEGER,INTENT(IN)::IPART(LIPART1,*)
104 INTEGER,INTENT(IN)::IGEO(NPROPGI,*)
105 INTEGER,INTENT(IN)::IPM(NPROPMI,*)
106 TYPE(SUBMODEL_DATA),INTENT(IN)::LSUBMODEL(NSUBMOD)
107
108 INTEGER,INTENT(OUT)::IXC(NIXC,*)
109 INTEGER,INTENT(OUT)::IPARTC(*)
110 INTEGER,INTENT(OUT)::ITAG(*)
112 . INTENT(OUT)::angle(*)
114 . INTENT(OUT)::thk(*)
115
116
117
118 INTEGER I, J, I1, I2, ID,IDS,IPID,MT,N,MID,PID,UID,NDEGEN,JC,STAT,
119 . IFLAGUNIT,FLAG_FMT,FLAG_FMT_TMP,IFIX_TMP,ISHXFEM,IOUTN,IERROR,INDEX_PART
120 CHARACTER MESS*40, MESS2*40
121 CHARACTER(LEN=NCHARTITLE) :: TITR
123 . bid,fac_l
124 INTEGER, DIMENSION(:), ALLOCATABLE :: SUB_SHELL,UID_SHELL
125 real*8, DIMENSION(:), ALLOCATABLE :: hm_thk,hm_angle
126
127
128
129 INTEGER NINTRN
130 INTEGER USR2SYS
131 DATA mess/'3D SHELL ELEMENTS DEFINITION '/
132 DATA mess2/'3D SHELL ELEMENTS SELECTION FOR TH PLOT '/
133
134
135
136
137
138 ALLOCATE (sub_shell(numelc0),stat=stat)
139 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
140 . msgtype=msgerror,
141 . c1='SUB_SHELL')
142 ALLOCATE (uid_shell(numelc0),stat=stat)
143 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
144 . msgtype=msgerror,
145 . c1='UID_SHELL')
146 ALLOCATE (hm_thk(numelc0),stat=stat)
147 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
148 . msgtype=msgerror,
149 . c1='HM_THK')
150 ALLOCATE (hm_angle(numelc0),stat=stat)
151 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
152 . msgtype=msgerror,
153 . c1='HM_ANGLE')
154 sub_shell(1:numelc0) = 0
155 uid_shell(1:numelc0) = 0
156 hm_thk(1:numelc0) = zero
157 hm_angle(1:numelc0) = zero
158 ndegen = 0
159 index_part = 1
160 uid = -1
161
162
163
164 CALL cpp_shell_read(ixc,nixc,ipartc,hm_angle,hm_thk,sub_shell,uid_shell)
165
166
167
168 DO i=1,numelc0
169
170
171
172 angle(i) = hm_angle(i) * pi / hundred80
173 thk(i) = hm_thk(i)
174
175
176
177 IF(sub_shell(i) /= 0)THEN
178 IF(uid_shell(i) == 0 .AND. lsubmodel(sub_shell(i))%UID /= 0)
179 . uid_shell(i) = lsubmodel(sub_shell(i))%UID
180 ENDIF
181
182
183
184 fac_l = one
185 IF(uid_shell(i) /= uid )THEN
186 uid = uid_shell(i)
187 iflagunit = 0
188 DO j=1,unitab%NUNITS
189 IF (unitab%UNIT_ID(j) == uid) THEN
190 fac_l = unitab%FAC_L(j)
191 iflagunit = 1
192 ENDIF
193 ENDDO
194 IF (uid/=0.AND.iflagunit==0) THEN
195 CALL ancmsg(msgid=643,anmode=aninfo,msgtype=msgerror,
196 . i1=uid,c1='/SHELL')
197 ENDIF
198 ENDIF
199 thk(i) = thk(i) * fac_l
200
201
202
203 IF( ipart(4,index_part) /= ipartc(i) )THEN
204 DO j=1,npart
205 IF(ipart(4,j)== ipartc(i) ) index_part = j
206 ENDDO
207 ENDIF
208 IF(ipart(4,index_part) /= ipartc(i)) THEN
210 . msgtype=msgerror,
211 . anmode=aninfo_blind_1,
212 . c1="SHELL",
213 . i1=ipartc(i),
214 . i2=ipartc(i),
215 . prmod=msg_cumu)
216 ENDIF
217 ipartc(i) = index_part
218
219 mt=ipart(1,index_part)
220 ipid=ipart(2,index_part)
221 ixc(1,i)=mt
222 ixc(6,i)=ipid
223 IF (ixc(nixc,i)>id_limit%GLOBAL)THEN
224 CALL ancmsg(msgid=509,anmode=aninfo,msgtype=msgerror,
225 . i1=ixc(nixc,i),c1=line,c2='/SHELL')
226 ELSEIF (nadmesh/=0.AND.ixc(nixc,i)>id_limit%ADMESH)THEN
227 CALL ancmsg(msgid=1069,anmode=aninfo,msgtype=msgerror,
228 . i1=ixc(nixc,i),c1=line,c2='/SHELL')
229 ENDIF
230 IF( ( ixc(4,i) == ixc(5,i)) .OR.
231 . ( ixc(5,i) == 0 )) THEN
232 ndegen = ndegen + 1
234 . msgtype=msgwarning,
235 . i1=ixc(nixc,i),
236 . anmode=aninfo_blind_2,
237 . prmod=msg_cumu)
238 ENDIF
239 IF(thk(i)>0) THEN
240 CALL apartset(index_part, check_thick_shell)
241 ENDIF
242
243 DO j=2,5
244 ixc(j,i)=
usr2sys(ixc(j,i),itabm1,mess,
id)
245 CALL anodset(ixc(j,i), check_shell)
246 ENDDO
247
248 ishxfem = igeo(19,ipid)
249
250 IF(ishxfem > 0) THEN
251 DO j=2,5
252 itag(ixc(j,i)) = 1
253 ENDDO
254 ENDIF
255 ENDDO
256
257
258 IF(ALLOCATED(sub_shell)) DEALLOCATE(sub_shell)
259 IF(ALLOCATED(uid_shell)) DEALLOCATE(uid_shell)
260 IF(ALLOCATED(hm_thk)) DEALLOCATE(hm_thk)
261 IF(ALLOCATED(hm_angle)) DEALLOCATE(hm_angle)
262
263 i1=1
264 i2=min0(50,numelc0)
265
266 IF(ipri>=5)THEN
267 90 WRITE (iout,'(//A/A//A,A/)')titre(110),titre(111),titre(102),titre(105)
268 DO i=i1,i2
269 mid = ipm(1,ixc(1,i))
270 pid = igeo(1,ixc(6,i))
271 WRITE (iout,fmt='(8(I10,1X),1PG20.13,1X,1PG20.13)') ixc(nixc,i),i,mid,pid,
272 . (itab(ixc(j,i)),j=2,5),angle(i),thk(i)
273 ENDDO
274 IF(i2==numelc0)GOTO 200
275 i1=i1+50
276 i2=min0(i2+50,numelc0)
277 GOTO 90
278 ENDIF
279
280 200 CONTINUE
281
283 . msgtype=msgerror,
284 . anmode=aninfo_blind_1,
285 . prmod=msg_print)
286
287
288
289 ids = 79
290 i = 0
291 j = 0
292 CALL vdouble(ixc(nixc,1),nixc,numelc0,mess,0,bid)
293 ids = 17
294
295 RETURN
296
void anodset(int *id, int *type)
void apartset(int *id, int *type)
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)
integer function usr2sys(iu, itabm1, mess, id)
subroutine vdouble(list, ilist, nlist, mess, ir, rlist)