231
232
233
236
237
238
239#include "implicit_f.inc"
240
241
242
243#include "param_c.inc"
244#include "com04_c.inc"
245#include "scr17_c.inc"
246#include "remesh_c.inc"
247
248
249
250 INTEGER IPART(LIPART1,*), IPARTC(*)
251
252
253
254
255
256
257
258 INTEGER ID,NP,J10(10),
259 . N,IP,I,J,NLEV,NI,NJ,NK,NL,NN,
260 . K,L,P,Q,QQ,STAT,
261 . LEVEL,NUMELC_LEV,NUMELTG_LEV,
262 . NUMELC_OLD,,
263 . NUMELC_OLD_OLD,NUMELTG_OLD_OLD,
264 . NUMELC_NEW,NUMELTG_NEW,NUMNOD_NEW,
265 . INILEV
266 INTEGER, DIMENSION(:),ALLOCATABLE ::
267 . KNOD2SH, NOD2SH
268 INTEGER, DIMENSION(:,:),ALLOCATABLE :: TAG
270 . angl,xa,xb
271 CHARACTER MESS*40
272 CHARACTER(LEN=NCHARTITLE) :: TITR
273 CHARACTER(LEN=NCHARKEY) :: KEY
274
275 DATA mess /'OPTIONS FOR ADAPTIVE MESHING DEFINITION '/
276
277 IF(iadmstat /= 0)RETURN
278
279
280 numnod_new =numnod0
281 numelc_old =0
282 numelc_new =numelc0
283 numeltg_old=0
284 numeltg_new=numeltg0
285
286 DO 100 level=1,levelmax
287 numelc_old_old=numelc_old
288 numelc_old =numelc_new
289 numeltg_old_old=numeltg_old
290 numeltg_old =numeltg_new
291
292 numelc_lev =numelc_old-numelc_old_old
293 numeltg_lev=numeltg_old-numeltg_old_old
294
295
296
297 ALLOCATE(knod2sh(0:numnod_new),stat=stat)
298 IF(stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
299 . msgtype=msgerror,
300 . c1='KNOD2SH')
301
302 knod2sh=0
303 DO n=numelc_old_old+1,numelc_old
304 DO i=1,4
305 ni=ixc(i+1,n)
306 knod2sh(ni)=knod2sh(ni)+1
307 END DO
308 END DO
309
310 DO n=numeltg_old_old+1,numeltg_old
311 DO i=1,3
312 ni=ixtg(i+1,n)
313 knod2sh(ni)=knod2sh(ni)+1
314 END DO
315 END DO
316
317 DO n=2,numnod_new
318 knod2sh(n)=knod2sh(n)+knod2sh(n-1)
319 END DO
320
321 ALLOCATE(nod2sh(4*numelc_lev+3*numeltg_lev),stat=stat)
322 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
323 . msgtype=msgerror,
324 . c1='NOD2SH')
325
326 DO n=1,numelc_lev
327 nn=numelc_old_old+n
328 DO i=1,4
329 ni=ixc(i+1,nn)-1
330 knod2sh(ni)=knod2sh(ni)+1
331 nod2sh(knod2sh(ni))=n
332 END DO
333 END DO
334
335 DO n=1,numeltg_lev
336 nn=numeltg_old_old+n
337 DO i=1,3
338 ni=ixtg(i+1,nn)-1
339 knod2sh(ni)=knod2sh(ni)+1
340 nod2sh(knod2sh(ni))=numelc_lev+n
341 END DO
342 END DO
343
344 DO n=numnod_new,1,-1
345 knod2sh(n)=knod2sh(n-1)
346 END DO
347 knod2sh(0)=0
348
349
350 ALLOCATE(tag(5,numelc_lev+numeltg_lev),stat=stat)
351 IF (stat /= 0)
CALL ancmsg(msgid=268,anmode=aninfo,
352 . msgtype=msgerror,
353 . c1='TAG')
354 tag=0
355
356 DO n=1,numelc_lev
357 nn=numelc_old_old+n
358 ip =ipartc(nn)
359 nlev=ipart(10,ip)
360 IF(nlev<level) cycle
361 DO i=1,4
362 IF(tag(i,n)==0)THEN
363 ni=ixc(i+1,nn)
364 nj=ixc(mod(i,4)+2,nn)
365
366 numnod_new=numnod_new+1
367 tag(i,n)=numnod_new
368 DO j=1,3
369 x(j,numnod_new)=half*(x(j,ni)+x(j,nj))
370 END DO
371 DO k=knod2sh(ni-1)+1,knod2sh(ni)
372 p=nod2sh(k)
373 IF(p/=n)THEN
374 DO l=knod2sh(nj-1)+1,knod2sh(nj)
375 q=nod2sh(l)
376 IF(q==p)THEN
377 IF(q<=numelc_lev)THEN
378 qq=numelc_old_old+q
379 DO j=1,4
380 nk=ixc(j+1,qq)
381 nl=ixc(mod(j,4)+2,qq)
382
383 IF((nk==ni.AND.
nl==nj).OR.
384 . (
nl==ni.AND.nk==nj))
THEN
385 tag(j,q)=numnod_new
386 END IF
387 END DO
388 ELSE
389 qq=numeltg_old_old+q-numelc_lev
390 DO j=1,3
391 nk=ixtg(j+1,qq)
392 nl=ixtg(mod(j,3)+2,qq)
393
394 IF((nk==ni.AND.
nl==nj).OR.
395 . (
nl==ni.AND.nk==nj))
THEN
396 tag(j,q)=numnod_new
397 END IF
398 END DO
399 END IF
400 END IF
401 END DO
402 END IF
403 END DO
404 END IF
405 END DO
406 END DO
407
408 DO n=1,numelc_lev
409 nn=numelc_old_old+n
410 ip =ipartc(nn)
411 nlev=ipart(10,ip)
412 IF(nlev<level) cycle
413 numnod_new=numnod_new+1
414 tag(5,n)=numnod_new
415 ni=tag(1,n)
416 nj=tag(3,n)
417 nk=tag(2,n)
419 DO j=1,3
420 xa=half*(x(j,ni)+x(j,nj))
421 xb=half*(x(j,nk)+x(j,
nl))
422 x(j,numnod_new)=half*(xa+xb)
423 END DO
424 END DO
425
426 DO n=1,numeltg_lev
427 nn=numeltg_old_old+n
428 ip =iparttg(nn)
429 nlev=ipart(10,ip)
430 IF(nlev<level) cycle
431 DO i=1,3
432 IF(tag(i,n+numelc_lev)==0)THEN
433 ni=ixtg(i+1,nn)
434 nj=ixtg(mod(i,3)+2,nn)
435
436 numnod_new=numnod_new+1
437 tag(i,n+numelc_lev)=numnod_new
438 DO j=1,3
439 x(j,numnod_new)=half*(x(j,ni)+x(j,nj))
440 END DO
441 DO k=knod2sh(ni-1)+1,knod2sh(ni)
442 p=nod2sh(k)
443 IF(p/=n+numelc)THEN
444 DO l=knod2sh(nj-1)+1,knod2sh(nj)
445 q=nod2sh(l)
446 IF(q==p)THEN
447 IF(q<=numelc_lev)THEN
448 qq=numelc_old_old+q
449 DO j=1,4
450 nk=ixc(j+1,qq)
451
452
453 IF((nk==ni.AND.
nl==nj).OR.
454 . (
nl==ni.AND.nk==nj))
THEN
455 tag(j,q)=numnod_new
456 END IF
457 END DO
458 ELSE
459 qq=numeltg_old_old+q-numelc_lev
460 DO j=1,3
461 nk=ixtg(j+1,qq)
462 nl=ixtg(mod(j,3)+2,qq)
463
464 IF((nk==ni.AND.
nl==nj).OR.
465 . (
nl==ni.AND.nk==nj))
THEN
466 tag(j,q)=numnod_new
467 END IF
468 END DO
469 END IF
470 END IF
471 END DO
472 END IF
473 END DO
474 END IF
475 END DO
476 END DO
477
478 numelc_new=numelc_old
479 DO n=1,numelc_lev
480 nn=numelc_old_old+n
481 ip =ipartc(nn)
482 nlev=ipart(10,ip)
483 IF(nlev<level) cycle
484
485 DO j=1,nixc
486 DO i=1,4
487 ixc(j,numelc_new+i)=ixc(j,nn)
488 END DO
489 END DO
490
491 numelc_new=numelc_new+1
492 ixc(2,numelc_new)=ixc(2,nn)
493 ixc(3,numelc_new)=tag(1,n)
494 ixc(4,numelc_new)=tag(5,n)
495 ixc(5,numelc_new)=tag(4,n)
496 ipartc(numelc_new)=ip
497
498 sh4tree(1,numelc_new)=nn
499 sh4tree(2,nn)=numelc_new
500
501
502
503 sh4tree(3,numelc_new)=-(level+1)
504
505 numelc_new=numelc_new+1
506 ixc(2,numelc_new)=tag(1,n)
507 ixc(3,numelc_new)=ixc(3,nn)
508 ixc(4,numelc_new)=tag(2,n)
509 ixc(5,numelc_new)=tag(5,n)
510 ipartc(numelc_new)=ip
511
512 sh4tree(1,numelc_new)=nn
513 sh4tree(3,numelc_new)=-(level+1)
514
515 numelc_new=numelc_new+1
516 ixc(2,numelc_new)=tag(5,n)
517 ixc(3,numelc_new)=tag(2,n)
518 ixc(4,numelc_new)=ixc(4,nn)
519 ixc(5,numelc_new)=tag(3,n)
520 ipartc(numelc_new)=ip
521
522 sh4tree(1,numelc_new)=nn
523 sh4tree(3,numelc_new)=-(level+1)
524
525 numelc_new=numelc_new+1
526 ixc(2,numelc_new)=tag(4,n)
527 ixc(3,numelc_new)=tag(5,n)
528 ixc(4,numelc_new)=tag(3,n)
529 ixc(5,numelc_new)=ixc(5,nn)
530 ipartc(numelc_new)=ip
531
532 sh4tree(1,numelc_new)=nn
533 sh4tree(3,numelc_new)=-(level+1)
534 END DO
535
536 numeltg_new=numeltg_old
537 DO n=1,numeltg_lev
538 nn=numeltg_old_old+n
539 ip =iparttg(nn)
540 nlev=ipart(10,ip)
541 IF(nlev<level) cycle
542
543 DO j=1,nixtg
544 DO i=1,4
545 ixtg(j,numeltg_new+i)=ixtg(j,nn)
546 END DO
547 END DO
548
549 numeltg_new=numeltg_new+1
550 ixtg(2,numeltg_new)= ixtg(2,nn)
551 ixtg(3,numeltg_new)= tag(1,n+numelc_lev)
552 ixtg(4,numeltg_new)= tag(3,n+numelc_lev)
553 iparttg(numeltg_new)=ip
554
555 sh3tree(1,numeltg_new)=nn
556 sh3tree(2,nn)=numeltg_new
557 sh3tree(3,numeltg_new)=-(level+1)
558
559 numeltg_new=numeltg_new+1
560 ixtg(2,numeltg_new)= tag(1,n+numelc_lev)
561 ixtg(3,numeltg_new)= ixtg(3,nn)
562 ixtg(4,numeltg_new)= tag(2,n+numelc_lev)
563 iparttg(numeltg_new)=ip
564
565 sh3tree(1,numeltg_new)=nn
566 sh3tree(3,numeltg_new)=-(level+1)
567
568 numeltg_new=numeltg_new+1
569 ixtg(2,numeltg_new)= tag(3,n+numelc_lev)
570 ixtg(3,numeltg_new)= tag(2,n+numelc_lev)
571 ixtg(4,numeltg_new)= ixtg(4,nn)
572 iparttg(numeltg_new)=ip
573
574 sh3tree(1,numeltg_new)=nn
575 sh3tree(3,numeltg_new)=-(level+1)
576
577 numeltg_new=numeltg_new+1
578 ixtg(2,numeltg_new)= tag(2,n+numelc_lev)
579 ixtg(3,numeltg_new)= tag(3,n+numelc_lev)
580 ixtg(4,numeltg_new)= tag(1,n+numelc_lev)
581 iparttg(numeltg_new)=ip
582
583 sh3tree(1,numeltg_new)=nn
584 sh3tree(3,numeltg_new)=-(level+1)
585 END DO
586
587
588 DEALLOCATE(tag)
589 DEALLOCATE(nod2sh)
590 DEALLOCATE(knod2sh)
591 100 CONTINUE
592
593
594
595 DO n=1,numelc0
597 END DO
598
599 DO n=1,numeltg0
601 END DO
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706 numnod=numnod_new
707
708
709 CALL constit(itab,itabm1,numnod)
710 RETURN
711
713 RETURN
recursive subroutine identson4(level, nn, ixc, sh4tree)
recursive subroutine identson3(level, nn, ixtg, sh3tree)
subroutine constit(itab, itabm1, numnod)
integer, parameter nchartitle
integer, parameter ncharkey
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)
character *2 function nl()