49
50
51
52
53
54
55
56
61
62
63
64#include "implicit_f.inc"
65#include "comlock.inc"
66
67
68
69#include "mvsiz_p.inc"
70
71
72
73#include "com01_c.inc"
74#include "param_c.inc"
75#include "task_c.inc"
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123 INTEGER I_MEM,ESHIFT,NSN,ISZNSNR,NSHEL_T,NIN,ITASK,
124 . MULNSN,NOINT,NSHELR_L,IGAP,NBX,NBY,NBZ,NBRIC,
125 . NSV(*),CAND_B(*),CAND_E(*),RENUM(*),
126 . IRECT(4,*), IXS(NIXS,*),
127 . BUFBRIC(NBRIC),
128 . VOXEL(NBX+2,NBY+2,NBZ+2),(*),NSHEL_L,II_STOK
129
131 . ,TARGET :: x(3,*)
132
134 . bminma(6),cand_p(*), stf(*),stfn(*),
135 . tzinf,marge
136
137 my_real,
DIMENSION(SIZ_XREM, NSHEL_T+1: NSHEL_T+NSHELR_L) ::
138 . xrem
139
140
141
142
143 INTEGER NB_NCN,NB_NCN1,NB_ECN,I,J,K,L,DIR,NB_NC,NB_EC,
144 . N1,N2,N3,N4,NN,NE,NS,NCAND_PROV,J_STOK,II,JJ,TT,
145 . OLDNUM(ISZNSNR), NSNF, NSNL,
146 . PROV_B(2*MVSIZ), PROV_E(2*MVSIZ), LAST_NE,
147 . VOXBND(2*MVSIZ,0:1,1:3)
148
150 . dx,dy,dz,xs,ys,zs,sx,sy
151 . xmin, xmax,ymin,
ymax,zmin, zmax, tz, gapsmx, gapl,
152 . d1x,d1y,d1z,d2x,d2y,d2z,dd1,dd2,d2,a2,gs, point(3),
153 . on1(3),n1n2(3)
154
155 INTEGER IX,IY,IZ,NEXT,M1,M2,M3,M4,M5,M6,M7,M8,
156 . IX1,IY1,IZ1,IX2,IY2,IZ2,IBUG,IBUG2,I_LOC,
157 . BIX1(NBRIC),BIY1(NBRIC),BIZ1(NBRIC),
158 . BIX2(NBRIC),BIY2(NBRIC),BIZ2(NBRIC),
159 . FIRST_ADD, PREV_ADD, LCHAIN_ADD, I_STOK
160
161 INTEGER :: NC, I_STOK_BAK, IPA,IPB
163 . xminb,yminb,zminb,xmaxb,ymaxb,zmaxb,
164 . dxb,dyb,dzb,
165 . aaa, daaa, dmax
166
167 LOGICAL, DIMENSION(NBRIC) :: TAGB
168
169 LOGICAL :: BOOL(NIRECT_L)
170 INTEGER NBCUT, DEJA, ISONSHELL, ISONSH3N
171 INTEGER :: COUNTER, NEDGE, NFACE, NODES8(8), COUNTER_BRICK(NBRIC)
172
173
174
175 INTEGER :: iN1, iN2, iN1a, iN2a, iN1b, iN2b , iN3, iN4
176 INTEGER :: POS, IAD, IB , NBF, NBL
177 INTEGER :: I_12bits, nbits, npqts, pqts(4), SUM, SECTION
178 INTEGER :: I_bits(12), MAX_ADD, IMIN_LOC, IMAX_LOC
179
181 . aeradiag,xx(8),yy(8),zz(8),diag(4)
182
183 CHARACTER*12 :: sectype
184 LOGICAL :: IsSecDouble, IsSTO
185
186 CHARACTER(LEN=1) filenum
187
188 INTEGER ::
189 . MIN_IX_LOC, MIN_IY_LOC, MIN_IZ_LOC,
190 . MAX_IX_LOC, MAX_IY_LOC,
191
192 INTEGER, ALLOCATABLE, DIMENSION(:) :: order, VALUE
193
194 INTEGER R2,MIN2
195
196
197
198
199
200
201
202
203
204
205
207 print *, " i22trivox:entering routine"
208 print *, ""
209 print *, "------------------BRICKS DOMAIN--------------------"
210 print *, " BMINMAL_I22TRIVOX=", bminma(4:6),bminma(1:3)
211 print *, " NBX,NBY,NBZ=", nbx,nby,nbz
212 print *, "---------------------------------------------------"
213 print *, ""
214 print *, ""
215 print *, " |-----------i22trivox.F---------|"
216 print *, " | DOMAIN INFORMATION |"
217 print *, " |-------------------------------|"
218 print *, " MPI =",ispmd +1
219 print *, " NT =",itask+1
220 print *, " NCYCLE =", ncycle
221 print *, " ITASK =", itask
223 print *, " local bricks :", nbric
224 print *, " tableau briques du domaine local :"
225 print *, ixs(11,bufbric(1:nbric))
226 print *, " local faces :",nshel_l
227 print *, " tableau facettes du domaine local :"
229 print *, i,nint(irect_l(1:4, i))
230 END DO
231 print *, " +remotes:"
233 print *, i,irect_l(1:4, i)
234 END DO
235 print *, " |-------------------------------|"
236 print *, ""
237 print *, " |-----i22trivox.F--------|"
238 print *, " | THREAD INFORMATION |"
239 print *, " |------------------------|"
240
241 print *, " cple candidats max : ", mulnsn
242 print *, " ESHIFT=", eshift
243 print *, " |------------------------|"
244 print *, ""
245 end if
247
248
249
250
251
252
253 max_add = mulnsn
254 aaa = zero
255
256
257
258
259
260
261
262 IF(itask == 0)THEN
263
275 END IF
276 IF(itask==nthread-1)THEN
285 END IF
286
288
289
290
291
292
293
294
295 xminb = bminma(4)
296 yminb = bminma(5)
297 zminb = bminma(6)
298 xmaxb = bminma(1)
299 ymaxb = bminma(2)
300 zmaxb = bminma(3)
301 aaa = tzinf
302
303 xminb = xminb - aaa
304 yminb = yminb - aaa
305 zminb = zminb - aaa
306 xmaxb = xmaxb + aaa
307 ymaxb = ymaxb + aaa
308 zmaxb = zmaxb + aaa
309
310 dxb = xmaxb-xminb
311 dyb = ymaxb-yminb
312 dzb = zmaxb-zminb
313
314
315 daaa = ( (bminma(1)-bminma(4))+(bminma(2)-bminma(5))+
316 . (bminma(3)-bminma(6)) ) / three/hundred
317 dmax =
max(
max(dxb,dyb),dzb)
318
319 IF(dxb/dmax<em06)dxb=daaa
320 IF(dyb/dmax<em06)dyb=daaa
321 IF(dzb/dmax<em06)dzb=daaa
322
323
326
327
328
329
330 DO ne=nbf,nbl
331 IF(irect_l(23,ne)==zero)cycle
332 IF(((xmaxe(ne)< xminb).OR.(xmine(ne)>xmaxb)).OR.
333 . ((ymaxe(ne)< yminb).OR.(ymine(ne)>ymaxb)).OR.
334 . ((zmaxe(ne)< zminb).OR.(zmine(ne)>zmaxb)))THEN
335 irect_l(23,ne)=zero
336
337 cycle
338 END IF
339
340
341
342
343 ix1=int(nbx*(irect_l(17,ne)-aaa-xminb)/dxb)
344 iy1=int(nby*(irect_l(18,ne)-aaa-yminb)/dyb)
345 iz1=int(nbz*(irect_l(19,ne)-aaa-zminb)/dzb)
349
350 ix2=int(nbx*(irect_l(20,ne)+aaa-xminb)/dxb)
351 iy2=int(nby*(irect_l(21,ne)+aaa-yminb)/dyb)
352 iz2=int(nbz*(irect_l(22,ne)+aaa-zminb)/dzb)
356 END DO
357
358
359
360
367
368
369
370#include "lockon.inc"
377#include "lockoff.inc"
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417 IF(itask==0)THEN
419 IF(irect_l(23,ne)==zero)cycle
420
422 print *, " traitement shell",nint(irect_l((/1,3/),ne)),
424 print *, " xmin/xmax=", irect_l((/17,20/),ne)
425 print *, " ymin/ymax=", irect_l((/18,21/),ne)
426 print *, " zmin/zmax=", irect_l((/19,22/),ne)
427 end if
428
432 first_add = voxel(ix,iy,iz)
433 IF(first_add == 0)THEN
434
439 ELSE
440
446 ENDIF
449
450
451 max_add = 2 * max_add
456 ENDIF
457 ENDDO
458 ENDDO
459 ENDDO
460 END DO
461 END IF
463
464
466 .print *, " i22trivox:voxel filled"
467
468
469
470
471
472
473
474 nc = 0
475 i_stok = 0
476 last_ne = 0
477 nbf = 1+itask*nbric/nthread
478 nbl = (itask+1)*nbric/nthread
479
480 DO i=nbf,nbl
481
482
483
484
485
486
487
488 ix1=int(nbx*(xmins(i)-xminb)/dxb)
489 iy1=int(nby*(ymins(i)-yminb)/dyb)
490 iz1=int(nbz*(zmins(i)-zminb)/dzb)
491 bix1(i)=
max(1,2+
min(nbx,ix1))
492 biy1(i)=
max(1,2+
min(nby,iy1))
493 biz1(i)=
max(1,2+
min(nbz,iz1))
494
495 ix2=int(nbx*(xmaxs(i)-xminb)/dxb)
496 iy2=int(nby*(ymaxs(i)-yminb)/dyb)
497 iz2=int(nbz*(zmaxs(i)-zminb)/dzb)
498 bix2(i)=
max(1,2+
min(nbx,ix2))
499 biy2(i)=
max(1,2+
min(nby,iy2))
500 biz2(i)=
max(1,2+
min(nbz,iz2))
501
502
503
504
505
506
507
508
509 DO iz = biz1(i),biz2(i)
510 DO iy = biy1(i),biy2(i)
511 DO ix = bix1(i),bix2(i)
512 lchain_add = voxel(ix,iy,iz)
513 DO WHILE(lchain_add /= 0)
515 bool(ne)=.false.
517 ENDDO
518 ENDDO
519 ENDDO
520 ENDDO
521
522 issto = .false.
523
524 DO iz = biz1(i),biz2(i)
525 DO iy = biy1(i),biy2(i)
526 DO ix = bix1(i),bix2(i)
527 lchain_add = voxel(ix,iy,iz)
528 DO WHILE(lchain_add /= 0)
530
531
532 IF(bool(ne))THEN
534 cycle
535 END IF
536 j = ne
537 ns = bufbric(i)
538 xx(1:8) = x(1,ixs(2:9,ns))
539 yy(1:8) = x(2,ixs(2:9,ns))
540 zz(1:8) = x(3,ixs(2:9,ns))
541 diag(1) = sqrt((xx(1)-xx(7))**2 + (yy(1)-yy(7))**2 + (zz(1)-zz(7))**2)
542 diag(2) = sqrt((xx(3)-xx(5))**2 + (yy(3)-yy(5))**2 + (zz(3)-zz(5)
543 diag(3) = sqrt((xx(2)-xx(8))**2 + (yy(2)-yy(8))**2 + (zz(2)-zz(8))**2)
544 diag(4) = sqrt((xx(4)-xx(6))**2 + (yy(4)-yy(6))**2 + (zz(4)-zz(6))**2)
545 aaa = 1.2d00*maxval(diag(1:4),1)
546
547
548 IF( (irect_l(17,ne)-aaa>xmaxs(i)).OR.
549 . (irect_l(20,ne)+aaa<xmins(i)).OR.
550 . (irect_l(18,ne)-aaa>ymaxs(i)).OR.
551 . (irect_l(21,ne)+aaa<ymins(i)).OR.
552 . (irect_l(19,ne)-aaa>zmaxs(i)).OR.
553 . (irect_l(22,ne)+aaa<zmins(i)) ) THEN
555 cycle
556 END IF
557 bool(ne) =.true.
558 i_stok = i_stok + 1
559 prov_b(i_stok) = i
560 prov_e(i_stok) = ne
562 tagb(i) = .true.
563
564 IF( (irect_l(17,ne) >xmaxs(i)).OR.
565 . (irect_l(20,ne) <xmins(i)).OR.
566 . (irect_l(18,ne) >ymaxs(i)).OR.
567 . (irect_l(21,ne) <ymins(i)).OR.
568 . (irect_l(19,ne) >zmaxs(i)).OR.
569 . (irect_l(22,ne) <zmins(i)) ) prov_e(i_stok) = -prov_e(i_stok)
570
571
572
573 IF(i_stok>=nvsiz)THEN
574
575
576
577
579 1 i_stok ,irect ,x , ii_stok, cand_b,
580 2 cand_e ,mulnsn ,noint , marge , i_mem ,
581 3 prov_b ,prov_e ,eshift , itask , nc ,
582 4 ixs ,bufbric ,nbric , issto )
583 i_stok = 0
584 IF(i_mem==2) THEN
586 print *, " i22trivox.F:too much candidates on thread=",
587 . itask+1
588 print *, " i22trivox.F:II_STOK=", ii_stok,mulnsn
589 end if
590 GOTO 1000
592 endif
593
594 ENDDO
595 ENDDO
596 ENDDO
597 ENDDO
598
599
600
601 IF(i_stok/=0)THEN
602
603
605 1 i_stok ,irect ,x , ii_stok ,cand_b,
606 2 cand_e ,mulnsn ,noint , marge ,i_mem ,
607 3 prov_b ,prov_e ,eshift , itask ,nc ,
608 4 ixs ,bufbric ,nbric , issto )
609 i_stok = 0
610 IF(i_mem==2) THEN
611
612
613
614
615
616 GOTO 1000
618 END IF
619
620
621
622
623 IF(issto)THEN
624
625
626#include "lockoff.inc"
627
628 END IF
629
630 END DO
631
632
633
634
635
636
637
638
639
640 1000 CONTINUE
641
643
645 . " i22trivox.F:nb de candidats:" , ii_stok, itask
646
647 IF(itask==0)THEN
648
652 voxel(i,j,k) = 0
653 END DO
654 END DO
655 END DO
656 ENDIF
657
658
659
660
661
662
663 IF(itask == 0)THEN
667 ENDIF
668
669
672 DO ix=1,(nbx+2)
673 DO iy=1,(nby+2)
674 DO iz=1,(nbz+2)
675 if (voxel(ix,iy,iz)/=0) then
676 print *, " i22trivox.F:error raz voxel",voxel(ix,iy,iz)
677 print *, " i22trivox.F:ix,iy,iz=", ix,iy,iz
678 stop
679 end if
680 END DO
681 END DO
682 END DO
683 print *, " i22trivox.F:raz voxel ok."
684 end if
685 if(i_mem==2)then
687 . print *,
688 . " i22trivox.F:returning i22buce (too much candidate)"
689 GOTO 2000
690 end if
692 . print *, " i22trivox.F:fin recherche des candidats, nb=",
693 . ii_stok
694
696 allocate(order(ii_stok) ,value(ii_stok))
697 min2 = minval(abs(cand_e(1:ii_stok)))
698 r2 = maxval(abs(cand_e(1:ii_stok))) - min2
699 DO i=1,ii_stok
700 value(i) = cand_b(i)*(r2+1)+abs(cand_e(i))-min2
701 ENDDO
702 order=0
703
704
705
706
707 print *, " II_STOK=", ii_stok
708 print *, " IXS(11,BUFBRIC(CAND_B)) ) =", ixs(11, bufbric(cand_b(order(1:ii_stok))))
709 print *, " BUFBRIC(CAND_B) =", bufbric(cand_b(order(1:ii_stok)))
710 print *, " CAND_B =", cand_b(order(1:ii_stok))
711 print *, " CAND_E =", cand_e(order(1:ii_stok))
712
713 deallocate(order,VALUE)
714 endif
715
716
717
718
719
720
721 2000 CONTINUE
723
724 RETURN
if(complex_arithmetic) id
subroutine i22sto(j_stok, irect, x, ii_stok, cand_b, cand_e, mulnsn, noint, marge, i_mem, prov_b, prov_e, eshift, itask, nc, ixs, bufbric, nbric, issto)
subroutine ymax(idn, fac, npc, pld, stiffmin, stiffmax, stiffini, stiffavg)
integer, dimension(:), pointer lchain_next
integer, dimension(:), pointer lchain_elem
integer, dimension(:), allocatable eiz2
integer, dimension(:), allocatable eiz1
integer, dimension(:), pointer lchain_last
integer, dimension(:), allocatable eiy2
integer, dimension(:), allocatable eix2
integer, dimension(:), allocatable eix1
integer, dimension(:), allocatable eiy1
integer function, dimension(:), pointer ireallocate(ptr, new_size)