COSMOS v7.655  COSMOSv7655
(AirShowerMC)
interface.f File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine xbgrun
 

Function/Subroutine Documentation

◆ xbgrun()

subroutine xbgrun ( )

Definition at line 4 of file interface.f.

References b, bin, c, cgetfname(), charge, cmintime2websec(), copenfw2(), cos, cqfirstid(), cqincident(), csetmuonpol(), csortstack(), d, d0, e, false, histdep(), kelec, kmuon, kphoton, kseblk(), kwhist(), kwhistai(), kwhistc(), kwhistd(), kwhistdir(), kwhistev(), kwhisti(), kwhistid(), kwhistp(), kwhists(), kwhistso(), mass, ne, nfai, ng, nmu, nrbin, p, subcode, t, tkarspec, tkrtspec, true, wgt, x, xyz, and y.

4  implicit none
5 #include "Zmaxdef.h"
6 #include "Zglobalc.h"
7 #include "Zmanagerp.h"
8 #include "Ztrack.h"
9 #include "Ztrackp.h"
10 #include "Ztrackv.h"
11 #include "Zcode.h"
12 #include "Zheavyp.h"
13 #include "Zobs.h"
14 #include "Zobsp.h"
15 #include "Zobsv.h"
16 #include "Zstackv.h"
17 #include "Zprivate.h"
18 #include "Zprivate2.h"
19 #include "../Zabsorb.h"
20  integer id ! input. 1 ==> aTrack is going out from
21 ! outer boundery.
22 ! 2 ==> reached at an observation level
23 ! 3 ==> reached at inner boundery.
24  type(track):: atrack
25 
26 ! type(track):: inci
27 !////////////
28  type(coord):: pdir, cdir
29 !////////////
30  type(coord):: tetafai
31 
32  character*128 input
33  character*64 dirstr
34  real sr, dr, tempr
35  integer i, j, k, m, icon
36  integer ansites
37  save ansites
38  integer iij, code
39  integer i1, i2, ic
40  integer ir, ifai, l, ridx, faiidx
41  real*8 e0, cosz
42  real*8 fai0, fai, sint
43  real*8 delta
44  integer reducedtime
45  integer nn
46  integer klena
47  integer w2hl(maxnoofsites)
48  real*8 r, eloss, rinmu, cosang
49  real*8 dedt, dedtf, rho, dist, disto, binfai
50  real*8 aa
51  real*8 wx, wy, wz, temp
52  real za
53  real de, ek, f, molu
54  real dt, tmin
55  real*8 cvh2den
56  data binfai/30./
57  integer ldep
58 ! integer ndummy
59  character*9 ptcln(4)
60  data ptcln/"Photons", "Electrons","Muons", "hadron"/
61  character*9 ptcl2(3)
62  data ptcl2/"Electrons", "Muons","All"/
63  real power(4)
64  integer nstr
65  data power/1.,1.,1., 1./
66  real power2(3)
67  data power2/1.,1.,1./
68  character*128 title
69  character*96 evid(nsites)
70  save evid
71  real*8 cog, cog2, sumne, obstimes, savederg(5)
72  real*8 firstcdepth, dd
73  logical dosort
74  real*4 wt, stime
75  real*8 sumebydedx, sumebydeath,sumebydeathneu,sumebydeathnut
76  real*8 sumebydeathe, sumebydeathg, sumebydeathmupik,
77  * sumebydeathp, sumebydeatho
78  real*8 sumecrash, sumespace
79  real*8 sumall, sumdeinair, summissing, sumuncertain
80  integer vn/2/ ! version number for the fnoB output
81  save
82 !/////////////
83  real*8 pabs, rcore, sina, cs, sn, cf, mom(3), ek8, u
84 !/////////////
85 
86 ! ***********************
87  include "interface1.h"
88 ! *********************
89 
90 
91  do i = 1, nsites
92  w2hl(i) = 0
93  enddo
94 
95  do i = 1, nsites
96 ! histdep(i) is the layer number
97  if(histdep(i) .eq. 0) exit
98  ansites = i
99  w2hl( histdep(i) ) = i
100  enddo
101 
102  r=rmin
103  dr = 10.**bin
104 
105  do i = 1, nrbin
106 ! center of the bin:
107  rbin(i) = r
108  r = r* dr
109  enddo
110 #if defined (MACOSX)
111 #else
112 ! specify bin or ascii output
113  call kwhistso( binw )
114 #endif
115 
116  return
117 ! *********************************** hook for Beginning of 1 event
118 ! * All system-level initialization for 1 event generation has been
119 ! * eneded at this moment.
120 ! * After this is executed, event generation starts.
121 ! *
122  entry xbgevent
123 
124  call cqincident(inci, angle)
125  e0 = inci.p.fm.p(4)
126  if(inci.p.code .eq. kmuon) then
127  call csetmuonpol(1.0d0)
128  endif
129  cosz = -angle.r(3)
130  fai0 = atan2(-angle.r(2), -angle.r(1))*todeg
131  sint = sqrt(1.0-cosz**2)
132 
133  if(inci.p.code .eq. 9) then
134  nn= inci.p.subcode
135  elseif(inci.p.code .eq. 1) then
136  nn=0
137  else
138  nn=1
139  endif
140 
141  write(0,'("i ", i6, i4, g13.4,3f11.7,f7.1)')
142  * eventno, inci.p.code,
143  * inci.p.fm.e, -angle.r(1), -angle.r(2), -angle.r(3)
144  write(0,'(a, 1p, 6g15.5)')
145  * '### ', detxaxis.r(1:3), detzaxis.r(1:3)
146  do i = 1, noofsites
147  sumeloss(i) = 0.
148  do j = 1, 4
149  ng(i) = 0.
150  ne(i) = 0.
151  nmu(i) = 0.
152  nhad(i) = 0.
153  enddo
154  decent(i) = 0.
155  do ifai = 1, nfai
156  do ir= 1, nrbin
157  derfai(ir, ifai, i) = 0.
158 ! do j = 1, 4
159 ! nrfaiAll(ir, ifai, j, i) = 0.
160 ! enddo
161  enddo
162  enddo
163  enddo
164 
165 
166 ! estimate time minimum and time bin for eeach web sector
167 
168  do i = 1, ansites
169  ldep = histdep(i)
170  call cmintime2websec(obssites(ldep).pos.xyz,
171  * ldep, i, webmin )
172  enddo
173 
174 #if defined (MACOSX)
175 #else
176 ! histogram: instanciate
177 ! t spectrum at each web sector
178  if(tkrtspec) then
179  do i = 1, ansites
180  do j = 1, 4
181 ! at center
182  call kwhisti( tspec0(j, i),
183  * -5., 0.05, 200, b'00000')
184  call kwhistai( tspec0(j, i),
185  * "Arrival time dist. of "//ptcln(j)//" at center",
186  * "t", "ptcls", .false., 0., "time", "ns")
187 ! clear
188  call kwhistc(tspec0(j, i))
189 
190  do ir=1, nrbin
191  do ifai=1, nfai
192  if(reducedtime .eq. 1) then
193  tmin = webmin(ir, 7, i)
194  else
195  tmin = webmin(ir, ifai,i)
196  endif
197  dt = 0.01*10.0**(bin*(ir-1))*100. ! approx core distnace m
198  dt = dt**0.75*1.e9/3.0e8/100. ! if sqrt 1m-->0.03 ns 10 m-->0.15 ns
199  ! 100m 1ns 1km 5ns 4km 10ns
200  ! dt**0.65 makes larger bin at large distance (<=x2)
201  if(j .eq. 4) dt=dt*10.0*ir/35.0 ! for delayed hadrons
202  dt= max(dt, 0.02)
203 
204  call kwhisti( tspec(j, ir, ifai, i),
205  * tmin, dt, 2000, b'00000')
206 
207  call kwhistai( tspec(j, ir, ifai, i),
208  * "Arrival time of "//ptcln(j)//" at (r,fai)",
209  * "rt", "ptcls", .false., 0., "time", "ns")
210 ! clear
211  call kwhistc(tspec(j, ir, ifai, i))
212  enddo
213  enddo
214  enddo
215  enddo
216  endif
217 
218 ! lateral in each fai bin
219  if(tkarspec) then
220 
221  do i = 1, ansites
222  do j = 1, 4 ! g,e,mu,h
223  do ifai = 1, nfai
224  call kwhisti(rspec(j, ifai, i),
225  * rmin, bin, nrbin, b'00011' )
226  call kwhistai(rspec(j, ifai, i),
227  * "Lateral Dist. of "//ptcln(j)//" at diff. azimuth",
228  * "ar", "ptcls", .true., power(j), "r", "m.u")
229 ! clear
230  call kwhistc( rspec(j, ifai, i) )
231  enddo
232  enddo
233  enddo
234  endif
235 #endif
236 
237  obstimes = 0.
238 
239  return
240 ! ***************
241  entry xobs(atrack, id)
242 !
243 ! For id =2, you need not output the z value, because it is always
244 ! 0 (within the computational accuracy).
245 !
246 
247  obstimes = obstimes + 1.d0
248  if(mod(obstimes, 100000.d0) .eq. 0. ) then
249  dosort=.false.
250  do i = 1, min(4,stack_pos)
251  if(stack(i).p.fm.p(4) .ne. savederg(i)) then
252  savederg(i)=stack(i).p.fm.p(4)
253  dosort=.true.
254  endif
255  enddo
256  if(dosort) then
257  call csortstack
258  endif
259  write(0, *) ' obstimes=', obstimes, ' ptclE=',atrack.p.fm.p(4)
260  do i = 1, min(4,stack_pos)
261  write(0,*)' stack tops=', stack(i).p.fm.p(4)
262  enddo
263  endif
264 ! ***************
265  code = atrack.p.code
266  ldep = atrack.where
267 ! ************
268  if(id .eq. 2 .and. code .le. 6 ) then ! neglect rare ptcls
269  wz = atrack.vec.w.r(3) ! downgoing < 0
270  if(wz .gt. 0) return
271  wz = -wz
272  r = sqrt( atrack.pos.xyz.x**2 +
273  * atrack.pos.xyz.y**2 )
274  molu = obssites(ldep).mu
275  rinmu =r/molu
276  sr = rinmu ! single precision
277  ridx = (log10( rinmu/rmin )/bin +0.5) +1
278 
279  ek = atrack.p.fm.p(4) -atrack.p.mass
280  wt = atrack.wgt ! wt is single
281  if(code .eq. kphoton) then
282  ng(ldep) = ng(ldep) + atrack.wgt
283  elseif(code .eq. kelec) then
284  ne(ldep) = ne(ldep) + atrack.wgt
285  elseif(code .eq. kmuon) then
286  nmu(ldep) = nmu(ldep) + atrack.wgt
287  elseif(code .le. 6) then
288  nhad(ldep) = nhad(ldep) +atrack.wgt
289  endif
290 ! ---------- compute energy loss
291  if(atrack.p.charge .ne. 0 ) then
292 ! -----------------
293 ! /| |
294 ! / | 1g/cm2
295 ! /A | |
296 ! -------------------
297 ! / ptcl direction
298 ! get energy loss when aTrack goes some distance
299 ! of which vertical gramage is 1g/cm2.
300 ! Gramage the particle travel is
301 ! 1/cos where cos is the cos of angle (i.e, A if Fig)
302 ! in the detctor system.
303 ! 1g/cm^2 = 10-3kg/10-4 m^2 =10 kg/m^2.
304 ! To travel 1 g/cm^2, the ptcl must
305 ! run dist kg/m^2
306  if(abs(wz) .gt. 1.d-2) then
307  dist =10./wz ! in kg/m2/(g/cm2)
308  else
309 ! for safety
310  dist =1000.
311  endif
312 
313  call cqelossrate(dedt,dedtf) ! loss rate GeV/(kg/m^2)
314 ! dedtF is the full eloss ; dedt is the restricted
315 ! loss. We may better use full here.
316 ! energy in 1 g/cm2 of vertical direction
317  eloss =min( real(dedtF*dist), ek) ! GeV/(g/cm2)
318  eloss = eloss*atrack.wgt ! GeV/(g/cm2)
319  sumeloss(ldep)=sumeloss(ldep) + eloss
320  else
321  eloss=0.
322  endif
323 
324  if(code .ge. 4) code=4
325  if( atrack.p.charge .ne. 0 .or.
326  * w2hl(ldep) .gt. 0 ) then
327 ! fai
328 ! fai is in -15 to 345 (for dfai=30.)
329  aa=atan2(atrack.pos.xyz.y, atrack.pos.xyz.x)*
330  * todeg -fai0
331  fai = aa/todeg
332  aa= mod(aa + 360.d0, 360.d0)
333  if(aa .gt. (360.d0-dfai/2.0d0)) aa= aa-360.d0
334  faiidx=(aa+dfai/2.0d0) /dfai + 1
335  if(ridx .ge. 1 .and. ridx .le. nrbin) then
336  derfai(ridx, faiidx, ldep) = derfai(ridx, faiidx, ldep)
337  * + eloss
338  elseif(ridx .le. 0) then
339  decent(ldep) = decent(ldep) + eloss
340  endif
341 !
342 ! do following for specified histo layers (typically only 1 layer)
343 !
344 #if defined (MACOSX)
345 #else
346  if( w2hl(ldep) .gt. 0 ) then
347  i = w2hl(ldep)
348  if(tkarspec) then
349  call kwhist( rspec(code, faiidx, i),
350  * sr, wt)
351  endif
352 
353  if( tkrtspec ) then
354  stime = atrack.t
355  if(reducedtime .eq. 1) then
356  delta = r*(cos(fai) + 1.)*sint*1.d9/c ! ns
357  stime = stime + delta
358  endif
359  ir = ridx
360  if(ir .lt. 1) then
361  call kwhist( tspec0(code, i),
362  * stime, wt)
363  elseif(ir .le. nrbin) then
364  call kwhist( tspec(code, ir, faiidx, i),
365  * stime, wt)
366  endif
367  endif
368  endif
369 #endif
370  endif
371  endif
372  return
373 ! **************
374  entry xenevent
375 ! **************
376 ! replace @ # % in basefilename by hostname, etc
377 ! and put it in basefilename2
378 !
379 
380  write(0,*) 'ev#=',eventno,
381  * ' generation phase finished. now writing data'
382 
383  call cgetfname(basefilename, basefilename2)
384  call cqfirstid(firstcdepth)
385  firstcdepth = firstcdepth* 0.1 ! in g/cm2 First col depth.
386 
387 
388 
389  if(observeas) then
390  cog = 0.
391  sumne = 0.
392  do i = 1, noofassites
393  if(i .gt. 1 .and. i .lt. noofassites ) then
394  dd =(asdepthlist(i+1) - asdepthlist(i-1))/2.0
395  elseif(i .eq. 1) then
396  dd =(asdepthlist(2) - asdepthlist(1))
397  else
398  dd =(asdepthlist(noofassites) -
399  * asdepthlist(noofassites-1))
400  endif
401  cog = cog + asobssites(i).esize*dd*asdepthlist(i)
402  sumne= sumne +asobssites(i).esize*dd
403  enddo
404 ! 0.1 is for g/cm2
405  cog = cog*0.1/sumne
406 
407  cog2 = 0.
408  sumne = 0.
409  do i = 1, noofassites
410  if( asobssites(i).age .gt.
411  * (2.0-asobssites(noofassites).age)) then
412  if(i .gt. 1 .and. i .lt. noofassites ) then
413  dd =( asdepthlist(i+1) - asdepthlist(i-1))/2.0
414  elseif(i .eq. 1) then
415  dd =(asdepthlist(2) - asdepthlist(1))
416  else
417  dd =(asdepthlist(noofassites) -
418  * asdepthlist(noofassites-1))
419  endif
420  dd = dd
421  cog2 = cog2 + asobssites(i).esize*asdepthlist(i)*dd
422  sumne= sumne +asobssites(i).esize*dd
423  endif
424  enddo
425  if(sumne .gt. 0.) then
426  cog2 = cog2*0.1/sumne
427  else
428 ! to deep penetration
429  cog2 = asdepthlist(noofassites)*0.1
430  endif
431 
432  filename = basefilename2(1:klena(basefilename2))//".hyb"
433  call copenfw2(fnob, filename, 1, icon)
434 
435  write(fnob,
436  * '("h ", i4, 3i3, 1pE11.3, 0p 3f11.7, 1pE11.3, 0p,
437  * 2f7.0,i2,a )')
438  * eventno, inci.p.code,
439  * inci.p.subcode, inci.p.charge,
440  * inci.p.fm.e, -angle.r(1), -angle.r(2), -angle.r(3),
441  * firstcdepth, cog, cog2, vn, ' /'
442 
443  sumebydedx = 0.
444  sumebydeathg =0.
445  sumebydeathe =0.
446  sumebydeathmupik =0.
447  sumebydeathneu = 0.
448  sumebydeathnut = 0.
449  sumebydeathp = 0.
450  sumebydeatho = 0.
451  sumebydeath = 0.
452  sumuncertain = 0.
453  sumecrash = 0.
454  sumespace = 0.
455 
456  do i = 1, noofassites
457  if(eabsorb(1) .ne. 0) then
458  write(fnob, '("t ", i3, 2f7.1, 2f6.3,
459  * 1p14g12.3 )')
460  * i,
461  * asdepthlist(i)*0.1, asobssites(i).mu,
462  * asobssites(i).age, asdepthlist(i)*0.1/cog2,
463  * ng(i), ne(i), nmu(i), nhad(i),
464  * asobssites(i).esize, sumeloss(i),
465  * debydedx(i), debydeath(i),
466 ! next ones are from 7.51
467  * debydeathg(i), debydeathe(i), debydeathmupik(i),
468  * debydeathp(i), debydeathnut(i), debydeatho(i)
469 
470  if(i .le. eabsorb(2) ) then
471 ! to see E consv. we should not count
472 ! level > Eabsorb(2).
473  sumebydedx = sumebydedx + debydedx(i)
474  sumebydeath = sumebydeath + debydeath(i)
475  sumebydeathneu = sumebydeathneu +debydeathneu(i)
476  sumebydeathnut = sumebydeathnut +debydeathnut(i)
477  sumebydeathg = sumebydeathg + debydeathg(i)
478  sumebydeathe = sumebydeathe + debydeathe(i)
479  sumebydeathmupik = sumebydeathmupik +
480  * debydeathmupik(i)
481  sumebydeathp = sumebydeathp +debydeathp(i)
482  sumebydeatho = sumebydeatho +debydeatho(i)
483  endif
484  else
485  write(fnob, '("t ", i3, 2f7.1, 2f6.3,
486  * 1p6E11.3 )')
487  * i,
488  * asdepthlist(i)*0.1, asobssites(i).mu,
489  * asobssites(i).age, asdepthlist(i)*0.1/cog2,
490  * ng(i), ne(i), nmu(i), nhad(i),
491  * asobssites(i).esize, sumeloss(i)
492  endif
493  enddo
494  if(eabsorb(1) .ne. 0) then
495  do i = 1, 7
496  sumecrash = sumecrash + ecrash(i)
497  sumespace = sumespace + espace(i)
498  enddo
499  write(fnob,'("b ", 1p7E11.3)') (espace(i), i=1,7)
500  write(fnob,'("b ", 1p7E11.3, i4)') (ecrash(i), i=1,7),
501  * eabsorb(2)
502  write(fnob,
503  * '("c ",1p7E11.3)' )
504  * maxebreak, maxrelebreak, sumediff, sumabsediff,
505  * maxebreak(1)/inci.p.fm.p(4)
506 
507  summissing = sumecrash + sumespace + sumebydeathneu
508  sumuncertain = sumebydeathnut
509  sumdeinair = sumebydedx + sumebydeath
510  sumall = sumdeinair + summissing + sumuncertain
511 
512  write(fnob,'("s ", 1p8E11.3)')
513  * sumebydedx, sumebydeath, sumdeinair,
514  * sumecrash, sumespace, sumebydeathnut,
515  * sumebydeathneu, sumall
516 
517  write(fnob,'("r ", 1p4E11.3)')
518  * sumdeinair/e0, sumuncertain/e0, summissing/e0, sumall/e0
519 ! normalized one
520  write(fnob,'("n ", 1p4E11.3)')
521  * sumdeinair/sumall, sumuncertain/sumall,summissing/sumall,
522  * 1.0
523 ! additional info for more details
524  write(fnob,'("a ", 1p5g12.3 )')
525  * sumebydeathg, sumebydeathe, sumebydeathmupik,
526  * sumebydeathp, sumebydeatho
527  endif
528  write(fnob,*)
529  close(fnob)
530  endif
531 
532  do i = 1, ansites
533  j=histdep(i)
534  write(evid(i),
535  * '(i3, i5, f5.2, f5.2,
536  * f7.1, i4)')
537  * histdep(i), int( asdepthlist(j)*0.1 ),
538  * asobssites(j).age, asdepthlist(j)*0.1/cog2,
539  * asobssites(j).mu, int(cog2)
540  enddo
541 #if defined (MACOSX)
542 #else
543  if(tkarspec) then
544  filename = basefilename2(1:klena(basefilename2))//"-r.hist"
545  call copenfw2(fnol, filename, binw, icon)
546  do i = 1, ansites
547  k=histdep(i)
548  do j = 1, 4
549  write(dirstr,'(a,"/d",i4, "/")')
550  * ptcln(j), int( depthlist(k)*0.1 )
551  call kseblk(dirstr, "|", nstr)
552  do l = 1, nfai
553  call kwhistdir(rspec(j, l, i), dirstr)
554 ! call kwhists( rspec(j, l, i), 0. )
555  call kwhists( rspec(j, l, i), 0. )
556  call kwhistev( rspec(j, l, i), eventno)
557  call kwhistid( rspec(j, l, i), evid(i))
558  call kwhistp( rspec(j, l, i), fnol)
559 ! *********** deallocate ********
560  call kwhistd( rspec(j, l, i) )
561  enddo ! code loop
562  enddo ! fai loop
563  enddo ! depth loop
564 
565  close(fnol)
566  endif
567 
568  if( tkrtspec ) then
569  filename = basefilename2(1:klena(basefilename2))//"-t.hist"
570  call copenfw2(fnot, filename, binw, icon)
571 
572  do i = 1, ansites
573  do j = 1, 4
574  call kwhists( tspec0(j,i), 0.)
575  call kwhistev( tspec0(j,i), eventno)
576  call kwhistid( tspec0(j,i), evid(i))
577  k=histdep(i)
578  dirstr = " "
579  write( dirstr,'(a,"/d",i4, "/")')
580  * ptcln(j), int( asdepthlist(k)*0.1 )
581  call kseblk( dirstr, "|", nstr)
582  call kwhistdir( tspec0(j,i), dirstr )
583  call kwhistp( tspec0(j,i), fnot )
584 ! *********** deallocate ********
585  call kwhistd( tspec0(j,i) )
586  enddo
587  enddo
588 
589  do i = 1, ansites
590  do j = 1, 4
591  do ifai= 1, nfai
592  do ir= 1, nrbin
593  call kwhists( tspec(j,ir, ifai,i), 0.)
594  call kwhistev(tspec(j,ir, ifai,i), eventno)
595  call kwhistid( tspec(j,ir, ifai,i), evid(i))
596  dirstr = " "
597  write(dirstr,'(a,"/d",i4, "/F",i2,"/")')
598  * ptcln(j), int( depthlist(k)*0.1), ifai
599  call kseblk(dirstr, "|", nstr)
600  call kwhistdir(tspec(j,ir, ifai,i), dirstr)
601  call kwhistp( tspec(j,ir, ifai,i), fnot)
602 ! *********** deallocate ********
603  call kwhistd( tspec(j, ir, ifai, i) )
604  enddo
605  enddo
606  enddo ! code loop
607  enddo ! depth loop
608  close(fnot)
609  endif
610 #endif
611 ! output web data
612  if(tkweb) then
613  filename = basefilename2(1:klena(basefilename2))//".nrfai"
614  call copenfw2(fnon, filename, 1, icon)
615 
616  write(fnon,
617  * '(i4,1pE11.3, 0p,i3, f8.4, 1pE11.3,0p, 4i4, 1p,8g11.3)')
618  * eventno, e0, nn, cosz, firstcdepth, nrbin, nfai, ansites,
619  * noofsites, keminobs ! this is not exist in the older version
620 !
621 ! dE/dx lateral
622  do i = 1, noofsites
623  do k = 1, nfai
624  write(fnon, '("dE/dx",f7.1, 3i4)' )
625  * depthlist(i)*0.1, i, i, k
626  write(fnon, '(1p10E11.3)')
627  * ( derfai(m,k,i), m=1,nrbin ), decent(i)
628 ! same center value is put for all fai
629  enddo
630  enddo
631  close(fnon)
632  endif
633 
634  write(0,*) 'ev#=',eventno,' finished completely'
635 
subroutine cgetfname(fnin, fn)
Definition: copenf.f:275
void kwhistid(struct histogram1 *h, char *id)
subroutine cqincident(incident, AngleAtObs)
Definition: cmkIncident.f:486
integer lengid integer lengdir character *dir integer kgetenv2 character *numb character *execid character *msg logical takehist save do nsites histdep(i)=0indivdep(i)=0enddo leng
integer nsites ! max real bin
Definition: Zprivate0.h:2
const int maxnoofsites
Definition: Zobs.h:7
dE dx *! Nuc Int sampling table e
Definition: cblkMuInt.h:130
others if is ng
Definition: cblkManager.h:9
subroutine csetmuonpol(val)
Definition: cinteNuc.f:224
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz r
Definition: ZavoidUnionMap.h:1
nodes i
! for length to thickness conversion or v v ! integer maxnodes real Hinf ! This is used when making table for dim simulation ! The slant length for vertical height to km is ! divided by LenStep m steps ! It can cover the slant length of about km for cos
Definition: Zatmos.h:8
const int kphoton
Definition: Zcode.h:6
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
void kwhistp(struct histogram1 *h, FILE *fno)
Definition: Ztrack.h:44
int nmu[nl][nth]
Definition: Zprivate.h:12
void kwhisti(struct histogram1 *h, float ixmin, float ibinORxmax, int inbin, int itklg)
void kwhistd(struct histogram1 *h)
max ptcl codes in the kelec
Definition: Zcode.h:2
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
void kwhistev(struct histogram1 *h, int evno)
logical KeepWeight ! see setupenv sh logical tkarspec ! get lateral histo in a web fai bin logical tkrtspec ! get time histo in each web bin logical SeeLowdE common Zprivatec2 tkrtspec
Definition: Zprivate4.h:7
void kwhist(struct histogram1 *h, float x, float w)
void kwhistdir(struct histogram1 *h, char *dir)
int ne[nl][nth]
Definition: Zprivate.h:11
! timing nrbin
Definition: Zprivate2.h:12
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
Definition: cblkHeavy.h:36
void kwhistso(int binw)
subroutine copenfw2(io, fnin, form, icon)
Definition: copenf.f:205
real(4), dimension(:), allocatable, save temp
Definition: cNRLAtmos.f:29
logical KeepWeight ! see setupenv sh logical tkarspec ! get lateral histo in a web fai bin logical tkrtspec ! get time histo in each web bin logical SeeLowdE common Zprivatec2 tkarspec
Definition: Zprivate4.h:7
integer w2hl(nsites)
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
subroutine cqfirstid(depth)
Definition: ciniTracking.f:188
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
Definition: cblkEvhnp.h:5
latitude latitude this system is used *****************************************************************! type coord sequence union map real y
Definition: Zcoord.h:25
dE dx *! Nuc Int sampling table d
Definition: cblkMuInt.h:130
void kwhistc(struct histogram1 *h)
real *8 function cvh2den(z)
Definition: ciniSegAtoms.f:54
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p charge
Definition: ZavoidUnionMap.h:1
block data include Zlatfit h c fitting region data data data data data d0 data data d0 data data m
Definition: ZlatfitBD.h:35
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
subroutine csortstack
Definition: cstack.f:102
nodes t
void kwhistai(struct histogram1 *h, char *title, char *categ, char *dNunit, int logv, float pw, char *label, char *unit)
real(4), save b
Definition: cNRLAtmos.f:21
void kwhists(struct histogram1 *h, float inorm)
Definition: Zcoord.h:43
*Zfirst p fm *Zfirst p mass
Definition: ZavoidUnionMap.h:1
max ptcl codes in the kmuon
Definition: Zcode.h:2
*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
subroutine kseblk(text, c, lc)
Definition: kseblk.f:18
subroutine cmintime2websec(obsdetxyz, ldep, depidx, awebmin)
! timing nfai
Definition: Zprivate2.h:12
! 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
*Zfirst p fm *Zfirst p Zfirst p Zfirst p subcode
Definition: ZavoidUnionMap.h:1
dE dx *! Nuc Int sampling table f
Definition: cblkMuInt.h:130
dE dx *! Nuc Int sampling table c
Definition: cblkMuInt.h:130
Here is the call graph for this function: