43
44
45
48#ifdef WITH_ASSERT
50#endif
51
52
53
54#include "implicit_f.inc"
55#include "comlock.inc"
56
57
58
59#include "mvsiz_p.inc"
60#include "assert.inc"
61#include "i25edge_c.inc"
62
63
64
65 INTEGER, INTENT(IN) :: S_STFE
66 INTEGER IRECT(4,*),CAND_M(*), CAND_S(*), IFPEN(*),
67 . I_STOK, NIN,IGAP ,ITASK, COUNT_REMSLVE(*),
68 . IEDGE, NEDGE, LEDGE(NLEDGE,*), MVOISIN(4,*), NSV(*), NRTM, IGAP0,IFQ
69 my_real ,
INTENT(IN) :: dgapload ,drad
71 . x(3,*),gap_m(*),v(3,*),stf(*),gap_m_l(*), gape(*), gap_e_l(*),
72 . stfe(s_stfe), cand_fx(4,*),cand_fy(4,*),cand_fz(4,*)
73
74
75
76
77#include "task_c.inc"
78#include "com01_c.inc"
79#include "param_c.inc"
80#include "parit_c.inc"
81
82
83
84 INTEGER I , L, M, E, IE, JE, NN1, NN2, IL, JL, I1, I2, SOL_EDGE, SH_EDGE,
85 . NRTMFT, NRTMLT
87 . xi,yi,zi,x1s,x2s,y1s,y2s,z1s,z2s,
88 . x1,x2,x3,x4,
89 . y1,y2,y3,y4,
90 . z1,z2,z3,z4,
91 . x5,x6,x7,x8,
92 . y5,y6,y7,y8,
93 . z5,z6,z7,z8,
94 . xmins,xmaxs,ymins,ymaxs,zmins,zmaxs,
95 . xminm,xmaxm,yminm,ymaxm,zminm,zmaxm,
96 . xminm_1,xmaxm_1,yminm_1,ymaxm_1,zminm_1,zmaxm_1,
97 . xminm_2,xmaxm_2,yminm_2,ymaxm_2,zminm_2,zmaxm_2,dxm,dym,dzm,
98 . v12,v22,v32,v42,vv,gapvd,s
99 INTEGER MSEG,CT
101 . gapv(mvsiz),dtti(mvsiz)
102 INTEGER LIST(MVSIZ), LISTI(MVSIZ)
103 INTEGER IS,JS,LS,NLS,NLT,NSEG,NLF,II,NLS2,NLSAV
104 INTEGER N1(MVSIZ),N2(MVSIZ),M1(MVSIZ),M2(MVSIZ)
105 INTEGER SG, FIRST, LAST,COUNT_CAND
106 INTEGER, DIMENSION(:),ALLOCATABLE :: TAGM
108 . DIMENSION(:,:),ALLOCATABLE :: boxm
109 SAVE tagm,boxm
110 INTEGER :: IDS(4)
111 INTEGER :: J
112 INTEGER :: MY_SIZE
113 INTEGER, DIMENSION(:), ALLOCATABLE :: LIST_REAL_CANDIDATE
114
115
116 sol_edge=iedge/10
117 sh_edge =iedge-10*sol_edge
118
119 count_cand = 0
120 ct = 0
121 mseg = nvsiz
122 first = 1 + i_stok*itask / nthread
123 last = i_stok*(itask+1) / nthread
124 my_size = last - first + 1
125 ALLOCATE( list_real_candidate(my_size) )
126
127 IF(sol_edge/=0)THEN
128
129 IF(itask==0)THEN
130 ALLOCATE(tagm(nrtm),boxm(6,nrtm))
131 tagm(1:nrtm)=0
132 END IF
133
135
136 DO i=first,last
137 l = cand_m(i)
138 IF(stf(l)/=zero)tagm(l)=1
139 END DO
140
142
143 nrtmft=1 + nrtm*itask / nthread
144 nrtmlt=nrtm*(itask+1) / nthread
145
146 DO l=nrtmft,nrtmlt
147
148 boxm(1,l)= ep30
149 boxm(2,l)=-ep30
150 boxm(3,l)= ep30
151 boxm(4,l)=-ep30
152 boxm(5,l)= ep30
153 boxm(6,l)=-ep30
154
155 IF(tagm(l)/=0)THEN
156
157 x1=x(1,irect(1,l))
158 y1=x(2,irect(1,l))
159 z1=x(3,irect(1,l))
160 x2=x(1,irect(2,l))
161 y2=x(2,irect(2,l))
162 z2=x(3,irect(2,l))
163 x3=x(1,irect(3,l))
164 y3=x(2,irect(3,l))
165 z3=x(3,irect(3,l))
166 x4=x(1,irect(4,l))
167 y4=x(2,irect(4,l))
168 z4=x(3,irect(4,l))
169
170 xminm =
min(x1,x2,x3,x4)
171 xmaxm =
max(x1,x2,x3,x4)
172 dxm = em02*(xmaxm-xminm)
173 xminm = xminm-dxm
174 xmaxm = xmaxm+dxm
175
176 yminm =
min(y1,y2,y3,y4)
177 ymaxm =
max(y1,y2,y3,y4)
178 dym = em02*(ymaxm-yminm)
179 yminm = yminm-dym
180 ymaxm = ymaxm+dym
181
182 zminm =
min(z1,z2,z3,z4)
183 zmaxm =
max(z1,z2,z3,z4)
184 dzm = em02*(zmaxm-zminm)
185 zminm = zminm-dzm
186 zmaxm = zmaxm+dzm
187
188 boxm(1,l)=xminm
189 boxm(2,l)=xmaxm
190 boxm(3,l)=yminm
191 boxm(4,l)=ymaxm
192 boxm(5,l)=zminm
193 boxm(6,l)=zmaxm
194
195 END IF
196 END DO
197
199
200 END IF
201
202 js = first-1
203 DO sg = first,last,mseg
204 nseg =
min(mseg,last-js)
205
206
207
208 IF(nspmd>1) THEN
209
210
211
212 nls = 0
213 nls2 = nseg+1
214 DO is = 1, nseg
215 i=js+is
216 IF(cand_s(i)<=nedge)THEN
217
218 IF(sh_edge==1.AND.
219 . ledge(7,cand_s(i))/=1.AND.
220 . ledge(3,cand_s(i))/=0) cycle
221 nls=nls+1
222 listi(nls)=is
223
224#ifdef WITH_ASSERT
225
230 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,i)
231#endif
232
233 ELSE
234 IF(sh_edge==1.AND.
235 .
ledge_fie(nin)%P(e_type,cand_s(i)-nedge)/=1.AND.
236 .
ledge_fie(nin)%P(e_right_seg,cand_s(i)-nedge)/=0) cycle
237 nls2=nls2-1
238 assert(is <= mvsiz)
239 assert(is > 0)
240 listi(nls2) = is
241#ifdef WITH_ASSERT
242
248#endif
249 ENDIF
250 ENDDO
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268 ELSE
269 nls = 0
270
271 DO is=1,nseg
272 i=js+is
273 IF(sh_edge==1.AND.
274 . ledge(7,cand_s(i))/=1.AND.
275 . ledge(3,cand_s(i))/=0) cycle
276
277
278#ifdef WITH_ASSERT
283 debug_e2e(
int_checksum(ids,4,1)==d_em.AND.ledge(8,cand_s(i)) == d_es,i)
284#endif
285
286 nls=nls+1
287 listi(nls)=is
288 ENDDO
289 ENDIF
290
291
292
293#include "vectorize.inc"
294 DO ls = 1, nls
295 is = listi(ls)
296 i=js+is
297 ie=cand_m(i)
298 je=cand_s(i)
299 gapv(is)=gape(je)
300 IF(sh_edge /= 0 .AND. igap0 /= 0) gapv(is
301 IF(igap==3)
302 . gapv(is)=
min(gapv(is),gap_m_l(ie)+gap_e_l(je))
303 gapv(is)=
max(gapv(is)+dgapload,drad)
304 ENDDO
305
306
307 nlf = 1
308 nlt = nls
309 nls = 0
310
311 DO ls = nlf, nlt
312 is = listi(ls)
313 i = js + is
314
315
316
317 l = ledge(1,cand_s(i))
318 s = zero
319#ifdef WITH_ASSERT
324 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,l)
325 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,ledge(ledge_weight,cand_s(i)))
326#endif
327
328 IF( l > 0 ) THEN
329 s = stfe(cand_s(i))
330 ELSEIF (l < 0) THEN
331
332
333
334 s = one
335
336 ENDIF
337
338#ifdef WITH_ASSERT
339 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,s)
340#endif
341
342 IF (s/=zero) THEN
343 n1(is)= ledge(5,cand_s(i))
344 n2(is)= ledge(6,cand_s(i))
345 z1s=x(3,n1(is))
346 z2s=x(3,n2(is))
347 gapvd = gapv(is)
348 zmins =
min(z1s,z2s)-gapvd
349 zmaxs =
max(z1s,z2s)+gapvd
350 zminm = boxm(5,cand_m(i))
351 zmaxm = boxm(6,cand_m(i))
352 zminm = zminm-gapvd
353 zmaxm = zmaxm+gapvd
354#ifdef WITH_ASSERT
359 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,zmaxs)
360 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,zmins)
361 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,zmaxm)
362 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,zminm)
363#endif
364
365 IF (zmaxs>=zminm.AND.zmaxm>=zmins) THEN
366 nls=nls+1
367 list(nls)=is
368 ENDIF
369 ENDIF
370 ENDDO
371
372 nlt=nls
373 nls=0
374
375 DO ls=nlf,nlt
376 is=list(ls)
377 i=js+is
378 y1s=x(2,n1(is))
379 y2s=x(2,n2(is))
380 gapvd = gapv(is)
381 ymins =
min(y1s,y2s)-gapvd
382 ymaxs =
max(y1s,y2s)+gapvd
383 yminm = boxm(3,cand_m(i))
384 ymaxm = boxm(4,cand_m(i))
385 yminm = yminm-gapvd
386 ymaxm = ymaxm+gapvd
387#ifdef WITH_ASSERT
392 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,ymaxs)
393 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,ymins)
394 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,ymaxm)
395 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,yminm)
396#endif
397
398 IF (ymaxs>=yminm.AND.ymaxm>=ymins) THEN
399 nls=nls+1
400 list(nls)=is
401 ENDIF
402 ENDDO
403
404 nlt = nls
405 nls=0
406
407 DO ls=nlf,nlt
408 is=list(ls)
409 i=js+is
410 x1s=x(1,n1(is))
411 x2s=x(1,n2(is))
412 gapvd = gapv(is)
413 xmins =
min(x1s,x2s)-gapvd
414 xmaxs =
max(x1s,x2s)+gapvd
415 xminm = boxm(1,cand_m(i))
416 xmaxm = boxm(2,cand_m(i))
417 xminm = xminm-gapvd
418 xmaxm = xmaxm+gapvd
419#ifdef WITH_ASSERT
424 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,xmaxs)
425 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,xmins)
426 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,xmaxm)
427 debug_e2e(
int_checksum(ids,4,1)==d_em .AND. ledge(8,cand_s(i)) == d_es,xminm)
428#endif
429
430 IF (xmaxs>=xminm.AND.xmaxm>=xmins) THEN
431 cand_s(i) = -cand_s(i)
432 count_cand = count_cand+1
433 list_real_candidate(count_cand) = i
434 ENDIF
435 ENDDO
436
437 IF(nspmd>1)THEN
438 nlf = nls2
439 nlt = nseg
440
441 DO ls = nlf, nlt
442 is = listi(ls)
443 i=js+is
444 ie=cand_m(i)
445 gapv(is)=
gapfie(nin)%P(cand_s(i)-nedge)
446 IF(sh_edge /= 0 .AND. igap0 /= 0) gapv(is)=two*gapv(is)
447
448 IF(igap==3)
449 . gapv(is)=
min(gapv(is),
gape_l_fie(nin)%P(cand_s(i)-nedge)+gap_m_l(ie))
450 gapv(is)=
max(gapv(is)+dgapload,drad)
451 ENDDO
452
453 nls=0
454
455 DO ls = nlf, nlt
456
457 is = listi(ls)
458 i=js+is
459 ii = cand_s(i)-nedge
460#ifdef WITH_ASSERT
466#endif
467
468 IF (
stifie(nin)%P(ii)/=zero)
THEN
469 nn1 = 2*(ii-1)+1
470 nn2 = 2*ii
471 z1s=
xfie(nin)%P(3,nn1)
472 z2s=
xfie(nin)%P(3,nn2)
473
474
475 gapvd = gapv(is)
476 zmins =
min(z1s,z2s)-gapvd
477 zmaxs =
max(z1s,z2s)+gapvd
478 zminm = boxm(5,cand_m(i))
479 zmaxm = boxm(6,cand_m(i))
480 zminm = zminm-gapvd
481 zmaxm = zmaxm+gapvd
482#ifdef WITH_ASSERT
487 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,zmaxs)
488 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,zmins)
489 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,zmaxm)
490 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,zminm)
491#endif
492
493 IF (zmaxs>=zminm.AND.zmaxm>=zmins) THEN
494 nls=nls+1
495 list(nls)=is
496 ENDIF
497
498 ENDIF
499 ENDDO
500
501 nlf=1
502 nlt=nls
503 nls=0
504
505 DO ls=nlf,nlt
506 is=list(ls)
507 i=js+is
508 ii = cand_s(i)-nedge
509 nn1 = 2*(ii-1)+1
510 nn2 = 2*ii
511 y1s=
xfie(nin)%P(2,nn1)
512 y2s=
xfie(nin)%P(2,nn2)
513
514
515 gapvd = gapv(is)
516 ymins =
min(y1s,y2s)-gapvd
517 ymaxs =
max(y1s,y2s)+gapvd
518 yminm = boxm(3,cand_m(i))
519 ymaxm = boxm(4,cand_m(i))
520 yminm = yminm-gapvd
521 ymaxm = ymaxm+gapvd
522
523#ifdef WITH_ASSERT
528 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,ymaxs)
529 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,ymins)
530 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,ymaxm)
531 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,yminm)
532#endif
533
534 IF (ymaxs>=yminm.AND.ymaxm>=ymins) THEN
535 nls=nls+1
536 list(nls)=is
537 ENDIF
538 ENDDO
539
540 DO ls=nlf,nls
541 is=list(ls)
542 i=js+is
543 ii = cand_s(i)-nedge
544 nn1 = 2*(ii-1)+1
545 nn2 = 2*ii
546 x1s=
xfie(nin)%P(1,nn1)
547 x2s=
xfie(nin)%P(1,nn2)
548 gapvd = gapv(is)
549 xmins =
min(x1s,x2s)-gapvd
550 xmaxs =
max(x1s,x2s)+gapvd
551 xminm = boxm(1,cand_m(i))
552 xmaxm = boxm(2,cand_m(i))
553 xminm = xminm-gapvd
554 xmaxm = xmaxm+gapvd
555#ifdef WITH_ASSERT
560 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,xmaxs)
561 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,xmins)
562 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,xmaxm)
563 debug_e2e(
int_checksum(ids,4,1)==d_em .AND.
ledge_fie(nin)%P(e_global_id,cand_s(i)-nedge) == d_es,xminm)
564#endif
565
566 IF (xmaxs>=xminm.AND.xmaxm>=xmins) THEN
567
568 cand_s(i) = -cand_s(i)
569 count_cand = count_cand+1
570 ct = ct+1
571 list_real_candidate(count_cand) = i
572
573 ENDIF
574 ENDDO
576 END IF
577 js = js + nseg
578 ENDDO
579 IF (ifq > 0) THEN
580#include "vectorize.inc"
581 DO j=1,count_cand
582 i = list_real_candidate(j)
583 IF(ifpen(i) == 0 ) THEN
584 cand_fx(1:4,i) = zero
585 cand_fy(1:4,i) = zero
586 cand_fz(1:4,i) = zero
587 ENDIF
588 ENDDO
589 DO i=first,last
590 ifpen(i) = 0
591 ENDDO
592 ENDIF
593
594#include "lockon.inc"
595 lskyi_count=lskyi_count+count_cand*5
596 count_remslve(nin)=count_remslve(nin)+ct
597#include "lockoff.inc"
598
599
600
601 IF(sol_edge/=0)THEN
602
604
605 IF(itask==0)DEALLOCATE(tagm,boxm)
606
607 END IF
608
609 DEALLOCATE( list_real_candidate )
610
611 RETURN
integer, dimension(:), allocatable itab_debug
User Node Identifiers.
pure integer function int_checksum(a, siz1, siz2)
type(real_pointer), dimension(:), allocatable gape_l_fie
type(int_pointer2), dimension(:), allocatable ledge_fie
type(real_pointer), dimension(:), allocatable gapfie
type(real_pointer2), dimension(:), allocatable xfie
type(real_pointer), dimension(:), allocatable stifie