58
59 USE my_alloc_mod
60 USE intbuf_fric_mod
63
64
65
66#include "implicit_f.inc"
67
68
69
70#include "com01_c.inc"
71#include "com04_c.inc"
72#include "param_c.inc"
73#include "remesh_c.inc"
74#include "scr03_c.inc"
75#include "scr17_c.inc"
76#include "units_c.inc"
77
78
79
80 INTEGER NRT, NINT, NTY, NOINT,NSN,IGAP,,
81 . INACTI,NRT_SH ,ILEV ,IGAP0,IGEO(NPROPGI,*), IVIS2
82 INTEGER IRECT(4,*), IXS(NIXS,*), IXC(NIXC,*),
83 . NSV(*), IXTG(NIXTG,*), IXT(NIXT,*), IXP(NIXP,*),
84 . KNOD2ELS(*), (*), KNOD2ELTG(*), NOD2ELS(*), NOD2ELC(*),
85 . NOD2ELTG(*), INTTH,
86 . SH3TREE(KSH3TREE,*), SH4TREE(KSH4TREE,*),(NIXR,*) ,
87 . IPART(LIPART1,*), IPARTC(*), IPARTTG(*),
88 . ITAB(*), IXS10(6,*),MSEGTYP(*), IXS16(*), IXS20(*),
89 . IWORKSH(3,*), KNOD2EL1D(*),NOD2EL1D(*),TAGPRT_FRIC(*),
90 . IPARTFRICS(*),IPARTFRICM(*),IPARTSM(*),IELES(*),IELEM(*)
91
93 . stfac, gap, gapscale, gapmin,gapinf, gapmax_s,bgapsmx ,gapmax_m,
94 . percent_size, gapm_mx, gaps_mx, gaps_l_mx, gapm_l_mx,drad
95
97 . x(3,*), stf(*), pm(npropm,*), geo(npropg,*), stfn(*),
98 . ms(*),wa(*),gap_s(*),gap_m(*),gap_n(4,*),
99 . areas(*),thk(*),thk_part(*),pen_old(5,nsn), fillsol(*),
100 . pm_stack(20,*),gap_s_l(*),gap_m_l(*)
101 INTEGER ID,IPARTS(*)
102 INTEGER, DIMENSION(NUMELT), INTENT(IN) :: IPARTT
103 INTEGER, DIMENSION(NUMELP), INTENT(IN) :: IPARTP
104 INTEGER, DIMENSION(NUMELR), INTENT(IN) :: IPARTR
105 CHARACTER(LEN=NCHARTITLE) :: TITR
106 TYPE(INTBUF_FRIC_STRUCT_) INTBUF_FRIC_TAB(*)
107 INTEGER , INTENT(INOUT) :: IDEL_SOLID
108 INTEGER , INTENT(INOUT) :: IELEM_M(2,NRT+NRT_SH)
109 INTEGER, DIMENSION(NUMELS), INTENT(INOUT):: ELEM_LINKED_TO_SEGMENT
110 INTEGER, INTENT(IN) :: NIN25
111 INTEGER, INTENT(IN) :: FLAG_ELEM_INTER25(NINTER25,NUMELS)
112
113
114
115 INTEGER NDX, I, J, INRT, NELS, MT, JJ, JJJ, NELC,
116 . MG, NUM, NPT, LL, L, NN, NELTG,N1,N2,N3,N4,IE,
117 . IP, NLEV, MYLEV, K, P, R, T,IAD,
118 . NS,IGTYP,NRTT,NNOD,ISUBSTACK,IPFMAX,IPL,
119 . IPFLMAX,IPG,NELEM,STAT
120 INTEGER, DIMENSION(:), ALLOCATABLE :: TAGB
121 INTEGER JPERM(4)
122
124 . dxm, gapmx, gapmn,
area, vol, dx, gapm, ddx,
125 . gaptmp, sx1,sy1,sz1,sx2,sy2,sz2,sx3,sy3,sz3,
126 . slsfac,xl,gaps_mn, stv
127 DATA jperm/2,3,4,1/
128 INTEGER, DIMENSION(:),ALLOCATABLE ::INRTIE
129
130
131
132
133
134
135
136 ALLOCATE(tagb(numnod))
137 slsfac = stfac
138
139 IF(igap==3)THEN
140 DO i=1,nrt
141 gap_m_l(i)=ep30
142 ENDDO
143 DO i=1,nsn
144 gap_s_l(i)=ep30
145 ENDDO
146 ENDIF
147
148 dxm=zero
149 ndx=0
150 gapmx=ep30
151 gapmn=ep30
152 gapm_mx =zero
153 gaps_mx =zero
154 gaps_mn =ep30
155 gaps_l_mx=zero
156 gapm_l_mx=zero
157
158 gapmin = zero
159
160
161 nrtt =nrt+nrt_sh
162
163 IF(intth > 0)THEN
164 nelem = numelc+numeltg+numels+numelr
165 + + numelp+numelt+numelq+numelr+numelx+numelig3d
166 ALLOCATE(inrtie(nelem),stat=stat)
167 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
168 . msgtype=msgerror,
169 . c1='INRTIE')
170 inrtie=0
171 END IF
172
173 IF(igap==3)THEN
174 DO i=1,numnod
175 wa(i)=ep30
176 ENDDO
177 DO i=1,nrt
178 xl = ep30
179
180 DO j=1,4
181 n1=irect(j,i)
182 n2=irect(jperm(j),i)
183 IF(n1 /= n2 .AND. n1 /= 0)
184 . xl=
min(xl,sqrt((x(1,n1)-x(1,n2))**2+(x(2,n1)-x(2,n2))**2+
185 . (x(3,n1)-x(3,n2))**2))
186 ENDDO
187
188 gap_m_l(i)=
min(percent_size*xl,gapmax_m)
189 gapm_l_mx =
max(gapm_l_mx,gap_m_l(i))
190
191 DO j=1,4
192 wa(irect(j,i)) =
min(wa(irect(j,i)),percent_size*xl)
193 ENDDO
194 ENDDO
195
196 DO i=1,nsn
197 gap_s_l(i)=wa(nsv(i))
198 gap_s_l(i)=
min(gap_s_l(i),gapmax_s)
199 ENDDO
200
201 ENDIF
202
203
204
205 DO i=1,numnod
206 wa(i)=zero
207 ENDDO
208 DO i=1,numelc
209 mg=ixc(6,i)
210 ip = ipartc(i)
211 igtyp = igeo(11,mg)
212 IF ( thk_part(ip) /= zero .AND. iintthick == 0) THEN
213 dx=half*thk_part(ip)
214 ELSEIF ( thk(i) /= zero .AND. iintthick == 0) THEN
215 dx=half*thk(i)
216 ELSEIF(igtyp == 17 .OR. igtyp == 51 .OR.igtyp ==52) THEN
217 dx=half*thk(i)
218 ELSE
219 dx=half*geo(1,mg)
220 ENDIF
221 wa(ixc(2,i))=
max(wa(ixc(2,i)),dx)
222 wa(ixc(3,i))=
max(wa(ixc(3,i)),dx)
223 wa(ixc(4,i))=
max(wa(ixc(4,i)),dx)
224 wa(ixc(5,i))=
max(wa(ixc(5,i)),dx)
225 ENDDO
226 DO i=1,numeltg
227 mg=ixtg(5,i)
228 ip = iparttg(i)
229 igtyp = igeo(11,mg)
230 IF ( thk_part(ip) /= zero .AND. iintthick == 0) THEN
231 dx=half*thk_part(ip)
232 ELSEIF ( thk(numelc+i) /= zero .AND. iintthick == 0) THEN
233 dx=half*thk(numelc+i)
234 ELSEIF(igtyp == 17 .OR. igtyp == 51 .OR. igtyp ==52) THEN
235 dx=half*thk(numelc+i)
236 ELSE
237 dx=half*geo(1,mg)
238 ENDIF
239 wa(ixtg(2,i))=
max(wa(ixtg(2,i)),dx)
240 wa(ixtg(3,i))=
max(wa(ixtg(3,i)),dx)
241 wa(ixtg(4,i))=
max(wa(ixtg(4,i)),dx)
242 ENDDO
243
244 IF (ilev/=3) THEN
245 DO i=1,numnod
246 tagb(i) = 0
247 END DO
248 DO i=1,nrt
249
250 IF (msegtyp(i) /= 0) THEN
251 DO j =1,4
252 nn= irect(j,i)
253 tagb(nn) = 1
254 END DO
255 END IF
256 END DO
257 DO i=1,numnod
258 IF (tagb(i)==0) wa(i)=0
259 END DO
260 END IF
261
262 DO i=1,numelt
263 mg=ixt(4,i)
264 ip = ipartt(i)
265 IF ( thk_part(ip) > zero ) THEN
266 dx=half*thk_part(ip)
267 ELSE
268 dx=half*sqrt(geo(1,mg))
269 END IF
270 wa(ixt(2,i))=
max(wa(ixt(2,i)),dx)
271 wa(ixt(3,i))=
max(wa(ixt(3,i)),dx)
272 ENDDO
273 DO i=1,numelp
274 mg=ixp(5,i)
275 ip = ipartp(i)
276 IF ( thk_part(ip) > zero ) THEN
277 dx=half*thk_part(ip)
278 ELSE
279 dx=half*sqrt(geo(1,mg))
280 END IF
281 wa(ixp(2,i))=
max(wa(ixp(2,i)),dx)
282 wa(ixp(3,i))=
max(wa(ixp(3,i)),dx)
283 ENDDO
284 DO i=1,numelr
285 ip = ipartr(i)
286 IF ( thk_part(ip) > zero ) THEN
287 mg=ixr(1,i)
288 igtyp = igeo(11,mg)
289 dx=half*thk_part(ip)
290 wa(ixr(2,i))=
max(wa(ixr(2,i)),dx)
291 wa(ixr(3,i))=
max(wa(ixr(3,i)),dx)
292 IF (igtyp==12) wa(ixr(4,i))=
max(wa(ixr(4,i)),dx)
293 END IF
294 ENDDO
295 DO i=1,nsn
296 gap_s(i)=gapscale * wa(nsv(i))
297 gap_s(i)=
min(gap_s(i),gapmax_s)
298 ENDDO
299
300 IF(igap0 == 1)THEN
301 DO i=1,numnod
302 tagb(i)=0
303 ENDDO
304
305 IF(ilev /= 3 )THEN
306 CALL i25bord(nrt ,irect ,tagb )
307
308
309 ENDIF
310
311
312
313
314 DO i=1,nsn
315 ns = nsv(i)
316 IF( tagb(ns) > 0 ) gap_s(i) = zero
317 ENDDO
318 ENDIF
319
320 DO i=1,nsn
321 IF(igap /= 3) THEN
322 gaps_mx=
max(gaps_mx,gap_s(i))
323 gaps_mn=
min(gaps_mn,gap_s(i))
324 ELSE
325 gaps_mx =
max(gaps_mx,gap_s(i))
326 gaps_l_mx =
max(gaps_l_mx,gap_s_l(i))
327 gaps_mn =
min(gaps_mn,gap_s(i),gap_s_l(i))
328 END IF
329 ENDDO
330
331
332
333
334 IF(intfric > 0) THEN
335
336 IF(numels/=0)THEN
337 DO i = 1,nsn
338 ipfmax = 0
339 ipflmax = 0
340 DO j= knod2els(nsv(i))+1,knod2els(nsv(i)+1)
341 ie = nod2els(j)
342 ip = iparts(ie)
343 ipg = tagprt_fric(ip)
344 IF(ipg > 0.AND.ip>ipfmax) THEN
346 . ipg,intbuf_fric_tab(intfric)%S_TABPARTS_FRIC,
347 . intbuf_fric_tab(intfric)%TABPARTS_FRIC,ipl )
348 IF(ipl /=0) THEN
349 ipfmax = ip
350 ipflmax = ipl
351 ENDIF
352 ENDIF
353 ENDDO
354
355
356 IF(ipfmax/=0) THEN
357 ipartfrics(i) = ipflmax
358 ENDIF
359
360 ENDDO
361 ENDIF
362
363 IF(numelc/=0.OR.numeltg/=0) THEN
364 DO i = 1,nsn
365 ipfmax = 0
366 ipflmax = 0
367 DO j= knod2elc(nsv(i))+1,knod2elc(nsv(i)+1)
368 ie = nod2elc(j)
369 ip = ipartc(ie)
370 ipg = tagprt_fric(ip)
371 IF(ipg > 0.AND.ip>ipfmax) THEN
373 . ipg,intbuf_fric_tab(intfric)%S_TABPARTS_FRIC,
374 . intbuf_fric_tab(intfric)%TABPARTS_FRIC,ipl )
375 IF(ipl /=0) THEN
376 ipfmax = ip
377 ipflmax = ipl
378 ENDIF
379 ENDIF
380 ENDDO
381
382 DO j= knod2eltg(nsv(i))+1,knod2eltg(nsv(i)+1)
383 ie = nod2eltg(j)
384 ip = iparttg(ie)
385 ipg = tagprt_fric(ip)
386 IF(ipg > 0.AND.ip>ipfmax) THEN
388 . ipg,intbuf_fric_tab(intfric)%S_TABPARTS_FRIC,
389 . intbuf_fric_tab(intfric)%TABPARTS_FRIC,ipl )
390
391 IF(ipl /=0) THEN
392 ipfmax = ip
393 ipflmax = ipl
394 ENDIF
395 ENDIF
396 ENDDO
397
398 IF(ipfmax/=0) THEN
399 ipartfrics(i) = ipflmax
400 ENDIF
401
402 ENDDO
403 ENDIF
404
405
406 ENDIF
407
408
409
410
411
412
414 1 x ,irect ,stf ,ixs ,pm ,
415 2 geo ,nrt ,ixc ,nint ,stfac ,
416 3 nty ,gap ,noint ,stfn ,nsn ,
417 4 ms ,nsv ,ixtg ,igap ,gap_m ,
418 6 ixt ,ixp ,
419 8 slsfac,dxm ,ndx ,
420 9 knod2els ,knod2elc ,knod2eltg ,nod2els ,
421 a nod2elc,nod2eltg ,intth,
422 b ieles ,ielem ,areas ,sh4tree ,sh3tree ,
423 c ipart ,ipartc ,iparttg ,thk ,thk_part ,
424 d ixr ,itab ,bgapsmx ,ixs10 ,msegtyp ,
425 e ixs16 ,ixs20 ,gap_n ,gaps_mx ,gapm_mx ,
426 f gapmx , gapmn ,gapscale ,gapmax_m,
427 g
id ,titr ,igeo ,fillsol ,nrtt ,
428 h pm_stack, iworksh,intfric,tagprt_fric,ipartfrics,
429 i ipartfricm,iparts,intbuf_fric_tab,ipartsm,inrtie,
430 j ivis2 ,ielem_m ,idel_solid,elem_linked_to_segment,
431 k nin25 ,flag_elem_inter25 )
432
433
434
435 gapmx=sqrt(gapmx)
436 gapmx=
min(gapmx,gapmax_m)
437
438
439
440 IF(gap<=zero)THEN
441 IF(ndx/=0)THEN
442 gapmin = gapmn
443 gapmin =
min(half*gapmx,gapmin)
444 ELSE
445
446 gapmin = zero
447 ENDIF
448
449 ELSE
450 gapmin = gap
451 ENDIF
452
453 gapmx=zero
454 gapmn=ep30
455 DO i=1,nrt
456 gapmx=
max(gapmx,gap_m(i))
457 gapmn=
min(gapmn,gap_m(i))
458 END DO
459 IF(ipri>=1) THEN
460 IF(gap<=zero)THEN
461 WRITE(iout,1400)gaps_mn,gaps_mx
462 WRITE(iout,1500)gapmn,gapm_mx
463 END IF
465
466
467 IF( igap == 3) THEN
468 gap =
min(gaps_mx+gapm_mx,gaps_l_mx+gapm_l_mx)
469 ELSE
470 gap = gaps_mx+gapm_mx
471 END IF
472
473
474
475 DO 610 l=1,nsn
476 stfn(l) = one
477 610 CONTINUE
478
479
480
481 bgapsmx = zero
482 gapinf=ep30
483 DO i = 1, nsn
484 bgapsmx =
max(bgapsmx,gap_s(i))
485 ENDDO
486 DO i = 1, nrt
487
488
489 IF(msegtyp(i)/=0) gapinf =
min(gapinf,gap_m(i))
490 ENDDO
491 gapinf=
max(gapinf,gapmin)
492
493 DO i=1,nrt
494 CALL insol3et(x ,irect ,ixs ,nint ,nels,i ,
495 .
area ,noint ,knod2els,nod2els,ixs10 ,
496 . ixs16,ixs20 ,nnod)
497
498 IF (nnod==10) THEN
499 gap_n(1,i) = three*one_over_8*gap_n(1,i)
500 stf(i) = sixteen*stf(i)
501 ELSEIF (nnod==16) THEN
502 gap_n(1,i) = gap_n(1,i)/4
503 END IF
504 END DO
505 IF (inacti/=0) THEN
507 1 x ,irect ,nrt ,nsn ,nsv ,pen_old,stf )
508 END IF
509
510 IF(intth > 0 .OR. ivis2==-1) THEN
511
512 IF(numelc/=0) THEN
513
514 IF(nadmesh==0)THEN
515 DO i = 1,nsn
516 areas(i) = zero
517 DO j= knod2elc(nsv(i))+1,knod2elc(nsv(i)+1)
518 ie = nod2elc(j)
519 sx1 = x(1,ixc(4,ie)) - x(1,ixc(2,ie))
520 sy1 = x(2,ixc(4,ie)) - x(2,ixc(2,ie))
521 sz1 = x(3,ixc(4,ie)) - x(3,ixc(2,ie))
522 sx2 = x(1,ixc(5
523 sy2 = x(2,ixc(5,ie)) - x(2,ixc(3,ie))
524 sz2 = x(3,ixc(5,ie)) - x(3,ixc(3,ie))
525 sx3 = sy1*sz2 - sz1*sy2
526 sy3 = sz1*sx2 - sx1*sz2
527 sz3 = sx1*sy2 - sy1*sx2
528 areas(i) = areas(i)
529 . + one_over_8*sqrt(sx3*sx3+sy3*sy3+sz3*sz3)
530
531 IF(intth > 0) THEN
532 ieles(i) = ixc(1,ie)
533 ENDIF
534 END DO
535
536 DO j= knod2eltg(nsv(i))+1,knod2eltg(nsv(i)+1)
537 ie = nod2eltg(j)
538 sx1 = x(1,ixtg(3,ie)) - x(1,ixtg(2,ie))
539 sy1 = x(2,ixtg(3,ie)) - x(2,ixtg(2,ie))
540 sz1 = x(3,ixtg(3,ie)) - x(3,ixtg(2,ie))
541 sx2 = x(1,ixtg(4,ie)) - x(1,ixtg(2,ie))
542 sy2 = x(2,ixtg(4,ie)) - x(2,ixtg(2,ie))
543 sz2 = x(3,ixtg(4,ie)) - x(3,ixtg(2,ie))
544 sx3 = sy1*sz2 - sz1*sy2
545 sy3 = sz1*sx2 - sx1*sz2
546 sz3 = sx1*sy2 - sy1*sx2
547 areas(i) = areas(i)
548 . + one_over_6*sqrt(sx3*sx3+sy3*sy3+sz3*sz3)
549
550 IF(intth > 0) THEN
551 ieles(i) = ixtg(1,ie)
552 ENDIF
553 END DO
554 END DO
555 ELSE
556 DO i = 1,nsn
557 areas(i) = zero
558 DO j= knod2elc(nsv(i))+1,knod2elc(nsv(i)+1)
559 ie = nod2elc(j)
560
561 ip = ipartc(ie)
562 nlev =ipart(10,ip)
563 mylev=sh4tree(3,ie)
564 IF(mylev < 0) mylev=-(mylev+1)
565
566 IF(mylev==nlev)THEN
567 sx1 = x(1,ixc(4,ie)) - x(1,ixc(2,ie))
568 sy1 = x(2,ixc(4,ie)) - x(2,ixc(2,ie))
569 sz1 = x(3,ixc(4,ie)) - x(3,ixc(2,ie))
570 sx2 = x(1,ixc(5,ie)) - x(1,ixc(3,ie))
571 sy2 = x(2,ixc(5,ie)) - x(2,ixc(3,ie))
572 sz2 = x(3,ixc(5,ie)) - x
573 sx3 = sy1*sz2 - sz1*sy2
574 sy3 = sz1*sx2 - sx1*sz2
575 sz3 = sx1*sy2 - sy1*sx2
576 areas(i) = areas(i)
577 . + one_over_8*sqrt(sx3*sx3+sy3*sy3+sz3*sz3)
578
579 IF(intth > 0) THEN
580 ieles(i) = ixc(1,ie)
581 ENDIF
582 END IF
583
584 END DO
585
586 DO j= knod2eltg(nsv(i))+1,knod2eltg(nsv(i)+1)
587 ie = nod2eltg(j)
588
589 ip = iparttg(ie)
590 nlev =ipart(10,ip)
591 mylev=sh3tree(3,ie)
592 IF(mylev < 0) mylev=-(mylev+1)
593
594 IF(mylev==nlev)THEN
595 sx1 = x(1,ixtg(3,ie)) - x(1,ixtg(2,ie))
596 sy1 = x(2,ixtg(3,ie)) - x(2,ixtg(2,ie))
597 sz1 = x(3,ixtg(3,ie)) - x(3,ixtg(2,ie))
598 sx2 = x(1,ixtg(4,ie)) - x(1,ixtg(2,ie))
599 sy2 = x(2,ixtg(4,ie)) - x(2,ixtg(2,ie))
600 sz2 = x(3,ixtg(4,ie)) - x(3,ixtg(2,ie))
601 sx3 = sy1*sz2 - sz1*sy2
602 sy3 = sz1*sx2 - sx1*sz2
603 sz3 = sx1*sy2 - sy1*sx2
604 areas(i) = areas(i)
605 . + one_over_6*sqrt(sx3*sx3+sy3*sy3+sz3*sz3)
606
607 IF(intth > 0) THEN
608 ieles(i) = ixtg(1,ie)
609 ENDIF
610 END IF
611
612 END DO
613 END DO
614 END IF
615 ENDIF
616 ENDIF
617
618
619 IF(intth > 0 ) THEN
620
621 IF(ilev /= 3 )THEN
622 IF(numels/=0)THEN
623 DO i = 1,nsn
624 areas(i) = zero
625 DO j= knod2els(nsv(i))+1,knod2els(nsv(i)+1)
626 ie = nod2els(j)
627 inrt = inrtie(ie)
628 IF(inrt/=0)THEN
629 n1=irect(1,inrt)
630 n2=irect(2,inrt)
631 n3=irect(3,inrt)
632 n4=irect(4,inrt)
633
634 IF(n3 /= n4) THEN
635 sx1 = x(1,n3) - x(1,n1)
636 sy1 = x(2,n3) - x(2,n1)
637 sz1 = x(3,n3) - x(3,n1)
638 sx2 = x(1,n4) - x(1,n2)
639 sy2 = x(2,n4) - x(2,n2)
640 sz2 = x(3,n4) - x(3,n2)
641 sx3 = sy1*sz2 - sz1*sy2
642 sy3 = sz1*sx2 - sx1*sz2
643 sz3 = sx1*sy2 - sy1*sx2
644 area = one_over_8*sqrt(sx3*sx3+sy3*sy3+sz3
645 areas(i) = areas(i) +
area
646
647
648 ELSE
649 sx1 = x(1,n2) - x(1,n1)
650 sy1 = x(2,n2) - x(2,n1)
651 sz1 = x(3,n2) - x(3,n1)
652 sx2 = x(1,n3) - x(1,n1)
653 sy2 = x(2,n3) - x(2,n1)
654 sz2 = x(3,n3) - x(3,n1)
655 sx3 = sy1*sz2 - sz1*sy2
656 sy3 = sz1*sx2 - sx1*sz2
657 sz3 = sx1*sy2 - sy1*sx2
658 area = one_over_6*sqrt(sx3*sx3+sy3*sy3+sz3*sz3)
659 areas(i) = areas(i) +
area
660 ENDIF
661 IF(intth > 0) THEN
662 ieles(i) = ixs(1,ie)
663 ENDIF
664 ENDIF
665 END DO
666 ENDDO
667 ENDIF
668 ENDIF
669
670 END IF
671
672 IF(intth > 0)THEN
673 IF(drad==zero)THEN
675 ELSEIF(drad<gap)THEN
676 drad=gap
677 END IF
678 WRITE(iout,2001)drad
679
680 IF(drad>gapmx)THEN
682 . msgtype=msgwarning,
683 . anmode=aninfo_blind_2,
685 . c1=titr,
686 . r1=drad ,
687 . r2=gapmx,
689 END IF
690 END IF
691
692 IF(intth > 0) DEALLOCATE(inrtie)
693
694 DEALLOCATE(tagb)
695
696 RETURN
697 1300 FORMAT(2x,'GAP MIN = ',1pg20.13)
698 1400 FORMAT(2x,'MIN,MAX OF SECONDARY GAP: ',2(1pg20.13))
699 1500 FORMAT(2x,'MIN,MAX OF MAIN GAP: ',2(1pg20.13)/)
700 2001 FORMAT(2x,'Maximum distance for radiation computation = ',
701 . 1pg20.13)
if(complex_arithmetic) id
subroutine i24normns(x, irect, nrt, nsn, nsv, pen_old, stf)
subroutine insol3et(x, irect, ixs, nint, nel, i, area, noint, knod2els, nod2els, ixs10, ixs16, ixs20, nnod)
subroutine i25gapm(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, intth, ieles, ielem, areas, sh4tree, sh3tree, ipart, ipartc, iparttg, thk, thk_part, ixr, itab, bgapsmx, ixs10, msegtyp, ixs16, ixs20, gap_n, gaps1, gaps2, gapmx, gapmn, gapscale, gapmax_m, id, titr, igeo, fillsol, nrtt, pm_stack, iworksh, intfric, tagprt_fric, ipartfrics, ipartfricm, iparts, intbuf_fric_tab, ipartsm, inrtie, ivis2, ielem_m, idel_solid, elem_linked_to_segment, nin25, flag_elem_inter25)
subroutine i25bord(nrtm, irect, tagb)