COSMOS v7.655  COSMOSv7655
(AirShowerMC)
timeslice2.f
Go to the documentation of this file.
1  implicit none
2  include "Zprivate2.f"
3 
4  character*120 tracefile
5  integer leng, icon, i, outtype
6  real*4 mint, maxt, dt, t1, t2
7  logical dothin, split
8  integer klena
9 
10  mint = 000.
11  maxt = 20000.
12  dt = 10.
13  pixel = dt
14  open(11, file='input')
15  read(11,*)
16  * tracefile, dir, mint, maxt, dt, pixel, dothin, split,
17  * outtype, mulalpha
18 
19  write(0,*)
20  * tracefile(1:klena(tracefile)), dir(1:klena(dir)),
21  * mint, maxt, dt, pixel, dothin, split,
22  * outtype, mulalpha
23 
24  call copenfw2(11, tracefile, 1, icon)
25  if(icon .ne. 1) then
26  write(0,*) tracefile, ' cannot be opened'
27  stop 1111
28  endif
29 
30  t2 = mint
31  do while (t2 .lt. maxt)
32  t1 = t2
33  t2 = min(t1+ dt*n , maxt)
34  jmax = 0
35  jmin = 10000000
36  call slice(t1, t2, dt)
37  write(0,*) ' t1=',t1, 't2=',t2, ' slice ended'
38  if(dothin) then
39  call thinning(jmin, jmax)
40  write(0,*) ' thinning ended'
41  endif
42 
43  if(split) then
44  if( ibits(outtype, 0, 1) .ne. 0) then
45  call mkfiles
46  endif
47  if( ibits(outtype, 1, 1) .ne. 0) then
48  call mkskelfiles
49  endif
50  write(0,*) ' all output finished'
51  else
52  if(ibits(outtype, 0, 1) .ne. 0) then
53  call mkafile
54  endif
55  if(ibits(outtype, 1, 1) .ne. 0) then
56  call mkaskelfile
57  endif
58  write(0,*) ' ouput to a file ended'
59  endif
60  if(t2 .lt. maxt) then
61 ! rewind(*) is imposible for stdin
62  write(0,*) ' rewind impossilbe'
63  stop 1111
64  endif
65  enddo
66  end
67 ! *********************************
68 ! read one trace file and slice data by constant time surface.
69 ! data is accumulated in x(i,j) etc. where i is the index of
70 ! number of ptcls in the given time plane. j the index of the
71 ! time plane.
72 ! *********************************
73  subroutine slice(mint, maxt, dt)
74  implicit none
75  include "Zprivate2.f"
76 
77  real*4 mint, maxt, dt
78  integer i, j
79  real*4 t, k
80  integer*2 code, chg
81  integer*2 temp
82  integer it1, it2
83  real*4 xx1, yy1, zz1, time1
84  real*4 xx2, yy2, zz2, time2
85 
86  character* 120 input
87 
88  do j = 1, n
89  idx(j) = 0
90  enddo
91 
92  do while (.true.)
93  input = ' '
94  read(*, '(a)', end=1000 ) input
95  if( input .ne. " " ) then
96  read(input, * ) xx1, yy1, zz1, time1, code, chg
97  do while( input .ne. " ")
98  read(*, '(a)' ) input
99  if( input .ne. " " ) then
100  read(input, * ) xx2, yy2, zz2, time2, code, chg
101  it1 = (time1- mint)/dt +1
102  it2 = (time2- mint)/dt
103  if(it1 .lt. 1) goto 900
104  if(it2 .gt. n) goto 900
105  if(time2 .gt. maxt) goto 900
106  jmin = min(jmin, it1)
107  jmax = max(jmax, it2)
108  do j = it1, it2
109  t = j*dt + mint
110  if( idx(j) .ge. maxp ) then
111  write(0,*)
112  * 'ptcls at time=', t , ' > ', maxp
113  write(0,*)
114  * 'try to thin ptcls in the same pixel'
115  call thinning(j,j)
116  endif
117  idx(j) = idx(j) + 1
118  if(idx(j) .gt. maxp) then
119  write(0,*) 'ptcls > ', maxp
120  write(0,*) 'thinning not worked'
121  stop 1234
122  endif
123 
124 ! (x2-x1)/(t2-t1) *(t-t1) +x1
125  k = (t - time1) /(time2-time1)
126  temp = (xx2-xx1) * k + xx1
127  if( abs(temp) .gt. max16bit) goto 200
128  x(idx(j), j) =temp
129  temp = (yy2-yy1) * k + yy1
130  if( abs(temp) .gt. max16bit) goto 200
131  y(idx(j), j) = temp
132  temp = (zz2-zz1) * k + zz1
133  if( abs(temp) .gt. max16bit) goto 200
134  z(idx(j), j) = temp
135  codex(idx(j), j) = code
136  chgx(idx(j), j) = chg
137  goto 210
138  200 continue
139  idx(j)= idx(j) -1
140  210 continue
141  enddo
142  900 continue
143  xx1 = xx2
144  yy1 = yy2
145  zz1 = zz2
146  time1 = time2
147  endif
148  enddo
149  endif
150  enddo
151  1000 continue
152  end
153 ! ***********************************
154 ! do thinning if two or more data fall in the dame pixel.
155 ! **********************************
156  subroutine thinning(i1, i2)
157  implicit none
158  include "Zprivate2.f"
159 ! culling overlapping points in a pixel
160 ! this is very rough thinning
161 ! sorr each x
162  integer i1, i2
163  integer nc, j, i, k1, k2, l, nc0
164  logical dothin
165 
166  do j = i1, i2
167  dothin = .false.
168  if( idx(j) .gt. 0) then
169  call kqsorth(x(1,j), si, idx(j))
170  do i = 1, idx(j)-1
171  k1 = si(i)
172  if(k1 .lt. 0) goto 20
173  do l = i+1, idx(j)
174  k2 = si(l)
175  if(k2 .lt. 0) goto 10
176  if(abs(x(k1, j)- x(k2,j)) .gt. pixel ) goto 20
177 ! since xx is sorted, we may safe to skip
178 ! further check
179 !
180  if(abs(y(k1, j)- y(k2,j)) .gt. pixel ) goto 10
181  if(abs(z(k1, j)- z(k2,j)) .gt. pixel ) goto 10
182 ! remove k2
183  si(l) = - k2
184  dothin = .true.
185  10 continue
186  enddo
187  20 continue
188  enddo
189  if(dothin) then
190  nc0 = idx(j)
191  call mvdatai(x, j, nc)
192  call mvdatai(y, j, nc)
193  call mvdatai(z, j, nc)
194  call mvdatai(codex, j, nc)
195  call mvdatai(chgx, j, nc)
196  idx(j) = nc
197 !/////////////
198  write(0,*) ' thinning ', nc0, "-->", nc
199 !//////////////
200  endif
201  endif
202  enddo
203  end
204 ! *******************************
205  subroutine mvdata(f, j, nc)
206  implicit none
207  include "Zprivate2.f"
208 
209  integer j
210  real*4 f(maxp, n)
211 
212  real*4 temp(maxp)
213  integer i, nc, l
214 
215  nc = 0
216 
217  do i = 1, idx(j)
218  l = si(i)
219  if(l .gt. 0 ) then
220  nc = nc + 1
221  temp(nc) = f(l, j)
222  endif
223  enddo
224 
225  do i = 1, nc
226  f(i, j) = temp(i)
227  enddo
228 
229 
230  end
231  subroutine mvdatai(f, j, nc)
232  implicit none
233  include "Zprivate2.f"
234  integer j
235  integer*2 f(maxp, n)
236 
237  integer*2 temp(maxp)
238  integer i, nc, l
239  nc = 0
240 
241  do i = 1, idx(j)
242  l = si(i)
243  if(l .gt. 0 ) then
244  nc = nc + 1
245  temp(nc) = f(l, j)
246  endif
247  enddo
248 
249  do i = 1, nc
250  f(i, j) = temp(i)
251  enddo
252 
253 
254  end
255 
256  subroutine mkfiles
257  implicit none
258  include "Zprivate2.f"
259 
260  character* 130 filename
261 
262  integer filec
263  integer klena
264  data filec/0/
265  save filec
266 
267  integer i, j
268 
269  do j = jmin, jmax
270  if(idx(j) .gt. 0) then
271  filec = filec + 1
272  write(filename,'(a, a, i5.5,a)') dir(1:klena(dir)),
273  * "/ts", j, ".dat"
274 ! * "/ts", filec, ".dat"
275  open(20, file=filename, form='formatted')
276  do i= 1, idx(j)
277  write(20,'(3i7,i3,i3)')
278  * x(i, j), y(i,j), z(i,j), codex(i,j), chgx(i,j)
279  enddo
280  close(20)
281  endif
282  enddo
283  end
284 
285  subroutine mkskelfiles
286  implicit none
287  include "Zprivate2.f"
288 
289  character* 130 filename
290 
291  integer filec
292  integer klena
293  data filec/0/
294  save filec
295 
296  integer i, j
297 
298  do j = jmin, jmax
299  if(idx(j) .gt. 0) then
300  filec = filec + 1
301  write(filename,'(a, a, i5.5, a)') dir(1:klena(dir)),
302  * "/ts", j, ".skel"
303  open(20, file=filename, form='formatted')
304 
305  write(20, '(a)') "SKEL"
306  call wtaskel(20, x(1,j), y(1,j), z(1,j),
307  * codex(1,j), chgx(1, j), idx(j), mulalpha)
308 
309  close(20)
310  endif
311  enddo
312  end
313 
314  subroutine mkafile
315  implicit none
316  include "Zprivate2.f"
317 
318  integer i, j
319  character* 130 filename
320 
321  integer filec
322  integer klena
323  data filec/0/
324  save filec
325 
326  if( filec .eq. 0 ) then
327  filename = dir(1:klena(dir))//"/timesorted.dat"
328  open(20, file=filename,
329  * form='formatted')
330  filec = 1
331  endif
332 
333  do j = jmin, jmax
334  do i= 1, idx(j)
335  write(20,'(3i7, i3,i3)' )
336  * x(i, j), y(i,j), z(i,j), codex(i,j), chgx(i,j)
337  enddo
338  if( idx(j) .gt. 0 ) write(20,*)
339  enddo
340  end
341  subroutine mkaskelfile
342  implicit none
343  include "Zprivate2.f"
344 
345  integer i, j
346  character* 130 filename
347 
348  integer filec
349  integer klena
350  data filec/0/
351  save filec
352 
353  if( filec .eq. 0 ) then
354  filename = dir(1:klena(dir))//"/timesorted.skel"
355  open(20, file=filename,
356  * form='formatted')
357  filec = 1
358  endif
359 
360  do j = jmin, jmax
361  if(idx(j) .gt. 0) then
362  write(20,'(a)') "SKEL"
363  call wtaskel(20,
364  * x(1, j), y(1,j), z(1,j), codex(1,j), chgx(1,j), idx(j),
365  * mulalpha)
366  write(20,*)
367  endif
368  enddo
369  end
370 ! ******************
371 ! write a skel data for Geomview
372  subroutine wtaskel(fno, xa, ya, za, code, chg, np, mulalpha)
373 !
374  implicit none
375  integer fno, np
376  real*4 xa(np), ya(np), za(np)
377  real*4 mulalpha
378  integer*2 code(np), chg(np)
379 
380  real r, g, b, alpha
381  integer i
382  if(np .gt. 0) then
383  write(fno, '(2i9)') np, np
384  do i = 1, np
385  write(fno, '(3i7)' ) xa(i), ya(i), za(i)
386  enddo
387  do i= 1, np
388  call code2rgb(code(i), chg(i), r, g, b, alpha)
389  write(fno, '("1 ", i8, 3f5.2,f6.3)')
390  * i-1, r, g, b, alpha*mulalpha
391  enddo
392  endif
393  end
394  subroutine code2rgb(codei, chgi, r, g, b, alpha)
395  implicit none
396  integer*2 codei, chgi
397  real r, g, b, alpha
398 
399  integer ncolor, mncolor
400  parameter( mncolor = 17 )
401  type colortab
402  integer*2 code
403  integer*2 chg
404  real r
405  real g
406  real b
407  real alpha
408  end type colortab
409  type(colortab):: tab(mncolor)
410 
411  character*80 input
412  integer i
413 
414  integer first
415  data first/0/
416  save first, ncolor
417 
418  if(first .eq. 0) then
419  input = ' '
420  open(13, file='colortab')
421  i = 0
422  do while(.true.)
423  read(12, '(a)',end=10) input
424  if(input(1:1) .ne. "#" .and. input .ne. ' ') then
425  i = i + 1
426  if(i .gt. mncolor) then
427  write(0,*) ' too many color spec. in colortab'
428  stop 99999
429  endif
430  read(input,*)
431  * tab(i).code, tab(i).chg,
432  * tab(i).r, tab(i).g, tab(i).b,
433  * tab(i).alpha
434  endif
435  enddo
436  10 continue
437  ncolor = i
438  first = 1
439  close(13)
440  endif
441 
442  do i = 1, ncolor
443  if(tab(i).code .eq. codei .and. tab(i).chg .eq. chgi) goto 100
444  enddo
445  i = ncolor
446  100 continue
447  r = tab(i).r
448  g = tab(i).g
449  b = tab(i).b
450  alpha = tab(i).alpha
451  end
452 
453 
454 
integer npitbl real *nx parameter(n=101, npitbl=46, nx=n-1) real *8 uconst
nodes z
subroutine mkfiles
Definition: timeslice.f:242
subroutine mvdata(f, j, nc)
Definition: timeslice.f:191
subroutine thinning(i1, i2)
Definition: timeslice.f:141
subroutine wtaskel(fno, xa, ya, za, code, chg, np, mulalpha)
Definition: timeslice.f:359
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
subroutine kqsorth(A, ORD, N)
Definition: kqsorth.f:23
averg real MaxCPU integer idx(Maxp)
subroutine copenfw2(io, fnin, form, icon)
Definition: copenf.f:205
subroutine mkskelfiles
Definition: timeslice.f:271
subroutine mkaskelfile
Definition: timeslice.f:328
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
subroutine code2rgb(codei, chgi, r, g, b, alpha)
Definition: timeslice.f:381
latitude latitude this system is used *****************************************************************! type coord sequence union map real y
Definition: Zcoord.h:25
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
!onst int maxp
Definition: Zprivate.h:3
subroutine mvdatai(f, j, nc)
Definition: timeslice.f:217
integer n
Definition: Zcinippxc.h:1
subroutine mkafile
Definition: timeslice.f:301
! structure defining a particle at production ! Basic idea of what is to be contained in ! the particle structue is that dynamical ones should be included those derivable from the particle code ! is not included ******************************************************type fmom momentum sequence union map real e endmap map real * x
Definition: Zptcl.h:21
subroutine slice(mint, maxt, dt)
Definition: timeslice.f:69