55
56
57
58 USE my_alloc_mod
59 USE intbuf_fric_mod
62
63
64
65#include "implicit_f.inc"
66
67
68
69#include "com01_c.inc"
70#include "com04_c.inc"
71#include "param_c.inc"
72#include "remesh_c.inc"
73#include "scr03_c.inc"
74#include "scr17_c.inc"
75#include "units_c.inc"
76
77
78
79 INTEGER NRT, NINT, NTY, NOINT,NSN,IGAP,INTFRIC,NMN,IGSTI,
80 . INACTI,NRT_SH ,ILEV ,IGAP0,INTNITSCHE,NRTS,IGEO(NPROPGI
81INTEGER IRECT(4,*), IXS(NIXS,*), IXC(NIXC,*),
82 . NSV(*), IXTG(NIXTG,*), IXT(NIXT,*), IXP(NIXP,*),
83 . KNOD2ELS(*), KNOD2ELC(*), KNOD2ELTG(*), NOD2ELS(*), NOD2ELC(*),
84 . NOD2ELTG(*), IELES(*), INTTH, IELEC(*),
85 . SH3TREE(KSH3TREE,*), SH4TREE(KSH4TREE,*),IXR(NIXR,*) ,
86 . IPART(LIPART1,*), IPARTC(*), IPARTTG(*),
87 . ITAB(*), IXS10(6,*),MSEGTYP(*), IXS16(8,*), IXS20(12,*),MVOISN(4,*),
88 . IWORKSH(3,*),TAGPRT_FRIC(*),IPARTFRICS(*),IPARTFRICM(*),
89 . IRECTS(4,*),IELNRTS(*),ADRECTS(4,*),FACNRTS(*),MSR(*)
90
92 . stfac, gap,gapmin,gapinf, gapmax_s,bgapsmx ,gapmax_m
93
95 . x(3,*), stf(*), pm(npropm,*), geo(npropg,*), stfn(*),
96 . ms(*),wa(*),gap_s(*),gap_m(*),gap_n(12,*),
97 . areas(*),thk(*),thk_part(*),pen_old(5,nsn), fillsol(*),
98 . pm_stack(20,*)
99 INTEGER ID,IPARTNS(*),IPARTS(*)
100 INTEGER, DIMENSION(NUMELT), INTENT(IN) :: IPARTT
101 INTEGER, DIMENSION(NUMELP), INTENT(IN) :: IPARTP
102 INTEGER, DIMENSION(NUMELR), INTENT(IN) :: IPARTR
103 INTEGER, DIMENSION(NUMELS), INTENT(INOUT):: ELEM_LINKED_TO_SEGMENT
104 CHARACTER(LEN=NCHARTITLE) :: TITR
105 TYPE(INTBUF_FRIC_STRUCT_) INTBUF_FRIC_TAB(*)
106 TYPE (SURF_) :: IGRSURF
107 TYPE (SURF_) :: IGRSURF2
108 INTEGER, INTENT(IN) :: FLAG_ELEM_INTER25(NINTER25,NUMELS)
109
110
111
112 INTEGER NDX, I, J, INRT, NELS, MT, JJ, JJJ, NELC,
113 . MG, NUM, NPT, LL, L, NN, NELTG,N1,N2,N3,N4,IE,
114 . IP, NLEV, MYLEV, K, P, R, T,NRT1,NRT2,NSHIF,
115 . NS,IGTYP,NRTT,IPL,IPFMAX,
116 . IPFLMAX,NM,NEL,FC,PERM,NSHIFF,N,IPG
117
118 INTEGER JPERM(4) ,FACES(4,6),TAB1(4),TAB2(4),FACES10(3,16)
119
121 . dxm, gapmx, gapmn,
area, vol, dx,gaps1,gaps2, gapm, ddx,
122 . gaptmp, gapscale,sx1,sy1,sz1,sx2,sy2,sz2,sx3,sy3,sz3,
123 . slsfac,xl,gaps_mn
124 INTEGER, DIMENSION(:),ALLOCATABLE ::TAGNOD,TAGB
125 DATA jperm/2,3,4,1/
126 DATA faces/1,2,3,4,
127 . 1,2,6,5,
128 . 2,3,7,6,
129 . 3,4,8,7,
130 . 1,5,8,4,
131 . 5,6,7,8/
132 DATA faces10/1,11,14,
133 . 3,11,15,
134 . 5,14,15,
135 . 11,14,15,
136 . 1,13,14,
137 . 6,13,16,
138 . 5,14,16,
139 . 13,14,16,
140 . 3,11,12,
141 . 6,12,13,
142 . 1,11,13,
143 . 11,12,13,
144 . 3,12,15,
145 . 6,12,16,
146 . 5,15,16,
147 . 12,15,16/
148
149
150
151
152
153
154
155
156
157 slsfac = stfac
158 dxm=zero
159 ndx=0
160 nshif=0
161 gapmx=ep30
162 gapmn=ep30
163 gaps1=zero
164 gaps2=zero
165 gaps_mn=ep30
166 gapscale = one
167
168
169 nrtt =nrt+nrt_sh
170
171
172
173 ALLOCATE(tagb(numnod))
174 DO i=1,numnod
175 wa(i)=zero
176 ENDDO
177 DO i=1,numelc
178 mg=ixc(6,i)
179 ip = ipartc(i)
180 igtyp = igeo(11,mg)
181 IF ( thk_part(ip) /= zero .AND. iintthick == 0) THEN
182 dx=half*thk_part(ip)
183 ELSEIF ( thk(i) /= zero .AND. iintthick == 0) THEN
184 dx=half*thk(i)
185 ELSEIF(igtyp == 17 .OR. igtyp ==51 .OR. igtyp ==52) THEN
186 dx=half*thk(i)
187 ELSE
188 dx=half*geo(1,mg)
189 ENDIF
190 wa(ixc(2,i))=
max(wa(ixc(2,i)),dx)
191 wa(ixc(3,i))=
max(wa(ixc(3,i)),dx)
192 wa(ixc(4,i))=
max(wa(ixc(4,i)),dx)
193 wa(ixc(5,i))=
max(wa(ixc(5,i)),dx)
194 ENDDO
195 DO i=1,numeltg
196 mg=ixtg(5,i)
197 ip = iparttg(i)
198 igtyp = igeo(11,mg)
199 IF ( thk_part(ip) /= zero .AND. iintthick == 0) THEN
200 dx=half*thk_part(ip)
201 ELSEIF ( thk(numelc+i) /= zero .AND. iintthick == 0) THEN
202 dx=half*thk(numelc+i)
203 ELSEIF(igtyp == 17 .OR. igtyp ==51 .OR. igtyp ==52) THEN
204 dx=half*thk(numelc+i)
205 ELSE
206 dx=half*geo(1,mg)
207 ENDIF
208 wa(ixtg(2,i))=
max(wa(ixtg(2,i)),dx)
209 wa(ixtg(3,i))=
max(wa(ixtg(3,i)),dx)
210 wa(ixtg(4,i))=
max(wa(ixtg(4,i)),dx)
211 ENDDO
212
213 IF (ilev/=3) THEN
214 DO i=1,numnod
215 tagb(i) = 0
216 END DO
217 DO i=1,nrt
218 IF (msegtyp(i) /= 0) THEN
219 DO j =1,4
220 nn= irect(j,i)
221 tagb(nn) = 1
222 END DO
223 END IF
224 END DO
225 DO i=1,numnod
226 IF (tagb(i)==0) wa(i)=0
227 END DO
228 END IF
229
230 DO i=1,numelt
231 mg=ixt(4,i)
232 ip = ipartt(i)
233 IF ( thk_part(ip) > zero ) THEN
234 dx=half*thk_part(ip)
235 ELSE
236 dx=half*sqrt(geo(1,mg))
237 END IF
238 wa(ixt(2,i))=
max(wa(ixt(2,i)),dx)
239 wa(ixt(3,i))=
max(wa(ixt(3,i)),dx)
240 ENDDO
241 DO i=1,numelp
242 mg=ixp(5,i)
243 ip = ipartp(i)
244 IF ( thk_part(ip) > zero ) THEN
245 dx=half*thk_part(ip)
246 ELSE
247 dx=half*sqrt(geo(1,mg))
248 END IF
249 wa(ixp(2,i))=
max(wa(ixp(2,i)),dx)
250 wa(ixp(3,i))=
max(wa(ixp(3,i)),dx)
251 ENDDO
252 DO i=1,numelr
253 ip = ipartr(i)
254 IF ( thk_part(ip) > zero ) THEN
255 mg=ixr(1,i)
256 igtyp = igeo(11,mg)
257 dx=half*thk_part(ip)
258 wa(ixr(2,i))=
max(wa(ixr(2,i)),dx)
259 wa(ixr(3,i))=
max(wa(ixr(3,i)),dx)
260 IF (igtyp==12) wa(ixr(4,i))=
max(wa(ixr(4,i)),dx)
261 END IF
262 ENDDO
263 DO i=1,nsn
264 gap_s(i)=gapscale * wa(nsv(i))
265 gap_s(i)=
min(gap_s(i),gapmax_s)
266 ENDDO
267
268 IF(igap0 > 0)THEN
269 DO i=1,numnod
270 tagb(i)=0
271 ENDDO
272
273 IF(ilev /= 3 )THEN
274 CALL i24bord(igrsurf2%NSEG ,igrsurf2%NODES ,tagb)
275 ENDIF
276 IF(ilev == 2)THEN
277 CALL i24bord(igrsurf%NSEG ,igrsurf%NODES ,tagb)
278 ENDIF
279 DO i=1,nsn
280 ns = nsv(i)
281 IF( tagb(ns) > 0 ) gap_s(i) = em20
282 ENDDO
283 ENDIF
284
285 DO i=1,nsn
286 gaps1=
max(gaps1,gap_s(i))
287 gaps_mn=
min(gaps_mn,gap_s(i))
288 ENDDO
289
290 IF(intth > 0 ) THEN
291 IF(nadmesh==0)THEN
292 DO i = 1,nsn
293 areas(i) = zero
294 DO j= knod2elc(nsv(i))+1,knod2elc(nsv(i)+1)
295 ie = nod2elc(j)
296 sx1 = x(1,ixc(4,ie)) - x(1,ixc(2,ie))
297 sy1 = x(2,ixc(4,ie)) - x(2,ixc(2,ie))
298 sz1 = x(3,ixc(4,ie)) - x(3,ixc(2,ie))
299 sx2 = x(1,ixc(5,ie)) - x(1,ixc(3,ie))
300 sy2 = x(2,ixc(5,ie)) - x(2,ixc(3,ie))
301 sz2 = x(3,ixc(5,ie)) - x(3,ixc(3,ie))
302 sx3 = sy1*sz2 - sz1*sy2
303 sy3 = sz1*sx2 - sx1*sz2
304 sz3 = sx1*sy2 - sy1*sx2
305 areas(i) = areas(i)
306 . + one_over_8*sqrt(sx3*sx3+sy3*sy3+sz3*sz3)
307
308 ielec(i) = ixc(1,ie)
309 END DO
310
311 DO j= knod2eltg(nsv(i))+1,knod2eltg(nsv(i)+1)
312 ie = nod2eltg(j)
313 sx1 = x(1,ixtg(3,ie)) - x(1,ixtg(2,ie))
314 sy1 = x(2,ixtg(3,ie)) - x(2,ixtg(2,ie))
315 sz1 = x(3,ixtg(3,ie)) - x(3,ixtg(2,ie))
316 sx2 = x(1,ixtg(4,ie)) - x(1,ixtg(2,ie))
317 sy2 = x(2,ixtg(4,ie)) - x(2,ixtg(2,ie))
318 sz2 = x(3,ixtg(4,ie)) - x(3,ixtg(2,ie))
319 sx3 = sy1*sz2 - sz1*sy2
320 sy3 = sz1*sx2 - sx1*sz2
321 sz3 = sx1*sy2 - sy1*sx2
322 areas(i) = areas(i)
323 . + one_over_6*sqrt(sx3*sx3+sy3*sy3+sz3*sz3)
324
325 ielec(i) = ixtg(1,ie)
326 END DO
327 END DO
328 ELSE
329 DO i = 1,nsn
330 areas(i) = zero
331 DO j= knod2elc(nsv(i))+1,knod2elc(nsv(i)+1)
332 ie = nod2elc(j)
333
334 ip = ipartc(ie)
335 nlev =ipart(10,ip)
336 mylev=sh4tree(3,ie)
337 IF(mylev < 0) mylev=-(mylev+1)
338
339 IF(mylev==nlev)THEN
340 sx1 = x(1,ixc(4,ie)) - x(1,ixc(2,ie))
341 sy1 = x(2,ixc(4,ie)) - x(2,ixc(2,ie))
342 sz1 = x(3,ixc(4,ie)) - x(3,ixc(2,ie))
343 sx2 = x(1,ixc(5,ie)) - x(1,ixc(3,ie))
344 sy2 = x(2,ixc(5,ie)) - x(2,ixc(3,ie))
345 sz2 = x(3,ixc(5,ie)) - x(3,ixc(3,ie))
346 sx3 = sy1*sz2 - sz1*sy2
347 sy3 = sz1*sx2 - sx1*sz2
348 sz3 = sx1*sy2 - sy1*sx2
349 areas(i) = areas(i)
350 . + one_over_8*sqrt(sx3*sx3+sy3*sy3+sz3*sz3)
351
352 ielec(i) = ixc(1,ie)
353 END IF
354
355 END DO
356
357 DO j= knod2eltg(nsv(i))+1,knod2eltg(nsv(i)+1)
358 ie = nod2eltg(j)
359
360 ip = iparttg(ie)
361 nlev =ipart(10,ip)
362 mylev=sh3tree(3,ie)
363 IF(mylev < 0) mylev=-(mylev+1)
364
365 IF(mylev==nlev)THEN
366 sx1 = x(1,ixtg(3,ie)) - x(1,ixtg(2,ie))
367 sy1 = x(2,ixtg(3,ie)) - x(2,ixtg(2,ie))
368 sz1 = x(3,ixtg(3,ie)) - x(3,ixtg(2,ie))
369 sx2 = x(1,ixtg(4,ie)) - x(1,ixtg(2,ie))
370 sy2 = x(2,ixtg(4,ie)) - x(2,ixtg(2,ie))
371 sz2 = x(3,ixtg(4,ie)) - x(3,ixtg(2,ie))
372 sx3 = sy1*sz2 - sz1*sy2
373 sy3 = sz1*sx2 - sx1*sz2
374 sz3 = sx1*sy2 - sy1*sx2
375 areas(i) = areas(i)
376 . + one_over_6*sqrt(sx3*sx3+sy3*sy3+sz3*sz3)
377
378 ielec(i) = ixtg(1,ie)
379 END IF
380
381 END DO
382 END DO
383 END IF
384 END IF
385
386
387
388
389 IF(intfric > 0) THEN
390
391 IF(numels/=0)THEN
392 DO i = 1,nsn
393 ipfmax = 0
394 ipflmax = 0
395 DO j= knod2els(nsv(i))+1,knod2els(nsv(i)+1)
396 ie = nod2els(j)
397 ip = iparts(ie)
398 ipg = tagprt_fric(ip)
399 IF(ipg > 0.AND.ip>ipfmax) THEN
401 . ipg,intbuf_fric_tab(intfric)%S_TABPARTS_FRIC,
402 . intbuf_fric_tab(intfric)%TABPARTS_FRIC,ipl)
403 IF(ipl /=0) THEN
404 ipfmax = ip
405 ipflmax = ipl
406 ENDIF
407 ENDIF
408 ENDDO
409
410
411 IF(ipfmax/=0) THEN
412 ipartfrics(i) = ipflmax
413 ENDIF
414
415 ENDDO
416 ENDIF
417
418 IF(numelc/=0.OR.numeltg/=0) THEN
419 DO i = 1,nsn
420 ipfmax = 0
421 ipflmax = 0
422 DO j= knod2elc(nsv(i))+1,knod2elc(nsv(i)+1)
423 ie = nod2elc(j)
424 ip = ipartc(ie)
425 ipg = tagprt_fric(ip)
426 IF(ipg > 0.AND.ip>ipfmax) THEN
428 . ipg,intbuf_fric_tab(intfric)%S_TABPARTS_FRIC,
429 . intbuf_fric_tab(intfric)%TABPARTS_FRIC,ipl)
430 IF(ipl /=0) THEN
431 ipfmax = ip
432 ipflmax = ipl
433 ENDIF
434 ENDIF
435 ENDDO
436
437
438 DO j= knod2eltg(nsv(i))+1,knod2eltg(nsv(i)+1)
439 ie = nod2eltg(j)
440 ip = iparttg(ie)
441 ipg = tagprt_fric(ip)
442 IF(ipg > 0.AND.ip>ipfmax) THEN
444 . ipg,intbuf_fric_tab(intfric)%S_TABPARTS_FRIC,
445 . intbuf_fric_tab(intfric)%TABPARTS_FRIC,ipl)
446
447 IF(ipl /=0) THEN
448 ipfmax = ip
449 ipflmax = ipl
450 ENDIF
451 ENDIF
452 ENDDO
453
454 IF(ipfmax/=0) THEN
455 ipartfrics(i) = ipflmax
456 ENDIF
457
458 ENDDO
459 ENDIF
460 ENDIF
461
462
463
464 IF(intnitsche > 0 ) THEN
465
466
467
470 DO nm=1,nmn
472 END DO
473
474 DO i=1,nrts
475 DO j=1,4
477 irects(j,i) = nm
478 ENDDO
479 ENDDO
480
482
483
484 IF (ilev==2) THEN
485 nrt1=igrsurf2%NSEG
486 DO i=1,nrt1
487 nel=igrsurf2%ELEM(i)
488 IF(igrsurf2%ELTYP(i)==1 ) THEN
489 ielnrts(i) = nel
490 ENDIF
491 ENDDO
492 nshiff = nrt1
493 nrt2=igrsurf%NSEG
494 DO i=1,nrt2
495 nel=igrsurf%ELEM(i)
496 IF(igrsurf%ELTYP(i) == 1 ) THEN
497 ielnrts(nshiff+i) = nel
498 ENDIF
499 ENDDO
500 ELSE
501 DO i=1,nrt
502 nel=igrsurf%ELEM(i)
503 IF(igrsurf%ELTYP(i) == 1 ) THEN
504 ielnrts(i) = nel
505 ENDIF
506 ENDDO
507 ENDIF
508
509
510 adrects(1:4,1:nrt) = 0
511 DO i=1,nrt
512 ie = ielnrts(i)
513 n1 = irect(1,i)
514 n2 = irect(2,i)
515 n3 = irect(3,i)
516 n4 = irect(4,i)
517
518
519 IF(ie > 0) THEN
520
521 IF (ie <= numels8 ) THEN
522
523 DO k=1,4
524 DO j=1,8
525 IF(adrects(k,i)==0) THEN
526 n=ixs(j+1,ie)
527 IF(n==irect(k,i)) THEN
528 adrects(k,i) = j
529 ENDIF
530 ENDIF
531 ENDDO
532 ENDDO
533
534 IF(n3==n4) THEN
535 DO k=1,4
536 IF(adrects(k,i) == 5) THEN
537 adrects(k,i) = 6
538 ELSEIF(adrects(k,i) == 6) THEN
539 adrects(k,i) = 5
540 ENDIF
541 ENDDO
542 ENDIF
543
544 ELSEIF(ie <= numels8+numels10 ) THEN
545 DO k=1,3
546 DO j=1,6
547 n=ixs10(j,ie-numels8)
548 IF(n==irect(k,i)) THEN
549 adrects(k,i) = 10 +j
550 ENDIF
551 ENDDO
552 DO j=1,8
553 IF(adrects(k,i)==0) THEN
554
555 n=ixs(j+1,ie)
556 IF(n==irect(k,i)) THEN
557 adrects(k,i) = j
558 ENDIF
559 ENDIF
560 ENDDO
561
562 ENDDO
563 ELSEIF(ie <= numels8+numels10+numels20 ) THEN
564 DO k=1,4
565 DO j=1,12
566 n=ixs20(j,ie-numels8-numels10)
567 IF(n==irect(k,i)) THEN
568 adrects(k,i) = 20 +j
569 ENDIF
570 ENDDO
571 DO j=1,8
572 IF(adrects(k,i)==0) THEN
573 n=ixs(j+1,ie)
574 IF(n==irect(k,i)) THEN
575 adrects(k,i) = j
576 ENDIF
577 ENDIF
578 ENDDO
579 ENDDO
580 ELSEIF(ie <= numels8+numels10+numels20+numels16)THEN
581 DO k=1,4
582 DO j=1,8
583 n=ixs20(j,ie-numels8-numels10-numels20)
584 IF(n==irect(k,i)) THEN
585 adrects(k,i) = 40 +j
586 ENDIF
587 ENDDO
588 DO j=1,8
589 IF(adrects(k,i)==0) THEN
590 n=ixs(j+1,ie)
591 IF(n==irect(k,i)) THEN
592 adrects(k,i) = j
593 ENDIF
594 ENDIF
595 ENDDO
596
597 ENDDO
598 ENDIF
599
600 ENDIF
601
602 ENDDO
603
604
605 DO i=1,nrt
606 ie = ielnrts(i)
607 n1 = irect(1,i)
608 n2 = irect(2,i)
609 n3 = irect(3,i)
610 n4 = irect(4,i)
611
612 IF(ie > 0) THEN
613
614 IF(ie<= numels8 ) THEN
615 IF(n3 /= n4) THEN
616 tab1(1) = n1
617 tab1(2) = n2
618 tab1(3) = n3
619 tab1(4) = n4
620 DO k=1,4
621 DO j=1,4-k
622 IF(tab1(j+1) < tab1(j)) THEN
623 perm = tab1(j+1)
624 tab1(j+1) = tab1(j)
625 tab1(j) = perm
626 ENDIF
627 ENDDO
628 ENDDO
629
630 DO fc=1,6
631 tab2(1) = ixs(faces(1,fc)+1,ie)
632 tab2(2) = ixs(faces(2,fc)+1,ie)
633 tab2(3) = ixs(faces(3,fc)+1,ie)
634 tab2(4) = ixs(faces(4,fc)+1,ie)
635 DO k=1,4
636 DO j=1,4-k
637 IF(tab2(j+1) < tab2(j)) THEN
638 perm = tab2(j+1)
639 tab2(j+1) = tab2(j)
640 tab2(j) = perm
641 ENDIF
642 ENDDO
643 ENDDO
644 IF(tab1(1)==tab2(1).AND.tab1(2)==tab2(2).AND.tab1(3)==tab2(3)) THEN
645 facnrts(i) = fc
646 EXIT
647 ENDIF
648 ENDDO
649 ELSE
650 tab1(1) = n1
651 tab1(2) = n2
652 tab1(3) = n3
653
654 DO k=1,3
655 DO j=1,3-k
656 IF(tab1(j+1) < tab1(j)) THEN
657 perm = tab1(j+1)
658 tab1(j+1) = tab1(j)
659 tab1(j) = perm
660 ENDIF
661 ENDDO
662 ENDDO
663
664 DO fc=1,6
665 n1 = ixs(faces(1,fc)+1,ie)
666 n2 = ixs(faces(2,fc)+1,ie)
667 n3 = ixs(faces(3,fc)+1,ie)
668 n4 = ixs(faces(4,fc)+1,ie)
669 tab2(1) =n1
670 IF(n1/=n2.AND.n2/=n3) THEN
671 tab2(2) =n2
672 tab2(3) =n3
673 ELSEIF(n1/=n2) THEN
674 tab2(2) =n2
675 tab2(3) =n4
676 ELSEIF(n2/=n3) THEN
677 tab2(2) =n3
678 tab2(3) =n4
679 ELSE
680 EXIT
681 ENDIF
682 DO k=1,3
683 DO j=1,3-k
684 IF(tab2(j+1) < tab2(j)) THEN
685 perm = tab2(j+1)
686 tab2(j+1) = tab2(j)
687 tab2(j) = perm
688 ENDIF
689 ENDDO
690 ENDDO
691 IF(tab1(1)==tab2(1).AND.tab1(2)==tab2(2).AND.tab1(3)==tab2(3)) THEN
692 facnrts(i) = fc
693 EXIT
694 ENDIF
695 ENDDO
696 ENDIF
697
698 ELSEIF(ie<= numels8+numels10 ) THEN
699 tab1(1) = adrects(1,i)
700 tab1(2) = adrects(2,i)
701 tab1(3) = adrects(3,i)
702 DO k=1,3
703 DO j=1,3-k
704 IF(tab1(j+1) < tab1(j)) THEN
705 perm = tab1(j+1)
706 tab1(j+1) = tab1(j)
707 tab1(j) = perm
708 ENDIF
709 ENDDO
710 ENDDO
711 DO fc=1,16
712 IF(tab1(1)==faces10(1,fc).AND.tab1(2)==faces10(2,fc).AND.tab1(3)==faces10(3,fc)) THEN
713 facnrts(i) = fc
714 EXIT
715 ENDIF
716 ENDDO
717
718 ELSEIF(ie <= numels8+numels10+numels20 ) THEN
719
720 ENDIF
721
722 ENDIF
723
724 ENDDO
725
726 ENDIF
727
728
729
730
731
732 IF (ilev==2) THEN
733
734 nrt1=igrsurf2%NSEG
736 1 x ,irect ,stf ,ixs ,pm ,
737 2 geo ,nrt1 ,ixc ,nint ,stfac ,
738 3 nty ,gap ,noint ,stfn ,nsn ,
739 4 ms ,nsv ,ixtg ,igap ,gap_m ,
740 6 ixt ,ixp ,slsfac,dxm ,ndx ,
741 9 knod2els ,knod2elc ,knod2eltg ,nod2els ,
742 a nod2elc,nod2eltg ,igrsurf2 ,intth,
743 b ieles ,ielec ,areas ,sh4tree ,sh3tree ,
744 c ipart ,ipartc ,iparttg ,thk ,thk_part ,
745 d ixr ,itab ,bgapsmx ,ixs10 ,msegtyp ,
746 e ixs16 ,ixs20 ,gap_n ,gaps1 ,gaps2 ,
747 f gapmx , gapmn ,gapscale ,nshif ,gapmax_m,
748 g
id ,titr ,igeo ,fillsol ,nrtt ,
749 h pm_stack, iworksh,intfric ,tagprt_fric,ipartfrics,
750 i ipartfricm,iparts,intbuf_fric_tab ,elem_linked_to_segment,
751 j igsti , flag_elem_inter25)
752 nrt2=igrsurf%NSEG
753 nshif = nrt1
755 1 x ,irect ,stf ,ixs ,pm ,
756 2 geo ,nrt2 ,ixc ,nint ,stfac ,
757 3 nty ,gap ,noint ,stfn ,nsn ,
758 4 ms ,nsv ,ixtg ,igap ,gap_m ,
759 6 ixt ,ixp ,
760 8 slsfac,dxm ,ndx ,
761 9 knod2els ,knod2elc ,knod2eltg ,nod2els ,
762 a nod2elc,nod2eltg ,igrsurf ,intth,
763 b ieles ,ielec ,areas ,sh4tree ,sh3tree ,
764 c ipart ,ipartc ,iparttg ,thk ,thk_part ,
765 d ixr ,itab ,bgapsmx ,ixs10 ,msegtyp ,
766 e ixs16 ,ixs20 ,gap_n ,gaps1 ,gaps2 ,
767 f gapmx , gapmn ,gapscale ,nshif ,gapmax_m,
768 g
id ,titr ,igeo ,fillsol ,nrtt ,
769 h pm_stack , iworksh,intfric,tagprt_fric,ipartfrics,
770 i ipartfricm,iparts,intbuf_fric_tab ,elem_linked_to_segment,
771 j igsti , flag_elem_inter25)
772 ELSE
774 1 x ,irect ,stf ,ixs ,pm ,
775 2 geo ,nrt ,ixc ,nint ,stfac ,
776 3 nty ,gap ,noint ,stfn ,nsn ,
777 4 ms ,nsv ,ixtg ,igap ,gap_m ,
778 6 ixt ,ixp ,slsfac,dxm ,ndx ,
779 9 knod2els ,knod2elc ,knod2eltg ,nod2els ,
780 a nod2elc,nod2eltg ,igrsurf ,intth,
781 b ieles ,ielec ,areas ,sh4tree ,sh3tree ,
782 c ipart ,ipartc ,iparttg ,thk ,thk_part ,
783 d ixr ,itab ,bgapsmx ,ixs10 ,msegtyp ,
784 e ixs16 ,ixs20 ,gap_n ,gaps1 ,gaps2 ,
785 f gapmx , gapmn ,gapscale ,nshif ,gapmax_m,
786 g
id ,titr ,igeo ,fillsol ,nrtt ,
787 h pm_stack , iworksh,intfric,tagprt_fric,ipartfrics,
788 i ipartfricm,iparts,intbuf_fric_tab ,elem_linked_to_segment,
789 j igsti , flag_elem_inter25)
790 END IF
791
792
793
794
795
796 gapmx=sqrt(gapmx)
797 gapmx=
min(gapmx,gapmax_m)
798
799
800
801 IF(gap<=zero)THEN
802 IF(ndx/=0)THEN
803 gapmin = gapmn
804 gapmin =
min(half*gapmx,gapmin)
805 ELSE
806
807 gapmin = zero
808 ENDIF
809
810 ELSE
811 gapmin = gap
812 ENDIF
813
814 gapmx=zero
815 gapmn=ep30
816 DO i=1,nrt
817 gapmx=
max(gapmx,gap_m(i))
818 gapmn=
min(gapmn,gap_m(i))
819 END DO
820 IF(ipri>=1) THEN
821 IF(gap<=zero)THEN
822 WRITE(iout,1400)gaps_mn,gaps1
823 WRITE(iout,1500)gapmn,gapmx
824 END IF
826
827 gap = gaps1+gaps2
828
829
830
831 DO 610 l=1,nsn
832 stfn(l) = one
833 610 CONTINUE
834
835
836
837 bgapsmx = zero
838 gapinf=ep30
839 DO i = 1, nsn
840 gapinf =
min(gapinf,gap_s(i))
841 bgapsmx =
max(bgapsmx,gap_s(i))
842 ENDDO
843 DO i = 1, nrt
844 gapinf =
min(gapinf,gap_m(i))
845 ENDDO
846 gapinf=
max(gapinf,gapmin)
847
848 DO i=1,nrt
849 CALL insol3et(x ,irect ,ixs ,nint ,mvoisn(2,i),i ,
850 .
area ,noint ,knod2els,nod2els,ixs10 ,
851 . ixs16,ixs20 ,mvoisn(1,i))
852
853 IF (mvoisn(1,i)==10) THEN
854
855 gap_n(1,i) = three*one_over_8*gap_n(1,i)
856 stf(i) = sixteen*stf(i)
857 ELSEIF (mvoisn(1,i)==16) THEN
858 gap_n(1,i) = gap_n(1,i)/4
859 END IF
860 END DO
861
862
863
864
865
866
867
868
869 IF (nrt_sh>0) THEN
870 j=nrt
871 DO i=1,nrt
872 IF (msegtyp(i) > 0 .AND.msegtyp(i)<=nrtt ) THEN
873 j = j + 1
874 stf(j) = stf(i)
875 gap_m(j)=gap_m(i)
876 IF(intth > 0 ) ieles(j) = ieles(i)
877 IF(intfric > 0) ipartfricm(j)=ipartfricm(i)
878 END IF
879 END DO
880 END IF
881
882
883
884
885 IF (inacti/=0) THEN
887 1 x ,irect ,nrt ,nsn ,nsv ,pen_old, stf)
888
889 DO i=1,numnod
890 tagb(i)=0
891 ENDDO
892
893 DO i=1,numelc
894 ip = ipartc(i)
895 DO j=1,4
896 tagb(ixc(1+j,i))=ip
897 ENDDO
898 ENDDO
899 DO i=1,numeltg
900 ip = iparttg(i)
901 DO j=1,3
902 tagb(ixtg(1+j,i))=ip
903 ENDDO
904 ENDDO
905
906
907
908
909
910
911
912
913
914
915
916
917 DO i=1,nrt
918 IF (mvoisn(2,i)>0) THEN
919 ip = iparts(mvoisn(2,i))
920 mvoisn(3,i) =ip
921 DO j=1,4
922 tagb(irect(j,i))=ip
923 ENDDO
924 END IF
925 END DO
926 DO i=1,nsn
927 ns = nsv(i)
928 ipartns(i) = tagb(ns)
929
930 IF (ipartns(i)==0) ipartns(i) =-1
931 ENDDO
932
933 j=nrt
934 DO i=1,nrt
935 IF (msegtyp(i) > 0 .AND.msegtyp(i)<=nrtt) THEN
936 j = j + 1
937 ip = tagb(irect(1,i))
938 mvoisn(3,i) =ip
939 mvoisn(3,j) =ip
940 END IF
941 END DO
942 END IF
943
944 DEALLOCATE(tagb)
945 RETURN
946
947 1400 FORMAT(2x,'MIN,MAX OF SECONDARY GAP: ',2(1pg20.13))
948 1500 FORMAT(2x,'MIN,MAX OF MAIN GAP: ',2(1pg20.13)/)
subroutine i24normns(x, irect, nrt, nsn, nsv, pen_old, stf)
subroutine i24bord(nseg, surf_nodes, tagb)
subroutine i24gapm(x, irect, stf, ixs, pm, geo, nrt, ixc, nint, stfac, nty, gap, noint, stfn, nsn, ms, nsv, ixtg, igap, gap_m, ixt, ixp, slsfac, dxm, ndx, knod2els, knod2elc, knod2eltg, nod2els, nod2elc, nod2eltg, igrsurf, intth, ieles, ielec, areas, sh4tree, sh3tree, ipart, ipartc, iparttg, thk, thk_part, ixr, itab, bgapsmx, ixs10, msegtyp, ixs16, ixs20, gap_n, gaps1, gaps2, gapmx, gapmn, gapscale, nshift, gapmax_m, id, titr, igeo, fillsol, nrtt, pm_stack, iworksh, intfric, tagprt_fric, ipartfrics, ipartfricm, iparts, intbuf_fric_tab, elem_linked_to_segment, igsti, flag_elem_inter25)
subroutine insol3et(x, irect, ixs, nint, nel, i, area, noint, knod2els, nod2els, ixs10, ixs16, ixs20, nnod)
integer, parameter nchartitle
subroutine tagnod(ix, nix, nix1, nix2, numel, iparte, tagbuf, npart)