42 . ELBUF_STR ,JFT ,JLT ,GEO ,IGEO ,
43 . MAT ,PID ,THKLY ,MATLY ,POSLY ,
44 . IGTYP ,IXFEM ,IXLAY ,NLAY ,NPT ,
45 . ISUBSTACK ,STACK ,DRAPE ,NFT ,THK ,
46 . NEL ,RATIO_THKLY, INDX_DRAPE,SEDRAPE , NUMEL_DRAPE)
56#include "implicit_f.inc"
70 INTEGER JFT,,NPT,NEL,IGTYP,ISUBSTACK,NLAY,IXLAY,IXFEM,NFT
71 INTEGER ,
INTENT(IN) :: SEDRAPE,NUMEL_DRAPE
72 INTEGER MAT(*), PID(*), (*), IGEO(NPROPGI,*)
73 my_real GEO(,*),POSLY(MVSIZ,*),THKLY(*),RATIO_THKLY(NEL,*),
75 INTEGER,
DIMENSION(SEDRAPE) :: INDX_DRAPE
76 TYPE(elbuf_struct_),
TARGET :: ELBUF_STR
77 TYPE (STACK_PLY) :: STACK
78 TYPE (DRAPE_),
DIMENSION(NUMEL_DRAPE),
TARGET :: DRAPE
82 INTEGER I, J, N, IADR, IPTHK, IPMAT, IPPOS ,IPPID, IPID,
83 . ipang,mat_ly(mvsiz),it,itl,ilay,nptt,max_nptt,ipt,jmly,iint,
84 . ipid_ly,ipt_all,mat_lay,idx,ie,nslice,ip,idrape,ipos
86 . zshift,thk_nptt,thickt_drape,
87 . thkl,pos_nptt,pos_0,thickt,thinning,thk_ly(mvsiz),pos_ly(mvsiz)
88 my_real ,
DIMENSION(:,:),
ALLOCATABLE :: thk_it
90 TYPE (DRAPE_PLY_),
POINTER :: DRAPE_PLY
91 TYPE(L_BUFEL_) ,
POINTER :: LBUF
94 . a_gauss(9,9),w_gauss(9,9)
100 2 -.577350269189626,0.577350269189626,0. ,
103 3 -.774596669241483,0. ,0.774596669241483,
106 4 -.861136311594053,-.339981043584856,0.339981043584856,
107 4 0.861136311594053,0. ,0. ,
109 5 -.906179845938664,-.538469310105683,0. ,
110 5 0.538469310105683,0.906179845938664,0. ,
112 6 -.932469514203152,-.661209386466265,-.238619186083197,
113 6 0.238619186083197,0.661209386466265,0.932469514203152,
115 7 -.949107912342759,-.741531185599394,-.405845151377397,
116 7 0. ,0.405845151377397,0.741531185599394,
117 7 0.949107912342759,0. ,0. ,
118 8 -.960289856497536,-.796666477413627,-.525532409916329,
119 8 -.183434642495650,0.183434642495650,0.525532409916329,
120 8 0.796666477413627,0.960289856497536,0. ,
121 9 -.968160239507626,-.836031107326636,-.613
122 9 -.324253423403809,0
123 9 0.613371432700590,0.836031107326636,0.968160239507626/
131 3 0.555555555555556,0.888888888888889,0.555555555555556,
134 4 0.347854845137454,0.652145154862546,0.652145154862546,
135 4 0.347854845137454,0.
137 5 0.236926885056189,0.478628670499366,0.568888888888889,
138 5 0.478628670499366,0.236926885056189,0. ,
140 6 0.171324492379170,0.360761573048139,0.467913934572691,
141 6 0.467913934572691,0.360761573048139,0.171324492379170,
143 7 0.129484966168870,0.279705391489277,0.38183005
144 7 0.417959183673469,0.38
145 7 0.129484966168870,0. ,0. ,
146 8 0.101228536290376,0.222381034453374,0.313706645877887,
147 8 0.362683783378362,0.362683783378362,0.313706645877887,
148 8 0.222381034453374,0.101228536290376,0. ,
149 9 0.081274388361574,0.180648160694857,0.260610696402935,
150 9 0.312347077040003,0.330239355001260,0.312347077040003,
151 9 0.260610696402935,0.180648160694857,0.081274388361574/
156 idrape = elbuf_str%IDRAPE
158 IF(igtyp == 51 .OR. igtyp == 52)
THEN
160 max_nptt = max_nptt + elbuf_str%BUFLY(ilay)%NPTT
163 IF(max_nptt > 0 )
THEN
164 ALLOCATE(thk_it(max_nptt,mvsiz))
166 ALLOCATE(thk_it(0,0))
170 IF (ixfem == 1 .and. ixlay > 0)
THEN
177 DO ilay=1,elbuf_str%NLAY
184 matly(j) = igeo(ipmat+ixlay,pid(1))
193 ipmat = ippid + elbuf_str%NLAY
194 ipthk = ipang + elbuf_str%NLAY
195 ippos = ipthk + elbuf_str%NLAY
197 nptt = elbuf_str%BUFLY(ixlay)%NPTT
198 iint = igeo(47,pid(1))
202 thk_ly(i) = stack%GEO(ipthk + ixlay,isubstack)
203 pos_ly(i) = stack%GEO(ippos + ixlay,isubstack)
204 mat_ly(i) = stack%IGEO(ipmat + ixlay,isubstack)
205 ratio_thkly(i,ixlay) = thk_ly(i)
206 jmly = (ixlay - 1)*jlt + i
209 thk_it(it,i) = one/nptt
210 thkly(j) = thk_it(it,i)
211 matly(jmly) = mat_ly(i)
215 ELSEIF(iint == 2)
THEN
217 thk_ly(i) = stack%GEO(ipthk + ixlay,isubstack)
218 pos_ly(i) = stack%GEO(ippos + ixlay,isubstack)
219 mat_ly(i) = stack%IGEO(ipmat + ixlay,isubstack)
220 ratio_thkly(i,ixlay) = thk_ly(i)
221 jmly = (ixlay - 1)*jlt + i
224 thk_it(it,i) = half*w_gauss(it,nptt)
225 thkly(j) = thk_it(it,i)
226 matly(jmly) = mat_ly(i)
242 zshift = geo(199, pid(1))
248 posly(i,n) = z0(n,npt)+zshift
257 pos_0 = geo(ippos+n,pid(1))
258 thk_nptt = geo(ipthk+n,pid(1))
271 thk_nptt = geo(ipthk+n,pid(1))
272 pos_0 = geo(ippos+n,pid(1))
273 mat_lay = igeo(ipmat+n,pid(1))
289 ipos = igeo(99,pid(1))
290 thickt = stack%GEO(1,isubstack)
291 zshift = geo(199, pid(1))
292 IF (ipos == 2 ) zshift = zshift /
max(thickt,em20)
298 matly(j) = stack%IGEO(ipmat + n ,isubstack)
299 thkly(j) = stack%GEO (ipthk + n ,isubstack)
300 posly(i,n) = stack%GEO (ippos + n ,isubstack)
304 thickt = stack%GEO(1,isubstack)
309 matly(j) = stack%IGEO(ipmat + n ,isubstack)
310 ie = indx_drape(nft + i)
312 thkly(j) = stack%GEO (ipthk + n
313 posly(i,n) = stack%GEO (ippos + n ,isubstack)
315 thickt_drape = drape(ie)%THICK
316 ip = drape(ie)%INDX_PLY(n)
318 thkly(j) = stack%GEO (ipthk + n ,isubstack)*thickt
319 ratio_thkly(i,n) = thkly(j)/thickt_drape
321 posly(i,n) = zshift + half*ratio_thkly(i,n)
323 posly(i,n) = posly(i,n-1)
324 . + half*(ratio_thkly(i,n)+ratio_thkly(i,n-1))
326 pos_ly(i) = posly(i,n)
328 drape_ply => drape(ie)%DRAPE_PLY(ip)
329 thinning = drape_ply%RDRAPE(1,1)
330 thkly(j) = stack%GEO(ipthk + n,isubstack)*thickt
331 thkly(j) = thkly(j)*thinning
332 thkly(j) = thkly(j)/thickt_drape
333 ratio_thkly(i,n) = thkly(j)
335 posly(i,n) = zshift + half*ratio_thkly(i,n)
337 posly(i,n) = posly(i,n-1)
338 . + half*(ratio_thkly(i,n)+ratio_thkly(i,n-1))
357 ipos = igeo(99,pid(1))
358 thickt = stack%GEO(1,isubstack)
359 zshift = geo(199, pid(1))
360 IF (ipos == 2 ) zshift = zshift /
max(thickt,em20)
364 nptt = elbuf_str%BUFLY(ilay)%NPTT
365 iint = igeo(47,pid(1))
368 mat_ly(i) = stack%IGEO(ipmat + ilay,isubstack)
369 thickt = stack%GEO(1,isubstack)
370 thk_ly(i) = stack%GEO(ipthk + ilay,isubstack)
371 pos_ly(i) = stack%GEO(ippos + ilay,isubstack)
373 jmly = (ilay-1)*jlt + i
377 thk_it(ipt,i) = thk_ly(i)/nptt
379 posly(i,ipt) = zshift + half*thk_it(ipt,i)
381 posly(i,ipt) = posly(i,ipt - 1)
382 . + half*(thk_it(ipt,i) + thk_it(ipt-1,i))
384 thkly(j) = thk_it(ipt,i)
386 matly(jmly) = mat_ly(i)
388 ipt_all = ipt_all + nptt
389 ELSEIF (iint == 2)
THEN
391 mat_ly(i) = stack%IGEO(ipmat + ilay,isubstack)
392 thk_ly(i) = stack%GEO(ipthk + ilay,isubstack)
393 pos_ly(i) = stack%GEO(ippos + ilay,isubstack)
394 ratio_thkly(i,ilay) = thk_ly(i)
395 jmly = (ilay-1)*jlt + i
399 thk_it(ipt,i) = half*thk_ly(i)*w_gauss(it,nptt)
401 posly(i,ipt) = zshift + half*thk_it(ipt,i)
403 posly(i,ipt) = posly(i,ipt - 1)
404 . + half*(thk_it(ipt,i) + thk_it(ipt-1,i))
406 thkly(j) = thk_it(ipt,i)
408 matly(jmly) = mat_ly(i)
410 ipt_all = ipt_all + nptt
416 nptt = elbuf_str%BUFLY(ilay)%NPTT
418 iint = igeo(47,pid(1))
421 mat_ly(i) = stack%IGEO(ipmat + ilay,isubstack)
422 thickt = stack%GEO(1,isubstack)
423 thk_ly(i) = stack%GEO(ipthk + ilay,isubstack)*thickt
424 pos_ly(i) = stack%GEO(ippos + ilay,isubstack)*thickt
425 ratio_thkly(i,ilay) = thk_ly(i)/thickt
426 jmly = (ilay-1)*jlt + i
427 ie = indx_drape(nft + i)
432 thk_it(ipt,i) = thk_ly(i)/thickt/nptt
434 posly(i,ipt) = zshift + half*thk_it(ipt,i)
436 posly(i,ipt) = posly(i,ipt - 1)
437 . + half*(thk_it(ipt,i) + thk_it(ipt-1,i))
439 thkly(j) = thk_it(ipt,i)
442 ip = drape(ie)%INDX_PLY(ilay)
443 thickt_drape = drape(ie)%THICK
445 drape_ply => drape(ie)%DRAPE_PLY(ip)
446 nslice = drape_ply%NSLICE
450 thinning = drape_ply%RDRAPE(it,1)
451 thk_it(ipt,i) = thinning*thk_ly(i)/nptt
452 thk_it(ipt,i) = thk_it(ipt,i)/thickt_drape
454 posly(i,ipt) = zshift + half*thk_it(ipt,i)
456 posly(i,ipt) = posly(i,ipt - 1)
457 . + half*(thk_it(ipt,i) + thk_it(ipt-1,i))
459 thkly(j) = thk_it(ipt,i)
465 thk_it(ipt,i) = thk_ly(i)/thickt_drape/nptt
469 posly(i,ipt) = posly(i,ipt - 1)
470 . + half*(thk_it(ipt,i) + thk_it(ipt-1,i))
472 thkly(j) = thk_it(ipt,i)
476 matly(jmly) = mat_ly(i)
478 ipt_all = ipt_all + nptt
479 ELSEIF (iint == 2)
THEN
482 thickt = stack%GEO(1,isubstack)
483 thk_ly(i) = stack%GEO(ipthk + ilay,isubstack)*thickt
484 pos_ly(i) = stack%GEO(ippos + ilay,isubstack)*thickt
486 jmly = (ilay-1)*jlt + i
487 ie = indx_drape(nft + i)
492 thk_it(ipt,i) = half*thk_ly(i)*w_gauss(it,nptt)/thk(i)
494 posly(i,ipt) = zshift + half*thk_it(ipt,i)
496 posly(i,ipt) = posly(i,ipt - 1)
497 . + half*(thk_it(ipt,i) + thk_it(ipt-1,i))
499 thkly(j) = thk_it(ipt,i)
502 ip = drape(ie)%INDX_PLY(ilay)
504 drape_ply => drape(ie)%DRAPE_PLY(ip)
505 nslice = drape_ply%NSLICE
509 thinning = drape_ply%RDRAPE(it,1)
510 thk_it(ipt,i) = thinning*half*thk_ly(i)*w_gauss(it,nptt)
511 thk_it(ipt,i) = thk_it(ipt,i)/thickt_drape
513 posly(i,ipt) = zshift + half*thk_it(ipt,i)
515 posly(i,ipt) = posly(i,ipt - 1)
516 . + half*(thk_it(ipt,i) + thk_it(ipt-1,i))
518 thkly(j) = thk_it(ipt,i)
524 thk_it(ipt,i) = half*thk_ly(i)*w_gauss(it,nptt)
525 thk_it(ipt,i) = thk_it(ipt,i)/thickt_drape
527 posly(i,ipt) = zshift + half*thk_it(ipt,i)
529 posly(i,ipt) = posly(i,ipt - 1)
530 . + half*(thk_it(ipt,i) + thk_it(ipt-1,i))
532 thkly(j) = thk_it(ipt,i)
536 matly(jmly) = mat_ly(i)
538 ipt_all = ipt_all + nptt
547 pos_0 = geo(ippos+n,pid(1))
548 thk_nptt = geo(ipthk+n,pid(1))