COSMOS v7.655  COSMOSv7655
(AirShowerMC)
smashSkelSmallFileNo.f
Go to the documentation of this file.
1  implicit none
2 ! We smash the skeleton into NCPU skeeltons; but flesh (MCPU+MARGIN) skeletons
3 ! and modify the fleshed one by multiplying a factor NCPU/MCPU
4 ! to the total number of particles.
5 ! We select (MCPU+MARGIN) skeletons among NCPU skeletons randomly.
6 !
7 !
8 ! read skelton data and store each children as a complete
9 ! track so that each can be put to stack area as incidnet
10 ! particle.
11 ! smashed skeleton data format
12 ! Assume ncpu cpu's; For each cpu, smashed skeleton files will be
13 !
14 ! skeleton001
15 ! cumnum, num, ir, Zfirst
16 ! Np
17 ! observed ptcles 1
18 ! observed ptcles 2
19 !
20 ! observed ptcles Np
21 ! nlowp
22 ! track-1
23 ! track-2
24 ! ...
25 ! track-nlowp
26 ! other skeleton file( skeleton002,...)
27 ! cumnum, num, ir, Zfirst
28 ! 0
29 ! nlowp
30 ! track-1
31 ! track-2
32 ! ...
33 ! track-nlowp
34 ! ....
35 !
36 #include "Ztrack.h"
37 #include "Zearth.h"
38  include "../../SkelFlesh/Zprivate.h"
39  include "Zprivate2.h"
40 
41 
42  type(child):: cc
43  integer icon
44  integer klena
45  integer i, nlow, cumnum, num, ir(2)
46  type(track):: Zfirst
47  character*120 skelefile, outdir
48  character*100 basename
49  character*100 filename
50  character*100 input
51  character*100 hostlist
52  character*15 field(3)
53  integer n, j, k, nr, ll, kgetenv2
54 
55  hostlist = ' '
56 
57  ll = kgetenv2("NCPU", msg)
58  read( msg(1:ll), *) ncpu
59  ll = kgetenv2("SKELETON", msg)
60  skelefile=msg(1:ll)
61  ll = kgetenv2("SKELDIR", msg)
62  outdir = msg(1:ll)
63  ll = kgetenv2("SKELNAME", msg)
64  basename= msg(1:ll)
65  ll = kgetenv2("HOSTLIST", msg)
66  if(ll .gt. 0) hostlist = msg(1:ll)
67 ! binary open
68  call copenfw2(11, skelefile, 2, icon)
69  if(icon .ne. 1) then
70  write(msg,*) skelefile(1:klena(skelefile)),
71  * ' could not be opened properly'
72  call cerrormsg(msg, 0)
73  endif
74  write(msg,*) "# of cpu's=",ncpu
75  call cerrormsg(msg, 1)
76  if(ncpu .lt. 1 .or. ncpu .gt. maxcpu) then
77  call cerrormsg("# of cpu's > MaxCPU <1 ",0)
78  endif
79 
80 ! open output smashed skeleton files
81  k = klena(outdir)
82  if( outdir(k:k) .ne. '/') then
83  k = k + 1
84  outdir(k:k)= '/'
85  endif
86  write(msg, '(a,a)') 'output directory is ',
87  * outdir(1:k)
88  call cerrormsg(msg, 1)
89  write(msg,*) ncpu,
90  * ' files will be created there as '//
91  * basename(1:klena(basename))//'0001 etc'
92  call cerrormsg(msg, 1)
93 
94 !
95  if(hostlist .ne. ' ') then
96  call copenf(12, hostlist, icon)
97  if(icon .ne. 0 ) then
98  call cerrormsg(hostlist, 1)
99  call cerrormsg(' could not be opened', 0)
100  endif
101  do i = 1, ncpu
102  read(12, '(a)') input
103 ! input may be like: 1 hosta 2.5
104  field(1) = ' '
105  field(2) = ' '
106  field(3) = ' '
107  call ksplit(input, 30, 3, field, nr)
108  read(field(1), '(i5)' ) numba(i)
109  if(nr .le. 2) then
110  cpupw(i) = 1.0
111  else
112  read(field(3), * ) cpupw(i)
113  endif
114  enddo
115  close(12)
116  else
117  write(0,*) ' hostlist not given'
118  stop 1234
119  endif
120 
121  do i = 1, ncpu
122  write(filename,'(a,i5.5)')
123  * basename(1:klena(basename)), numba(i)
124  skelefile=outdir(1:klena(outdir))//filename
125  call copenfw2(basefn+i, skelefile, 2, icon)
126  if(icon .ne. 0) then
127  call cerrormsg(skelefile, 1)
128  call cerrormsg('could not be opened properly',1)
129  call cerrormsg('maybe they already exist', 0)
130  endif
131  enddo
132 
133 
134 ! ------------
135 
136 
137  do while(.true.)
138  read(11, end=100) cumnum, num, ir, zfirst
139  do i = 1, ncpu
140  write(basefn+i) cumnum, num, ir, zfirst
141  enddo
142 
143  read(11) np
144  call cerrormsg('------------', 1)
145  write(msg, *) np, ' ptcls are observed ones in skeleton'
146  call cerrormsg(msg, 1)
147  if(np .gt. maxob) then
148  call cerrormsg(
149  * 'It is too large; enlarge Maxob', 0)
150  endif
151 
152  do i = 1, np
153  read(11) oo(i)
154  enddo
155  nlow = 1
156  ctc=0
157  do while (nlow .ge. 0)
158  read(11) nlow, pp
159 ! nlow = 0, if pp.asflag=-1.
160  do i = 1, nlow
161  read(11) cc
162  if(ctc .lt. maxp) then
163  ctc = ctc + 1
164  call movetrack(cc, ct(ctc) )
165  else
166  call cerrormsg(
167  * 'too many particles in skeleton',1)
168  call cerrormsg(
169  * 'Enlarge Maxp in Zprivate2.h', 0)
170  endif
171  enddo
172  enddo
173 
174  write(msg,*)
175  * '# of total ptcls at flesh=',ctc
176  call cerrormsg(msg, 1)
177 
178 ! 1 event data is ready now in oo and ct.
179 ! distribute particles to ncpu
180 ! first sort ct by energy
181  call sortbyerg
182 ! deploy particles to Ncpu so that
183 ! sum energy on each cpu is roughly the same
184  if(ctc .lt. ncpu) then
185  n = ctc
186  write(msg, *) '# of ptcls < Ncpu'
187  else
188  n = ncpu
189  endif
190 
191  call distribute( n )
192 
193  call memoforcpu( n )
194 
195  call issuemsg( ncpu )
196  enddo
197 
198  100 continue
199  call cerrormsg('all events have been smashed',1)
200  do i = 1, ncpu
201  close(basefn+i)
202  enddo
203 
204  end
205 ! ----------------------------
206  subroutine distribute( n )
207  implicit none
208 #include "Ztrack.h"
209  include "../../SkelFlesh/Zprivate.h"
210  include "Zprivate2.h"
211  integer i, k
212  integer n, j
213 
214  do i = 1, ncpu
215  sumergi(i)= 0.
216  sumergw(i) = 0.
217  noncpu(i) = 0
218  enddo
219  do i = 1, n
220 ! max energy ptcl for i-th cpu
221  sumergi(i) = erg(idx(i))
222  sumergw(i) = erg(idx(i)) / cpupw(i)
223  noncpu(i) = 1
224  idxlist(1, i) = idx(i)
225  idxlocal(i) = i
226  enddo
227 ! if all cpupw =1, next two not needed
228  call kqsortd(sumergw, idxlocal, n)
229  call ksortinv(idxlocal, n)
230 
231 !///////////
232 ! write(0,*) ' top E=',(sumergi(i), i=1, n)
233 ! write(0,*) ' idx=',(idx(i), i=1, n)
234 !////////
235 ! next explanation is for cpupw = 1
236 ! erg idx sumergi idxlocal nOnCpu idxlist
237 ! 1,1
238 ! 1 9 5 30 1 1 5
239 ! 2 1 3 18 2 1 3
240 ! n 3 18 7 15 3 1 7
241 ! 4 5 8
242 ! 5 30 1
243 ! 6 4 4
244 ! 7 15
245 ! 8 13
246 ! .
247 ! .
248 ! . 6
249 ! ctc . 2
250 !
251 ! after j= 4
252 ! sumergi idxlocal nOnCpu idxlist
253 ! 1 2
254 ! 30 1 1 5
255 ! 18 2 1 3
256 ! 28 3 2 7 8
257 ! after j=5
258 ! sumergi idxlocal nOnCpu idxlist
259 ! 1 2
260 ! 30 1 1 5
261 ! 27 3 2 3 1
262 ! 28 2 2 7 8
263 ! after j=6
264 ! sumergi idxlocal nOnCpu idxlist
265 ! 1 2 3
266 ! 30 1 1 5
267 ! 32 3 3 3 1 4
268 ! 28 2 2 7 8
269 !
270  do j = n+1, ctc
271  if(n .ge. 2) then
272  if( sumergw( idxlocal(n) ) .gt.
273  * sumergw( idxlocal(n-1) ) ) then
274  call kqsortd(sumergw, idxlocal, n)
275  call ksortinv(idxlocal, n)
276  endif
277  endif
278  k = idxlocal(n)
279  noncpu( k ) = noncpu( k ) + 1
280  if( noncpu( k ) .gt. maxptclpercpu ) then
281  write(msg, *)
282  * '# of ptcls on a cpu', k, ' exceeded limit=',
283  * maxptclpercpu
284  call cerrormsg(msg, 1)
285  call cerrormsg('Enlarge MaxPtclPerCpu in Zprivate2.h',0)
286  endif
287  idxlist( noncpu(k), k ) = idx(j)
288  sumergw(k) = sumergw(k) + erg(idx(j))/cpupw(k)
289  sumergi(k) = sumergi(k) + erg(idx(j))
290  enddo
291 
292  end
293 ! *************************
294  subroutine memoforcpu( n )
295  implicit none
296 #include "Ztrack.h"
297  include "../../SkelFlesh/Zprivate.h"
298  include "Zprivate2.h"
299 
300  integer n
301  integer navob, navobc
302  integer i, j
303 
304 
305 
306 ! we distribute Np observed ptcls (at skeleton making time)
307 ! almost equally to n cpu;
308 ! number of average ptcls
309 
310 ! navob = max(Np/n, 1)
311  navob = max(np/ncpu, 1)
312  if( np .eq. 0 ) navob = 0
313  navobc = 0
314  do i = 1, ncpu
315  if(navobc+navob .gt. np .or. i .eq. n ) then
316  navob = np - navobc
317  endif
318  write(basefn+i) navob
319  do j = navobc +1, navobc+navob
320 
321  write(basefn+i) oo(j)
322  enddo
323  navobc = navobc + navob
324  enddo
325  do i = 1, ncpu
326 !cc if(i .eq. 1) then
327 ! for the first skeleton, put observed ptcls
328 !c write(basefn+i) Np
329 !c do j = 1, Np
330 !c write(basefn+1) oo(j)
331 !c enddo
332 !c else
333 !c write(basefn+i) 0
334 !c endif
335  write(basefn+i) noncpu(i)
336  do j = 1, noncpu(i)
337  write(basefn+i) ct( idxlist(j, i) )
338  enddo
339  enddo
340  end
341  subroutine issuemsg( n )
342  implicit none
343 #include "Ztrack.h"
344  include "../../SkelFlesh/Zprivate.h"
345  include "Zprivate2.h"
346 
347  integer n
348  integer i
349 
350  msg = ' cpu# cpuPW Sum E # of ptcls'
351 ! msg = 'cpu# Sum E # of ptcls'
352  call cerrormsg(msg, 1)
353  do i = 1, n
354  write(msg,'(i4, f7.1, g16.7, i9)')
355 ! write(msg,'(i3, g16.7, i9)')
356  * i, cpupw(i), sumergi(i), noncpu(i)
357 ! * i, sumergi(i), nOnCpu(i)
358  call cerrormsg(msg, 1)
359  enddo
360  end
361 
362 
363  subroutine sortbyerg
364  implicit none
365 #include "Ztrack.h"
366  include "../../SkelFlesh/Zprivate.h"
367  include "Zprivate2.h"
368 
369  integer i
370 
371  averg = 0.
372  do i = 1, ctc
373  erg(i) = ct(i).p.fm.p(4)
374  averg = averg + erg(i)
375  enddo
376  call kqsortd(erg, idx, ctc)
377 ! high to low
378  call ksortinv(idx, ctc)
379  if(ctc .gt. 0.) then
380 ! average total energy on 1 cpu
381  averg = averg/ctc * ncpu
382  else
383  call cerrormsg('no child',1)
384  return
385  endif
386  if( erg(idx(ctc) ) .gt. averg*1.1 ) then
387 ! max energy is too large. issue
388 ! warning
389  write(msg,*) 'WARGNING: max E=', erg(idx(i)),
390  * ' is > average total energy for 1 cpu=',
391  * averg
392  call cerrormsg(msg, 1)
393  endif
394  end
395 
396 
397 
398  subroutine movetrack(f, t)
399  implicit none
400 #include "Ztrack.h"
401 #include "Zearth.h"
402  include "../../SkelFlesh/Zprivate.h"
403  include "Zprivate2.h"
404 
405  type(child):: f
406  type(track):: t
407 
408  t.p.code = f.code
409  t.p.subcode = f.subcode
410  t.p.charge = f.charge
411  t.p.fm.p(1) = f.fm(1)
412  t.p.fm.p(2) = f.fm(2)
413  t.p.fm.p(3) = f.fm(3)
414  t.p.fm.p(4) = f.fm(4)
415  t.p.mass = f.mass
416  t.pos.xyz.r(1) = pp.posx
417  t.pos.xyz.r(2) = pp.posy
418  t.pos.xyz.r(3) = pp.posz
419 
420  t.pos.depth = pp.depth
421  t.pos.height = pp.height
422  t.pos.colheight = pp.colheight
423  t.t = pp.atime
424  t.where = pp.where
425  t.pos.radiallen =
426  * eradius + pp.height
427  t.pos.xyz.sys = 'xyz'
428  t.vec.w.sys = 'xyz'
429  t.wgt = 1.0
430  t.asflag = 0
431 ! t.user = pp.user
432  call cresetdirec( t )
433  end
434 
435 
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
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
Definition: Zprivate.h:25
!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