COSMOS v7.655  COSMOSv7655
(AirShowerMC)
smashSkelTrial.f
Go to the documentation of this file.
1 #if defined (KEKB) || defined (KEKA)
2 #define AVOIDFOOL
3 #endif
4  implicit none
5 ! This version runs very quick with torelable accuracy : i.e,
6 ! each skeleton will get almost the same sum of energy and the number of particles
7 ! (example of energy sum list for 8000 cpu's is in Trial.rsl)
8 !
9 !
10 ! We smash the skeleton into NCPU skeeltons; but flesh (MCPU+MARGIN) skeletons
11 ! and modify the fleshed one by multiplying a factor NCPU/MCPU
12 ! to the total number of particles.
13 ! We select (MCPU+MARGIN) skeletons among NCPU skeletons randomly.
14 !
15 !
16 ! read skelton data and store each children as a complete
17 ! track so that each can be put to stack area as incidnet
18 ! particle.
19 ! smashed skeleton data format
20 ! Assume ncpu cpu's; For each cpu, smashed skeleton files will be
21 !
22 ! skeleton001
23 ! cumnum, num, ir, Zfirst
24 ! Np
25 ! observed ptcles 1
26 ! observed ptcles 2
27 !
28 ! observed ptcles Np
29 ! nlowp
30 ! track-1
31 ! track-2
32 ! ...
33 ! track-nlowp
34 ! other skeleton file( skeleton002,...)
35 ! cumnum, num, ir, Zfirst
36 ! 0
37 ! nlowp
38 ! track-1
39 ! track-2
40 ! ...
41 ! track-nlowp
42 ! ....
43 !
44 #include "Ztrack.h"
45 #include "Zearth.h"
46  include "../../SkelFlesh/Zprivate.h"
47  include "Zprivate2.h"
48 
49 
50  type(child):: cc
51  integer icon
52  integer klena
53  integer i, nlow, cumnum, num, ir(2)
54  integer ii
55  type(track):: Zfirst
56  character*120 outdir
57  character*120 skelfilebase
58  character*100 basename
59  character*100 filename
60  character*100 input
61  character*100 hostlist, thinhostlist
62  character*15 field(3)
63  integer n, j, k, nr, ll, kgetenv2
64 
65  hostlist = ' '
66  thinhostlist = ' '
67 
68  ll = kgetenv2("NCPU", msg)
69  read( msg(1:ll), *) ncpu
70  ll = kgetenv2("MCPU", msg)
71  read( msg(1:ll), *) mcpu
72  ll = kgetenv2("MARGIN", msg)
73  read( msg(1:ll), *) margin
74 
75 
76  ll = kgetenv2("SKELETON", msg)
77  skelfilebase=msg(1:ll)
78  ll = kgetenv2("SMSKELDIR", msg)
79  outdir = msg(1:ll)
80  ll = kgetenv2("SKELNAME", msg)
81  basename= msg(1:ll)
82  ll = kgetenv2("HOSTLIST", msg)
83  if(ll .gt. 0) hostlist = msg(1:ll)
84 
85  ll = kgetenv2("THINHOSTLIST", msg)
86  if(ll .gt. 0) thinhostlist = msg(1:ll)
87 
88 ! binary open
89  call copenfw2(11, skelfilebase, 2, icon)
90  if(icon .ne. 1) then
91  write(msg,*) skelfilebase(1:klena(skelfilebase)),
92  * ' could not be opened properly'
93  call cerrormsg(msg, 0)
94  endif
95  write(msg,*) "# of cpu's=",ncpu, mcpu
96  call cerrormsg(msg, 1)
97  if(ncpu .lt. 1 .or. ncpu .gt. maxcpu) then
98  call cerrormsg("# of cpu's > MaxCPU <1 ",0)
99  endif
100 
101 ! open output smashed skeleton files
102  k = klena(outdir)
103  if( outdir(k:k) .ne. '/') then
104  k = k + 1
105  outdir(k:k)= '/'
106  endif
107  write(msg, '(a,a)') 'output directory is ',
108  * outdir(1:k)
109  call cerrormsg(msg, 1)
110  write(msg,*) ncpu,
111  * ' files will be created there as '//
112  * basename(1:klena(basename))//'0001 etc'
113  call cerrormsg(msg, 1)
114 
115 !
116 
117  if(hostlist .ne. ' ') then
118  call copenf(12, hostlist, icon)
119  if(icon .ne. 0 ) then
120  call cerrormsg(hostlist, 1)
121  call cerrormsg(' could not be opened', 0)
122  endif
123  else
124  write(0,*) ' hostlist not given'
125  stop 1234
126  endif
127 
128  if( mcpu .le. ncpu ) then
129  if( thinhostlist .ne. ' ' ) then
130  call copenf(13, thinhostlist, icon)
131  if(icon .ne. 0 ) then
132  call cerrormsg(thinhostlist, 1)
133  call cerrormsg(' could not be opened', 0)
134  endif
135  else
136  write(0,*) ' thinhostlist not given'
137  stop 1234
138  endif
139  else
140  write(0,*) ' Mcpu =', mcpu, ' > Ncpu=', ncpu
141  stop 1234
142  endif
143 
144  do i = 1, ncpu
145  read(12, '(a)') input
146 ! input may be like: 1 hosta 2.5
147  field(1) = ' '
148  field(2) = ' '
149  field(3) = ' '
150  call ksplit(input, 30, 3, field, nr)
151  read(field(1), '(i6)' ) numba(i)
152  if( numba(i) .gt. ncpu .or. numba(i) .lt. 1 ) then
153  write(0,*) i, '-th line has ivalid number=',
154  * numba(i), ' in Hosts'
155  stop 0000
156  endif
157  if(nr .le. 2) then
158  cpupw(i) = 1.0
159  else
160  read(field(3), * ) cpupw(i)
161  endif
162  enddo
163  close(12)
164 
165  if(mcpu .le. ncpu) then
166  do i = 1, mcpu+margin
167  read(13, '(a)') input
168 ! input may be like: 1 hosta 2.5
169  field(1) = ' '
170  field(2) = ' '
171  field(3) = ' '
172  call ksplit(input, 30, 3, field, nr)
173  read(field(1), '(i6)' ) ii
174  if( ii .gt. ncpu .or. ii .lt. 1 ) then
175  write(0,*) i, '-th line has ivalid number=',
176  * ii, ' in ThinHosts'
177  stop 0000
178  endif
179  numba(ii) = -ii
180  enddo
181  close(13)
182  endif
183 
184  do i = 1, ncpu
185  if( numba(i) .lt. 0 ) then
186  write(filename,'(a,i5.5)')
187  * basename(1:klena(basename)), i
188  skelfile(i) = outdir(1:klena(outdir))//filename
189 ! We don't open files here; too many files
190 ! might not be opened simultaneously.
191 ! call copenfw2(basefn+i, skelefile, 2, icon)
192 ! if(icon .ne. 0) then
193 ! call cerrorMsg(skelfile(i), 1)
194 ! call cerrorMsg('could not be opened properly',1)
195 ! call cerrorMsg('maybe they already exist', 0)
196  endif
197  enddo
198 
199 
200 ! ------------
201 
202 
203  do while(.true.)
204  read(11, end=100) cumnum, num, ir,
205 #if defined (AVOIDFOOL)
206 #include "ZavoidUnionMap.h"
207 #else
208  * zfirst
209 #endif
210  do i = 1, ncpu
211  if( numba(i) .lt. 0 ) then
212 ! open one file at a time and
213 ! if possible.
214 #if defined (AVOIDFOOL)
215  open(basefn+i, file=skelfile(i), position="append",
216 #else
217  open(basefn+i, file=skelfile(i), access="append" ,
218 #endif
219  * form="unformatted", iostat=icon)
220  if(icon .eq. 0) then
221  write(basefn+i) cumnum, num, ir,
222 #if defined (AVOIDFOOL)
223 #include "ZavoidUnionMap.h"
224 #else
225  * zfirst
226 #endif
227 
228  else
229  write(0,*) skelfile(i), " could not be opened"
230  stop 0000
231  endif
232  close(basefn+i)
233  endif
234  enddo
235 
236  read(11) np
237  call cerrormsg('------------', 1)
238  write(msg, *) np, ' ptcls are observed ones in skeleton'
239  call cerrormsg(msg, 1)
240  if(np .gt. maxob) then
241  call cerrormsg(
242  * 'It is too large; enlarge Maxob', 0)
243  endif
244 
245  do i = 1, np
246  read(11) oo(i)
247  enddo
248  nlow = 1
249  ctc=0
250  do while (nlow .ge. 0)
251  read(11) nlow, pp
252 ! nlow = 0, if pp.asflag=-1.
253  do i = 1, nlow
254  read(11) cc
255  if(ctc .lt. maxp) then
256  ctc = ctc + 1
257  call movetrack(cc, ct(ctc) )
258  else
259  call cerrormsg(
260  * 'too many particles in skeleton',1)
261  call cerrormsg(
262  * 'Enlarge Maxp in Zprivate2.h', 0)
263  endif
264  enddo
265  enddo
266 
267  write(msg,*)
268  * '# of total ptcls at flesh=',ctc
269  call cerrormsg(msg, 1)
270 
271 ! 1 event data is ready now in oo and ct.
272 ! distribute particles to ncpu
273 ! first sort ct by energy
274 !///////////
275  write(0,*) ' sort by energy starts'
276  call sortbyerg
277  write(0,*) ' sort by energy ended'
278 !/////////////////
279 ! deploy particles to Ncpu so that
280 ! sum energy on each cpu is roughly the same
281  if(ctc .lt. ncpu) then
282  n = ctc
283  write(msg, *) '# of ptcls < Ncpu'
284  call cerrormsg(msg, 1)
285  else
286  n = ncpu
287  endif
288  write(0,*) ' distribute particles to', n, ' cpus'
289  call distribute( n )
290 
291  write(0,*) ' starts to write sub skeletons'
292  call memoforcpu( n )
293 
294  call issuemsg( ncpu )
295  enddo
296 
297  100 continue
298  call cerrormsg('all events have been smashed',1)
299 ! do i = 1, Ncpu
300 ! close(basefn+i)
301 ! enddo
302 
303  end
304 ! ----------------------------
305  subroutine distribute( n )
306  implicit none
307 #include "Ztrack.h"
308  include "../../SkelFlesh/Zprivate.h"
309  include "Zprivate2.h"
310  integer i, k
311  integer n, j
312  logical bigtosmall
313 
314 
315  do i = 1, ncpu
316  sumergi(i)= 0.
317  sumergw(i) = 0.
318  noncpu(i) = 0
319  enddo
320  do i = 1, n
321 ! max energy ptcl for i-th cpu
322  sumergi(i) = erg(idx(i))
323  sumergw(i) = erg(idx(i)) / cpupw(i)
324  noncpu(i) = 1
325  idxlist(1, i) = idx(i)
326  idxlocal(i) = i
327  enddo
328 ! if all cpupw =1, next two not needed
329  call kqsortd(sumergw, idxlocal, n)
330  call ksortinv(idxlocal, n)
331 
332 !///////////
333 ! write(0,*) ' top E=',(sumergi(i), i=1, n)
334 ! write(0,*) ' idx=',(idx(i), i=1, n)
335 !////////
336 ! next explanation is for cpupw = 1
337 ! erg idx sumergi idxlocal nOnCpu idxlist
338 ! 1,1
339 ! 1 9 5 30 1 1 5
340 ! 2 1 3 18 2 1 3
341 ! n 3 18 7 15 3 1 7
342 ! 4 5 8
343 ! 5 30 1
344 ! 6 4 4
345 ! 7 15
346 ! 8 13
347 ! .
348 ! .
349 ! . 6
350 ! ctc . 2
351 !
352 ! after j= 4
353 ! sumergi idxlocal nOnCpu idxlist
354 ! 1 2
355 ! 30 1 1 5
356 ! 18 2 1 3
357 ! 28 3 2 7 8
358 ! after j=5
359 ! sumergi idxlocal nOnCpu idxlist
360 ! 1 2
361 ! 30 1 1 5
362 ! 27 3 2 3 1
363 ! 28 2 2 7 8
364 ! after j=6
365 ! sumergi idxlocal nOnCpu idxlist
366 ! 1 2 3
367 ! 30 1 1 5
368 ! 32 3 3 3 1 4
369 ! 28 2 2 7 8
370 !
371  k = n + 1
372  bigtosmall=.true.
373 
374 
375  do j = n+1, ctc
376  if( bigtosmall ) then
377  k = k - 1
378  if( k .eq. 0 ) then
379  bigtosmall = .false.
380  k = 1
381  endif
382  else
383  k = k + 1
384  if( k .gt. n ) then
385  bigtosmall = .true.
386  k =n
387  endif
388  endif
389 
390  noncpu( k ) = noncpu( k ) + 1
391  if( noncpu( k ) .gt. maxptclpercpu ) then
392  write(msg, *)
393  * '# of ptcls on a cpu', k, ' is ', noncpu( k ) ,
394  * ' exceeded limit=', maxptclpercpu
395  call cerrormsg(msg, 1)
396  call cerrormsg('Enlarge MaxPtclPerCpu in Zprivate2.h',0)
397  endif
398  idxlist( noncpu(k), k ) = idx(j)
399  sumergw(k) = sumergw(k) + erg(idx(j))/cpupw(k)
400  sumergi(k) = sumergi(k) + erg(idx(j))
401  enddo
402 
403  end
404 ! *************************
405  subroutine memoforcpu( n )
406  implicit none
407 #include "Ztrack.h"
408  include "../../SkelFlesh/Zprivate.h"
409  include "Zprivate2.h"
410 
411  integer n
412  integer navob, navobc, navobx
413  integer i, j, icon
414  real avob, resob
415  real*8 u
416  integer cpuc
417  type(track)::Zfirst ! name is some reason
418 
419 ! we distribute Np observed ptcls (at skeleton making time)
420 ! almost equally to Mcpu cpu (not to Margin);
421 ! If some hosts fails, observed ones will be lost since
422 ! hosts of Margin have no observed ptcls. This may not have
423 ! any dangour since, observed ptcls will be only at the core
424 ! region and we don't need such region for detector simulation
425 ! number of average ptcls
426 
427  avob = np
428  avob = avob/mcpu
429 ! navobx = max(Np/Ncpu, 1)
430  navobx = np/mcpu
431 ! if( Np .eq. 0 ) navobx = 0
432 
433  resob = avob-navobx ! 0<= resob< 1
434 
435  navobc = 0
436 !/////////////////
437  write(0,*) ' navobx=', navobx, ' resob=',resob
438 !///////////
439  cpuc = 0
440  do i = 1, ncpu
441  if(numba(i) .lt. 0 ) then
442  cpuc = cpuc + 1
443  navob = navobx
444  call rndc(u)
445  if( u .lt. resob) then
446  navob = navobx + 1
447  endif
448  if(navobc+navob .gt. np .or. cpuc .eq. mcpu ) then
449  navob = np - navobc
450  endif
451 #if defined (AVOIDFOOL)
452  open(basefn+i, file=skelfile(i), position="append",
453 #else
454  open(basefn+i, file=skelfile(i), access="append",
455 #endif
456  * form="unformatted", iostat=icon)
457  if(icon .eq. 0) then
458 !/////////////
459  write(0,*) ' cpu ',i, ' obs=',navob
460 !//////////////
461  write(basefn+i) navob
462 !
463 
464  do j = navobc +1, navobc+navob
465  write(basefn+i) oo(j)
466  enddo
467  navobc = navobc + navob
468  else
469  write(0,*) ' skelfile=', skelfile(i), " cannot be opened"
470  stop 11111
471  endif
472 
473 ! *** enddo
474 ! *** do i = 1, Ncpu
475 !cc if(i .eq. 1) then
476 ! for the first skeleton, put observed ptcls
477 !c write(basefn+i) Np
478 !c do j = 1, Np
479 !c write(basefn+1) oo(j)
480 !c enddo
481 !c else
482 !c write(basefn+i) 0
483 !c endif
484  write(basefn+i) noncpu(i)
485  do j = 1, noncpu(i)
486 #if defined (AVOIDFOOL)
487  zfirst =ct( idxlist(j, i) )
488  write(basefn+i)
489 #include "ZavoidUnionMap.h"
490 #else
491  write(basefn+i) ct( idxlist(j, i) )
492 #endif
493  enddo
494  close(basefn+i)
495  endif
496  enddo
497  end
498  subroutine issuemsg( n )
499  implicit none
500 #include "Ztrack.h"
501  include "../../SkelFlesh/Zprivate.h"
502  include "Zprivate2.h"
503 
504  integer n
505  integer i
506 
507  msg = ' cpu# cpuPW Sum E # of ptcls'
508 ! msg = 'cpu# Sum E # of ptcls'
509  call cerrormsg(msg, 1)
510  do i = 1, n
511  write(msg,'(i6, f7.1, g16.7, i9)')
512 ! write(msg,'(i3, g16.7, i9)')
513  * numba(i), cpupw(i), sumergi(i), noncpu(i)
514 ! * i, sumergi(i), nOnCpu(i)
515  call cerrormsg(msg, 1)
516  enddo
517  end
518 
519 
520  subroutine sortbyerg
521  implicit none
522 #include "Ztrack.h"
523  include "../../SkelFlesh/Zprivate.h"
524  include "Zprivate2.h"
525 
526  integer i
527 
528  averg = 0.
529  do i = 1, ctc
530  erg(i) = ct(i).p.fm.p(4)
531  averg = averg + erg(i)
532  enddo
533  call kqsortd(erg, idx, ctc)
534 ! high to low
535  call ksortinv(idx, ctc)
536  if(ctc .gt. 0.) then
537 ! average total energy on 1 cpu
538  averg = averg/ctc * ncpu
539  else
540  call cerrormsg('no child',1)
541  return
542  endif
543  if( erg(idx(ctc) ) .gt. averg*1.1 ) then
544 ! max energy is too large. issue
545 ! warning
546  write(msg,*) 'WARGNING: max E=', erg(idx(i)),
547  * ' is > average total energy for 1 cpu=',
548  * averg
549  call cerrormsg(msg, 1)
550  endif
551  end
552 
553 
554 
555  subroutine movetrack(f, t)
556  implicit none
557 #include "Ztrack.h"
558 #include "Zearth.h"
559  include "../../SkelFlesh/Zprivate.h"
560  include "Zprivate2.h"
561 
562  type(child):: f
563  type(track):: t
564 
565  t.p.code = f.code
566  t.p.subcode = f.subcode
567  t.p.charge = f.charge
568  t.p.fm.p(1) = f.fm(1)
569  t.p.fm.p(2) = f.fm(2)
570  t.p.fm.p(3) = f.fm(3)
571  t.p.fm.p(4) = f.fm(4)
572  t.p.mass = f.mass
573  t.pos.xyz.r(1) = pp.posx
574  t.pos.xyz.r(2) = pp.posy
575  t.pos.xyz.r(3) = pp.posz
576 
577  t.pos.depth = pp.depth
578  t.pos.height = pp.height
579  t.pos.colheight = pp.colheight
580  t.t = pp.atime
581  t.where = pp.where
582  t.pos.radiallen =
583  * eradius + pp.height
584  t.pos.xyz.sys = 'xyz'
585  t.vec.w.sys = 'xyz'
586  t.wgt = 1.0
587  t.asflag = 0
588 ! t.user = pp.user
589  call cresetdirec( t )
590  end
591 
592 
subroutine ksplit(a, m, n, b, nr)
Definition: ksplit.f:2
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz *Zfirst pos *Zfirst pos depth
Definition: ZavoidUnionMap.h:1
subroutine cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
subroutine issuemsg(n)
Definition: smashSkel.f:503
integer function kgetenv2(envname, envresult)
Definition: cgetLoginN.f:77
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz *Zfirst pos *Zfirst pos Zfirst pos *Zfirst pos colheight
Definition: ZavoidUnionMap.h:1
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz r
Definition: ZavoidUnionMap.h:1
nodes i
subroutine movetrack(f, t)
Definition: smashSkel.f:560
latitude latitude this system is used *****************************************************************! type coord sequence union map real z z in m endmap xyz map real ! latitude in deg is to the north ! longitude in deg is to the east *h ! height in m endmap llh map real ! polar angle ! azimuthal angle *radius ! radial distance endmap sph endunion character *sys ! which system xyz
Definition: Zcoord.h:25
Definition: Ztrack.h:44
block data cblkElemag data *AnihiE ! Eposi< 1 TeV, anihilation considered *X0/365.667/, ! radiation length of air in kg/m2 *Ecrit/81.e-3/, ! critical energy of air in GeV *MaxComptonE/1./, ! compton is considered below 1 GeV *MaxPhotoE/1.e-3/, ! above this, PhotoElectric effect neg. *MinPhotoProdE/153.e-3/, ! below 153 MeV, no gp --> hadrons ! scattering const not MeV *Knockon true
Definition: cblkElemag.h:7
averg real * sumergi(MaxCPU)
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz sys
Definition: ZavoidUnionMap.h:1
subroutine rndc(u)
Definition: rnd.f:91
averg real MaxCPU integer idx(Maxp)
subroutine cresetdirec(aTrack)
Definition: cresetDirec.f:5
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
subroutine copenfw2(io, fnin, form, icon)
Definition: copenf.f:205
subroutine kqsortd(A, ORD, N)
Definition: kqsortd.f:23
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz *Zfirst pos *Zfirst pos Zfirst pos *Zfirst pos *Zfirst Zfirst vec w *Zfirst vec w Zfirst vec *Zfirst Zfirst Zfirst asflag
Definition: ZavoidUnionMap.h:1
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
subroutine ksortinv(idx, n)
Definition: ksortinv.f:2
averg real sumergw(MaxCPU)
subroutine distribute(n)
Definition: smashSkel.f:315
subroutine copenf(io, fnin, icon)
Definition: copenf.f:8
subroutine sortbyerg
Definition: smashSkel.f:525
averg real MaxCPU integer idxlocal(MaxCPU) integer numba(MaxCPU) integer ctc
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz *Zfirst pos *Zfirst pos Zfirst pos height
Definition: ZavoidUnionMap.h:1
float erg[maxp]
Definition: Zprivate.h:7
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p charge
Definition: ZavoidUnionMap.h:1
integer function klena(cha)
Definition: klena.f:20
block data cblkElemag data *AnihiE ! Eposi< 1 TeV, anihilation considered *X0/365.667/, ! radiation length of air in kg/m2 *Ecrit/81.e-3/, ! critical energy of air in GeV *MaxComptonE/1./, ! compton is considered below 1 GeV *MaxPhotoE/1.e-3/, ! above this, PhotoElectric effect neg. *MinPhotoProdE/153.e-3/, ! below 153 MeV, no gp --> hadrons ! scattering const not MeV *Knockon ! knockon is considered Obsolete *PhotoProd false
Definition: cblkElemag.h:7
Definition: Zprivate.h:25
Definition: Zpos.h:16
!onst int maxp
Definition: Zprivate.h:3
*Zfirst p fm *Zfirst p mass
Definition: ZavoidUnionMap.h:1
averg real cpupw(MaxCPU) integer nOnCpu(MaxCPU) integer idxlist(MaxPtclPerCpu
subroutine memoforcpu(n)
Definition: smashSkel.f:403
integer n
Definition: Zcinippxc.h:1
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz *Zfirst pos *Zfirst pos Zfirst pos *Zfirst pos *Zfirst Zfirst vec w *Zfirst vec w Zfirst vec *Zfirst wgt
Definition: ZavoidUnionMap.h:1
*Zfirst p fm *Zfirst p Zfirst p Zfirst p subcode
Definition: ZavoidUnionMap.h:1
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz *Zfirst pos radiallen
Definition: ZavoidUnionMap.h:1