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

Go to the source code of this file.

Functions/Subroutines

subroutine chookbgrun
 
integer function csighandler (sig, code, context)
 
subroutine chookbgevent
 
subroutine ccount (nc, aTrack)
 
subroutine chookobs (aTrack, id)
 
subroutine cwhere2dep (where, depth)
 
subroutine chookenevent
 
subroutine chookenrun
 
subroutine chooktrace
 
subroutine chookeint (never)
 
subroutine chookgint (never)
 
subroutine chooknepint (never)
 

Function/Subroutine Documentation

◆ ccount()

subroutine ccount ( integer, dimension(nth, nl nc,
type(track aTrack 
)

Definition at line 115 of file chook.f.

References e, eth, mass, ne, ng, nh, nmu, ntha, p, parameter(), and where.

Referenced by chookobs().

115  implicit none
116 #include "Zcode.h"
117 #include "Ztrack.h"
118 
119  type(track):: atrack
120  integer i
121 ! ///////////
122  integer nl, nth
123  parameter(nl = 20, nth=12)
124  common /testcos/eth(nth),
125  * ng(nth, nl), ne(nth, nl), nmu(nth, nl),
126  * nh(nth, nl), ntha
127  integer ng, ne, nmu, nh, ntha
128  real*8 eth
129 !
130  integer nc(nth, nl)
131 
132  do i = 1, ntha
133  if( atrack.p.fm.e- atrack.p.mass .lt. eth(i)) goto 10
134  nc(i, atrack.where) = nc(i, atrack.where) + 1
135  enddo
136  10 continue
integer npitbl real *nx parameter(n=101, npitbl=46, nx=n-1) real *8 uconst
dE dx *! Nuc Int sampling table e
Definition: cblkMuInt.h:130
others if is ng
Definition: cblkManager.h:9
nodes i
Definition: Ztrack.h:44
int nmu[nl][nth]
Definition: Zprivate.h:12
!onst int nth
Definition: Zprivate.h:2
int ne[nl][nth]
Definition: Zprivate.h:11
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
int ntha
Definition: Zprivate.h:14
int nh[nl][nth]
Definition: Zprivate.h:13
!onst int nl
Definition: Zprivate.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 Zfirst where
Definition: ZavoidUnionMap.h:1
real cut integer nc
Definition: Zprivate.h:1
*Zfirst p fm *Zfirst p mass
Definition: ZavoidUnionMap.h:1
float eth[nth]
Definition: Zprivate.h:8
Here is the call graph for this function:
Here is the caller graph for this function:

◆ chookbgevent()

subroutine chookbgevent ( )

Definition at line 77 of file chook.f.

References code, cqincident(), cqinirn(), e, eth, ne, ng, nh, nmu, ntha, p, parameter(), and r.

77  implicit none
78 #include "Zmanagerp.h"
79 #include "Ztrack.h"
80 #include "Ztrackv.h"
81 
82 ! ///////////
83  integer nl, nth
84  parameter(nl = 20, nth=12)
85  common /testcos/eth(nth),
86  * ng(nth, nl), ne(nth, nl), nmu(nth, nl),
87  * nh(nth, nl), ntha
88  integer ng, ne, nmu, nh, ntha
89  real*8 eth
90 ! //////////////
91  type(track):: inci
92  type(coord):: angle
93 
94  integer nev
95 ! //////////////
96  integer i, j
97  integer seed(2)
98  do i = 1, nl
99  do j = 1, ntha
100  ng(j, i) = 0
101  ne(j, i) = 0
102  nh(j, i) = 0
103  nmu(j, i) = 0
104  enddo
105  enddo
106 
107 ! write(*, *)
108  call cqincident(inci, angle)
109  write(*,'(i7,i4,g13.4,3f10.7)') eventno, inci.p.code, inci.p.fm.e,
110  * -angle.r(1), -angle.r(2), -angle.r(3)
111  call cqinirn(seed)
112 ! write(*,*) ' seed=', seed
integer npitbl real *nx parameter(n=101, npitbl=46, nx=n-1) real *8 uconst
subroutine cqincident(incident, AngleAtObs)
Definition: cmkIncident.f:486
dE dx *! Nuc Int sampling table e
Definition: cblkMuInt.h:130
others if is ng
Definition: cblkManager.h:9
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz r
Definition: ZavoidUnionMap.h:1
nodes i
Definition: Ztrack.h:44
int nmu[nl][nth]
Definition: Zprivate.h:12
!onst int nth
Definition: Zprivate.h:2
int ne[nl][nth]
Definition: Zprivate.h:11
********************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
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
int ntha
Definition: Zprivate.h:14
int nh[nl][nth]
Definition: Zprivate.h:13
subroutine cqinirn(ir)
Definition: cwriteSeed.f:4
!onst int nl
Definition: Zprivate.h:1
Definition: Zcoord.h:43
float eth[nth]
Definition: Zprivate.h:8
Here is the call graph for this function:

◆ chookbgrun()

subroutine chookbgrun ( )

Definition at line 10 of file chook.f.

References cprintobs(), cprintprim(), csighandler(), cwriteparam(), d, d0, eth, ne, ng, nh, nmu, ntha, and parameter().

10  implicit none
11 #include "Zmanagerp.h"
12 #include "Ztrack.h"
13 #include "Ztrackv.h"
14 
15 ! ///////////
16  integer nl, nth
17  parameter(nl = 20, nth=12)
18  common /testcos/eth(nth),
19  * ng(nth, nl), ne(nth, nl), nmu(nth, nl),
20  * nh(nth, nl), ntha
21  integer ng, ne, nmu, nh, ntha
22  real*8 eth
23 ! //////////////
24 
25 ! If you feel writing the parameters on stderr is
26 ! a bother, comment out the next or
27 ! use other device than ErrorOut.
28 ! Also you may comment out all output routines below.
29 #ifdef sun4
30  external csighandler
31  integer ieeer, ieee_handler
32 
33  ieeer = ieee_handler('set', 'invalid', csighandler)
34 #endif
35 
36 !
37 ! namelist output
38  call cwriteparam(errorout, 0)
39 ! primary information
40  call cprintprim(errorout)
41 ! observation level information
42  call cprintobs(errorout)
43 
44  eth(1) = 0.3d-3
45  eth(2) = 0.5d-3
46  eth(3)= 1.d-3
47  eth(4) = 2.d-3
48  eth(5) = 5.d-3
49  eth(6) = 10.d-3
50  eth(7) = 20.d-3
51  eth(8)= 50.d-3
52  eth(9) = 100.d-3
53  eth(10) = 200.d-3
54  eth(11) = 500.d-3
55  eth(12) = 1.d0
56 
57 ! ////////////
58  ntha = 1 ! for each ptcle out put use only 1 threshold
59 ! /////////////
integer npitbl real *nx parameter(n=101, npitbl=46, nx=n-1) real *8 uconst
subroutine cprintobs(io)
Definition: cprintObs.f:2
others if is ng
Definition: cblkManager.h:9
int nmu[nl][nth]
Definition: Zprivate.h:12
subroutine cprintprim(out)
Definition: cprintPrim.f:3
!onst int nth
Definition: Zprivate.h:2
int ne[nl][nth]
Definition: Zprivate.h:11
subroutine cwriteparam(io, force)
Definition: cwriteParam.f:4
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
Definition: cblkEvhnp.h:5
int ntha
Definition: Zprivate.h:14
integer function csighandler(sig, code, context)
Definition: chook.f:63
dE dx *! Nuc Int sampling table d
Definition: cblkMuInt.h:130
int nh[nl][nth]
Definition: Zprivate.h:13
!onst int nl
Definition: Zprivate.h:1
float eth[nth]
Definition: Zprivate.h:8
Here is the call graph for this function:

◆ chookeint()

subroutine chookeint ( integer  never)

Definition at line 414 of file chook.f.

414  implicit none
415 
416 #include "Ztrack.h"
417 #include "Ztrackv.h"
418 ! #include "Ztrackp.h"
419 
420  integer never ! input & output
421 
422 ! don't make never = 1, if you want to get
423 ! information after an electron made interaction
424 ! if this is made non zero, this routine will never be called.
425 !
426 ! MovedTrack is the electron that made interaction
427 ! Pwork contains produced particles.
428 ! Nproduced has the number of particles in Pwork
429 ! IntInfArray(ProcessNo) contains the type of interaction
430 !
431 ! default setting
432  never = 1
433 !
434 ! IntInfArray(ProcessNo).process will have one of
435 ! 'brems', 'mscat', 'bscat', 'anihi' or 'mbrem'
436 !

◆ chookenevent()

subroutine chookenevent ( )

Definition at line 288 of file chook.f.

References cecent2sph(), cqfirstid(), cqincident(), d0, depth, eth, ne, ng, nh, nmu, ntha, p, parameter(), and r.

288 
289  implicit none
290 #include "Ztrack.h"
291 #include "Ztrackv.h"
292 #include "Zobs.h"
293 #include "Zobsp.h"
294 #include "Zobsv.h"
295 
296 
297 
298 
299  type(track):: inci
300  type(coord):: angle, tetafai
301  integer i, j
302 
303 ! ///////////
304  integer nl, nth
305  parameter(nl = 20, nth=12)
306  common /testcos/ eth(nth),
307  * ng(nth, nl), ne(nth, nl), nmu(nth, nl),
308  * nh(nth, nl), ntha
309  integer ng, ne, nmu, nh, ntha
310  real*8 eth
311 ! //////////////
312 
313 
314 
315 ! ///////////
316  real*8 fdepth, bsin, teta, fai, sumsize
317  real*8 cgetbsin, sumx, sumy
318  real*8 avex, avey, sume
319  integer nnew
320 ! //////////////
321 ! call cqIncident(inci, angle)
322 ! write(*,*) inci.vec.coszenith, angle.r(3)
323 
324  if(observeas) then
325  call cqfirstid(fdepth)
326  fdepth = fdepth * 0.1 ! in g/cm2
327  call cqincident(inci, angle)
328  angle.r(1) = -angle.r(1) ! angle is directed to downward
329  angle.r(2) = -angle.r(2)
330  angle.r(3) = -angle.r(3)
331  call cecent2sph(angle, tetafai)
332  teta = tetafai.r(1)
333  fai = tetafai.r(2)
334  if(fai .lt. 0. ) fai = 360.d0+fai
335  bsin = cgetbsin(inci.p, mag)*1.e4
336 ! electron size in B approx.
337 ! write(*, *) (ASObsSites(i).esize, i=1, NoOfASSites)
338 ! size weighted age
339 ! write(*, *) (ASObsSites(i).age, i=1, NoOfASSites)
340  sumsize = 0.
341 ! write(*, *)
342  do j = 1, ntha
343  if(ntha .gt. 1) then
344 ! write(*,*) j
345  endif
346  do i = 1, noofassites
347  sumsize = sumsize + asobssites(i).esize
348  write(*, '(f7.1,g13.3,f8.3,f7.1,
349  * 4i8,f7.4)')
350 ! * f8.3, g13.3,f10.3,f10.3) ')
351 ! * sngl(ASObsSites(i).pos.depth/10./angle.r(3)),
352  * sngl(asobssites(i).pos.depth/10.),
353  * sngl(asobssites(i).esize),
354  * sngl(asobssites(i).age), sngl(fdepth),
355 ! * sngl(bsin), sngl(sumsize), sngl(teta), sngl(fai)
356  * ne(j, i), nmu(j, i), nh(j, i), ng(j, i), eth(j)
357  enddo
358  enddo
359  endif
360 
integer npitbl real *nx parameter(n=101, npitbl=46, nx=n-1) real *8 uconst
*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 cqincident(incident, AngleAtObs)
Definition: cmkIncident.f:486
others if is ng
Definition: cblkManager.h:9
subroutine cecent2sph(a, bb)
Definition: ceCent2sph.f:2
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz r
Definition: ZavoidUnionMap.h:1
nodes i
Definition: Ztrack.h:44
int nmu[nl][nth]
Definition: Zprivate.h:12
!onst int nth
Definition: Zprivate.h:2
int ne[nl][nth]
Definition: Zprivate.h:11
********************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
subroutine cqfirstid(depth)
Definition: ciniTracking.f:188
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
Definition: cblkEvhnp.h:5
real *8 function cgetbsin(aPtcl, mag)
Definition: cgetBsin.f:5
real * sume
Definition: Zprivate.h:1
int ntha
Definition: Zprivate.h:14
int nh[nl][nth]
Definition: Zprivate.h:13
!onst int nl
Definition: Zprivate.h:1
Definition: Zcoord.h:43
float eth[nth]
Definition: Zprivate.h:8
Here is the call graph for this function:

◆ chookenrun()

subroutine chookenrun ( )

Definition at line 366 of file chook.f.

366 
367  implicit none

◆ chookgint()

subroutine chookgint ( integer  never)

Definition at line 443 of file chook.f.

443  implicit none
444 
445 #include "Ztrack.h"
446 #include "Ztrackv.h"
447 ! #include "Ztrackp.h"
448 
449  integer never ! input & output
450 
451 ! don't make never = 1, if you want to get
452 ! information after a gamma ray made interaction
453 ! if this is made non zero, this routine will never be called.
454 !
455 ! MovedTrack is the gamma that made interaction
456 ! Pwork contains produced particles.
457 ! Nproduced has the number of particles in Pwork
458 ! IntInfArray(ProcessNo) contains the type of interaction
459 !
460 ! default setting
461  never = 1
462 ! IntInfArray(ProcessNo).process will have one of
463 ! 'pair', 'comp', 'photoe' 'photop' 'mpair'
464 !

◆ chooknepint()

subroutine chooknepint ( integer  never)

Definition at line 471 of file chook.f.

References code, kkaon, kpion, p, and process().

471  implicit none
472 
473 
474 #include "Zcode.h"
475 #include "Ztrack.h"
476 #include "Ztrackv.h"
477 
478 ! #include "Ztrackp.h"
479 
480  integer never ! input & output
481 
482 ! don't make never = 1, if you want to get
483 ! information after a non-e-g particle made interaction
484 ! if this is made non zero, this routine will never be called.
485 !
486 ! MovedTrack is the particle that made interaction
487 ! Pwork contains produced particles.
488 ! Nproduced has the number of particles in Pwork
489 ! IntInfArray(ProcessNo) contains the type of interaction
490 !
491 ! default setting
492 !
493 ! never = 1
494  never = 1
495  if(movedtrack.p.code .eq. kpion .or.
496  * movedtrack.p.code .eq. kkaon) then
497  if(intinfarray(processno).process .eq. 'coll') then
498 ! write(*,*)
499 ! * MovedTrack.p.code,
500 ! * sngl(MovedTrack.p.fm.p(4)), Nproduced
501  endif
502  endif
503 !
504 ! IntInfArray(ProcessNo).process will have
505 ! 'col' or 'decay'
! parameters for Elemag process(-> ---------------------------------------------- real *8 RecoilKineMinE !2 Recoil Kinetic Min Energy above which the recoil(=knock-on process) ! is treated. Below this energy, the effect is included as continuous ! energy loss. Used only if KnockOnRatio $>$ 1. ! If this is 0 or if KnockOnRatio=1, KEminObs(gamma)=KEminObs(elec) is used. ! See also KnockOnRatio. real *8 KnockOnRatio !2 KnockOnRatio *KEminoObs is used instead of RecoilKineMinE if KnockOnRatio $< $1. real *8 X0 !2 Radiation length in kg/m$^2$ for air. Normally the user should not touch this. real *8 Ecrit !2 Critical energy in GeV. \newline ! Employed only when calculating air shower size in the hybrid ! air shower generation. The value would be dependent on the ! experimental purpose. The default value, 81 MeV, is bit too ! small in many applications(The air shower size is overestimated). ! Comparisons of sizes by the hybrid method and by the full Monte ! Carlo tell that \newline ! $N_e$(full 3-D M.C) $< N_e$(hybrid AS with $E_c=81$ MeV) $< N_e$(full 1-D M.C) ! $ {\ \lower-1.2pt\vbox{\hbox{\rlap{$<$}\lower5pt\vbox{\hbox{$\sim$}}}}\ } ! N_e$(hybrid AS with $E_c={76}$ MeV) at around shower maximum. ! Hybrid AS is always essentially 1-D. logical Knockon !2 Obsolete. Don 't use this. See RecoilKineMinE ! and KnockonRatio. real *8 AnihiE !2 If E(positron) $<$ AnihiE, annihilation is considered. real *8 Es !2 Modified scattering constant. 19.3d-3 GeV real *8 MaxComptonE !2 Above this energy, Compton scattering is neglected. real *8 MaxPhotoE !2 Above this energy, photoelectric effect is neglected. real *8 MinPhotoProdE !1 Below this energy, no photo-prod of hadron. See also PhotoProd. logical PhotoProd !1 Switch. if .false., no photo prod. of hadron is considered at all. ! See also MinPhotoProdE, HowPhotoP real *8 Excom1 !2(GeV). If photon energy is<=Excom1, use XCOM data for ! compton/p.e/coherent scattering(must be< 100 GeV). real *8 Excom2 !2(GeV). If photon energy is<=Excom2, use XCOM data for ! pair creation cross-section.(must be< 100 GeV). integer Moliere !2 2$\rightarrow$ use Moliere scat.\newline ! 0$\rightarrow$ use Gaussian scattrign. \newline ! 1$\rightarrow$ use Moli\`ere scattering for non-electrons \newline ! 2$\rightarrow$ use Moli\`ere scattering for all charged ! particles. But treatment is not so rigorous as case of 3. ! \newline ! 3$\rightarrow$ use rigorus Moliere scattering. Diff. from 2 is verysmall. May be some effect in the ! core region. integer ALateCor !2 1$\rightarrow$ angular and lateral correlation is taken into account when Moliere=0 .\newline ! t$\rightarrow$ Use angular-lateral correlation by Gaussian ! approximation. No effect is seen if path length is short. !<-) ---------------------------------------------- common/Zelemagc/RecoilKineMinE
max ptcl codes in the kkaon
Definition: Zcode.h:2
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
max ptcl codes in the kpion
Definition: Zcode.h:2
Here is the call graph for this function:

◆ chookobs()

subroutine chookobs ( type(track aTrack,
integer  id 
)

Definition at line 143 of file chook.f.

References ccount(), charge, code, cqincident(), cwhere2dep(), eth, kelec, kkaon, kmuon, knuc, kphoton, kpion, ne, ng, nh, nmu, ntha, p, parameter(), x, y, and z.

143 !
144 ! Note that every real variable is in double precision so
145 ! that you may output it in sigle precision to save the memory.
146 ! In some cases it is essential to put it in sigle (say,
147 ! for gnuplot).
148 !
149  implicit none
150 #include "Zcode.h"
151 #include "Ztrack.h"
152 #include "Ztrackv.h"
153 #include "Zheavyp.h"
154  integer id ! input. 1 ==> aTrack is going out from
155 ! outer boundery.
156 ! 2 ==> reached at an observation level
157 ! 3 ==> reached at inner boundery.
158  type(track):: atrack
159  type(track):: inci
160  type(coord):: angle, tetafai
161 ! integer i
162 ! ///////////
163 
164 ! ///////////
165  integer nl, nth
166  parameter(nl = 20, nth=12)
167  common /testcos/eth(nth),
168  * ng(nth, nl), ne(nth, nl), nmu(nth, nl),
169  * nh(nth, nl), ntha
170  integer ng, ne, nmu, nh, ntha
171  real*8 eth
172 ! //////////////
173  real*8 depth
174  integer iij
175 
176 
177 
178 !
179 ! For id =2, you need not output the z value, because it is always
180 ! 0 (within the computational accuracy).
181 !
182 ! if(id .eq. 2 .and. aTrack.p.code .eq. kmuon ) then
183  if( id .eq. 2) then
184  call cqincident(inci, angle)
185  iij = atrack.p.code
186 ! call cgpid(iij, ptclid)
187  if(iij .eq. kelec ) then
188  call ccount(ne, atrack)
189 ! ne(aTrack.where) = ne(aTrack.where) + 1
190  elseif(iij .eq. kphoton ) then
191  call ccount(ng, atrack)
192 ! ng(aTrack.where) = ng(aTrack.where) + 1
193  elseif(iij .eq. kmuon ) then
194  call ccount(nmu, atrack)
195 ! nmu(aTrack.where) = nmu(aTrack.where) + 1
196  elseif( iij .eq. kpion .or. iij .eq. kkaon .or.
197  * iij .eq. knuc) then
198  if(atrack.p.charge .ne. 0 ) then
199  call ccount(nh, atrack)
200 ! nh(aTrack.where) = nh(aTrack.where) + 1
201  endif
202  endif
203  endif
204 
205 ! output typical quantities.
206 ! id .eq. 2 below if want otuput
207 ! if(id .eq. 2 .and. aTrack.where .eq. 8 ) then
208 ! if(id .eq. 2 .and. aTrack.where .eq. 1 ) then
209  if(id .eq. 0 ) then ! never happens
210 ! if(aTrack.p.code .ne. kneue .and. aTrack.p.code .ne.
211 ! * kneumu) then
212  call cwhere2dep(atrack.where, depth)
213 ! write(*,*) int(depth/10. +0.001),
214  write(*,*)
215  * atrack.p.code,
216 ! * aTrack.p.subcode,
217 ! * aTrack.p.charge,
218 ! * sngl(aTrack.p.fm.e-aTrack.p.mass),
219 ! * sngl(aTrack.vec.coszenith),
220 ! * sngl(inci.p.fm.p(4)-inci.p.mass)/
221 ! * Code2massN(int(inci.p.code)),
222 ! * inci.p.code,
223 ! * aTrack.pos.xyz.x, aTrack.pos.xyz.y, aTrack.pos.xyz.z,
224  * sngl(atrack.vec.w.x), sngl(atrack.vec.w.y),
225  * sngl(atrack.vec.w.z),
226  * atrack.vec.w.x**2+atrack.vec.w.y**2+atrack.vec.w.z**2
227 !
228 ! write(*,
229 ! * '(i2,1x,i2,1x,f12.2, g13.4, f12.2,1x, f12.2,1x,f7.4,i3)')
230 ! * nev,
231 ! * aTrack.where, ! observation level. integer*2. 1 is highest.
232 ! * aTrack.p.code, ! " ", ptclid, ! ptcl code. integer*2.
233 ! * aTrack.p.charge, ! charge, integer*2
234 ! * sngl(aTrack.t), ! relateive arrival time in nsec (NOT sec).
235 ! ! if TimeStructure is F, nonsense.
236 ! * sngl(aTrack.p.fm.e), ! - aTrack.p.mass), ! kinetic energy in GeV
237 ! * sngl(aTrack.pos.xyz.x), sngl(aTrack.pos.xyz.y), ! x, y, erg in m
238 ! * sngl(aTrack.vec.w.x), ! direc. cos.x in the current detector system.
239 ! * sngl(aTrack.vec.w.y), ! direc. cos.y
240 ! * sngl(aTrack.vec.w.z), ! direc. cos.z
241 ! * sngl(-angle.r(3)) ,
242 ! * sngl(aTrack.vec.coszenith), ! cos of zenith angle
243 ! * sngl(inci.p.fm.p(4)-inci.p.mass)/Code2massN(int(inci.p.code)),
244 ! * inci.p.code
245 ! if(aTrack.p.code .eq. kelec) then
246 ! write(*, *) aTrack.where
247 ! endif
248 ! endif
249 ! you may need in some case other information such as
250 ! * aTrack.p.subcode ! sub code of the particle integer*2
251 ! aTrack.p.mass ! mass
252 ! aTrack.wgt ! weight of the particle (may not be 1. if
253 ! ! ThinSampling =T)
254 ! aTrack.p.fm.x ! momentum x component. Note. Momentum is
255 ! given in the Earth xyz system.
256 
257 ! aTrack.p.fm.y ! y
258 ! aTrack.p.fm.z ! z
259 ! if(aTrack.p.code .eq. kelec .or. aTrack.p.code .eq. kphoton)
260 ! * then
261 ! ng = ng+1
262 ! sumg = sumg + aTrack.p.fm.e
263 
264 ! endif
265  endif
integer npitbl real *nx parameter(n=101, npitbl=46, nx=n-1) real *8 uconst
*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
nodes z
subroutine cqincident(incident, AngleAtObs)
Definition: cmkIncident.f:486
others if is ng
Definition: cblkManager.h:9
const int kphoton
Definition: Zcode.h:6
Definition: Ztrack.h:44
int nmu[nl][nth]
Definition: Zprivate.h:12
max ptcl codes in the kkaon
Definition: Zcode.h:2
max ptcl codes in the kelec
Definition: Zcode.h:2
!onst int nth
Definition: Zprivate.h:2
int ne[nl][nth]
Definition: Zprivate.h:11
subroutine cwhere2dep(where, depth)
Definition: chook.f:268
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
subroutine ccount(nc, aTrack)
Definition: chook.f:115
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code knuc
Definition: cblkHeavy.h:7
int ntha
Definition: Zprivate.h:14
latitude latitude this system is used *****************************************************************! type coord sequence union map real y
Definition: Zcoord.h:25
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p charge
Definition: ZavoidUnionMap.h:1
int nh[nl][nth]
Definition: Zprivate.h:13
!onst int nl
Definition: Zprivate.h:1
Definition: Zcoord.h:43
max ptcl codes in the kpion
Definition: Zcode.h:2
float eth[nth]
Definition: Zprivate.h:8
max ptcl codes in the kmuon
Definition: Zcode.h:2
! 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
Here is the call graph for this function:

◆ chooktrace()

subroutine chooktrace ( )

Definition at line 378 of file chook.f.

References height.

378  implicit none
379 
380 #include "Ztrack.h"
381 #include "Ztrackv.h"
382 #include "Ztrackp.h"
383 #include "Zobs.h"
384 #include "Zobsv.h"
385 
386  real*4 h1, h2
387 !
388 ! Every time a particle is moved in the atmosphere, this routine is called,
389 ! if trace > 100
390 ! For a one track segment,
391 ! TrackBefMove has track information at the beginning of the segment.
392 ! MoveTrack has track information at the end of the segment.
393 !
394 ! You can know the information a track contains in the
395 ! chookObs routine. (Note however, no conversion of coordinate
396 ! has been done. The values are in the Earth xyz system.)
397 ! Besides quantities explained there, you can use, for a given 'track'
398 !
399 ! atrack.pos.xyz.x, atrack.pos.xyz.y, atrack.pos.xyz.z (x,y.z)
400 ! atrack.pos.radiallen (distance from the center of the earth)
401 ! atrack.pos.depth (vertical depth)
402 ! atrack.pos.height (vertical heigth from sea level)
403 !
404 
405  h1 = trackbefmove.pos.height- obssites(noofsites).pos.height
406  h2 = movedtrack.pos.height - obssites(noofsites).pos.height
407 
*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

◆ csighandler()

integer function csighandler ( integer  sig,
integer  code,
integer, dimension(5)  context 
)

Definition at line 63 of file chook.f.

Referenced by chookbgrun().

63  implicit none
64 #include "Zmanagerp.h"
65  integer sig, code, context(5)
66  write(errorout, *) ' f.p exception content=' , context(4)
67 ! call abort()
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
Here is the caller graph for this function:

◆ cwhere2dep()

subroutine cwhere2dep ( integer*2  where,
real*8  depth 
)

Definition at line 268 of file chook.f.

Referenced by chookobs().

268  implicit none
269 #include "Zcoord.h"
270 #include "Zpos.h"
271 #include "Zmagfield.h"
272 #include "Zobs.h"
273 #include "Zobsv.h"
274 
275  integer*2 where
276  real*8 depth
277  if(where .le. 0 .or. where .gt. noofsites) then
278  write(*,*) where, noofsites
279  stop 'error'
280  endif
281 
282  depth =obssites(where).pos.depth
*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
*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 where
Definition: ZavoidUnionMap.h:1
Here is the caller graph for this function: