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

Go to the source code of this file.

Functions/Subroutines

subroutine time (xxx)
 
subroutine chookbgrun
 
subroutine chookbgevent
 
subroutine chookobs (aTrack, id)
 
subroutine chookenevent
 
subroutine chookenrun
 
subroutine chookeint (never)
 
subroutine chookgint (never)
 
subroutine chooknepint (never)
 
subroutine chooktrace
 

Function/Subroutine Documentation

◆ chookbgevent()

subroutine chookbgevent ( )

Definition at line 39 of file chook.f.

References cquhookr(), cut, nc, sume, and sumepi0.

Referenced by ceventloop().

39  implicit none
40 #include "Ztrack.h"
41 #include "Zobs.h"
42 #include "Zobsv.h"
43  include "Zprivate.h"
44 
45  integer i, j
46  sume = 0
47  sumepi0 = 0
48  nc = 0
49  ncpi0= 0
50  call cquhookr(1, cut)
real sumepi0
Definition: Zprivate.h:1
nodes i
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
Definition: cblkHeavy.h:36
subroutine cquhookr(i, rv)
Definition: cqUHookr.f:2
real * sume
Definition: Zprivate.h:1
real cut integer ncpi0 common Zuserc cut
Definition: Zprivate.h:1
real cut integer nc
Definition: Zprivate.h:1
Here is the call graph for this function:
Here is the caller graph for this function:

◆ chookbgrun()

subroutine chookbgrun ( )

Definition at line 15 of file chook.f.

References cprintobs(), cprintprim(), and cwriteparam().

Referenced by cbeginrun().

15  implicit none
16 #include "Zmanagerp.h"
17 
18 
19 ! If you feel writing the parameters on stderr is
20 ! a bother, comment out the next or
21 ! use other device than ErrorOut.
22 ! Also you may comment out all output routines below.
23 
24 ! namelist output
25  call cwriteparam(errorout, 0)
26 ! primary information
27  call cprintprim(errorout)
28 ! observation level information
29  call cprintobs(errorout)
subroutine cprintobs(io)
Definition: cprintObs.f:2
subroutine cprintprim(out)
Definition: cprintPrim.f:3
subroutine cwriteparam(io, force)
Definition: cwriteParam.f:4
Here is the call graph for this function:
Here is the caller graph for this function:

◆ chookeint()

subroutine chookeint ( integer  never)

Definition at line 162 of file chook.f.

Referenced by cinteraction(), and ctracking().

162  implicit none
163 
164 #include "Ztrack.h"
165 #include "Ztrackv.h"
166 ! #include "Ztrackp.h"
167 
168  integer never ! input & output
169 
170 ! don't make never = 1, if you want to get
171 ! information after an electron made interaction
172 ! if this is made non zero, this routine will never be called.
173 !
174 ! MovedTrack is the electron that made interaction
175 ! Pwork contains produced particles.
176 ! Nproduced has the number of particles in Pwork
177 ! IntInfArray(ProcessNo) contains the type of interaction
178 !
179 ! default setting
180  never = 1
181 !
182 ! IntInfArray(ProcessNo).process will have one of
183 ! 'brems', 'mscat', 'bscat',or 'anihi'
184 !
Here is the caller graph for this function:

◆ chookenevent()

subroutine chookenevent ( )

Definition at line 116 of file chook.f.

Referenced by ceventloop().

116 
117  implicit none
118 #include "Ztrack.h"
119 #include "Ztrackv.h"
120 #include "Zobs.h"
121 #include "Zobsp.h"
122 #include "Zobsv.h"
123  include "Zprivate.h"
124 
125  integer i, j
126 ! do i = 1, NoOfSites
127 ! do j = 1, 3
128 ! write(*, *) i, j, nc(j, i)
129 ! enddo
130 ! enddo
131  if(observeas) then
132 ! electron size in B approx.
133 ! write(*,*) 'e ', sngl(sume), nc, sngl(sumepi0), ncpi0
134  do i = 1, noofassites
135  write(*, *) 's ', sngl( asdepthlist(i)*0.1 ),
136  * sngl(asobssites(i).esize), sngl(asobssites(i).age)
137  enddo
138  endif
139 ! write(*,*)
nodes i
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
Definition: cblkHeavy.h:36
Here is the caller graph for this function:

◆ chookenrun()

subroutine chookenrun ( )

Definition at line 147 of file chook.f.

Referenced by cendrun().

147 
148  implicit none
149 #include "Ztrack.h"
150 #include "Ztrackp.h"
151 
152 
153 
154 
Here is the caller graph for this function:

◆ chookgint()

subroutine chookgint ( integer  never)

Definition at line 191 of file chook.f.

Referenced by cinteraction().

191  implicit none
192 
193 #include "Ztrack.h"
194 #include "Ztrackv.h"
195 ! #include "Ztrackp.h"
196 
197  integer never ! input & output
198 
199 ! don't make never = 1, if you want to get
200 ! information after a gamma ray made interaction
201 ! if this is made non zero, this routine will never be called.
202 !
203 ! MovedTrack is the gamma that made interaction
204 ! Pwork contains produced particles.
205 ! Nproduced has the number of particles in Pwork
206 ! IntInfArray(ProcessNo) contains the type of interaction
207 !
208 ! default setting
209  never = 1
210 ! IntInfArray(ProcessNo).process will have one of
211 ! 'pair', 'comp', 'photoe' or 'photop'
212 !
Here is the caller graph for this function:

◆ chooknepint()

subroutine chooknepint ( integer  never)

Definition at line 219 of file chook.f.

References charge, code, cut, knuc, kpion, mass, nc, p, process(), sume, and sumepi0.

Referenced by cinteraction().

219  implicit none
220 
221 #include "Ztrack.h"
222 #include "Ztrackv.h"
223 #include "Zcode.h"
224  include "Zprivate.h"
225  integer never ! input & output
226  integer i
227 
228 ! don't make never = 1, if you want to get
229 ! information after a non-e-g particle made interaction
230 ! if this is made non zero, this routine will never be called.
231 !
232 ! MovedTrack is the particle that made interaction
233 ! Pwork contains produced particles.
234 ! Nproduced has the number of particles in Pwork
235 ! IntInfArray(ProcessNo) contains the type of interaction
236 !
237 ! default setting is 1
238  never = 1
239 
240 !
241 ! IntInfArray(ProcessNo).process will have
242 ! 'coll' or 'decay'
243  if(cut .lt. 1.) then
244  if( intinfarray(processno).process .eq. 'coll' ) then
245  do i = 1, nproduced
246 ! for pions, kaons put E=mass if X > cut (for cut>0)
247  if( pwork(i).code .lt. knuc ) then
248  if( pwork(i).fm.p(4) / movedtrack.p.fm.p(4)
249  * .gt. cut) then
250  sume = sume + pwork(i).fm.p(4)
251  nc = nc +1
252  if( pwork(i).code .eq. kpion .and.
253  * pwork(i).charge .eq. 0 ) then
254  sumepi0 = sumepi0 + pwork(i).fm.p(4)
255  ncpi0= ncpi0 + 1
256  endif
257  pwork(i).fm.p(4) = pwork(i).mass*1.1
258  endif
259  endif
260  enddo
261  endif
262  endif
real sumepi0
Definition: Zprivate.h:1
nodes i
! 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
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
*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
real * sume
Definition: Zprivate.h:1
real cut integer ncpi0 common Zuserc cut
Definition: Zprivate.h:1
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p charge
Definition: ZavoidUnionMap.h:1
real cut integer nc
Definition: Zprivate.h:1
*Zfirst p fm *Zfirst p mass
Definition: ZavoidUnionMap.h:1
max ptcl codes in the kpion
Definition: Zcode.h:2
Here is the call graph for this function:
Here is the caller graph for this function:

◆ chookobs()

subroutine chookobs ( type(track aTrack,
integer  id 
)

Definition at line 59 of file chook.f.

Referenced by cobservation(), and cobshes().

59 !
60 ! Note that every real variable is in double precision so
61 ! that you may output it in sigle precision to save the memory.
62 ! In some cases it is essential to put it in sigle (say,
63 ! for gnuplot).
64 !
65  implicit none
66 #include "Ztrack.h"
67 #include "Zcode.h"
68  include "Zprivate.h"
69 
70  integer id ! input. 1 ==> aTrack is going out from
71 ! outer boundery.
72 ! 2 ==> reached at an observation level
73 ! 3 ==> reached at inner boundery.
74  type(track):: atrack
75 !
76 ! For id =2, you need not output the z value, because it is always
77 ! 0 (within the computational accuracy).
78 !
79 ! if(id .eq. 2 .and. aTrack.vec.coszenith .gt. 0 ) then
80 ! if(aTrack.p.code .le. 3) then
81 ! nc(aTrack.p.code, aTrack.where) =
82 ! * nc(aTrack.p.code, aTrack.where) +1
83 ! endif
84 ! endif
85 ! output typical quantities.
86 ! write(*, '(3i5, )
87 ! * aTrack.where, ! observation level. integer*2. 1 is highest.
88 ! * aTrack.p.code, ! ptcl code. integer*2.
89 ! * aTrack.p.charge, ! charge, integer*2
90 ! * sngl(aTrack.t), ! relateive arrival time in nsec (NOT sec).
91 ! ! if TimeStructure is F, nonsense.
92 ! * sngl(aTrack.p.fm.p(4)) ! total energy in GeV.
93 ! * sngl(aTrack.pos.xyz.r(1)), sngl(aTrack.pos.xyz.r(2)), ! x, y in m
94 ! * sngl(aTrack.vec.w.r(1)), ! direc. cos.x in the current detector system.
95 ! * sngl(aTrack.vec.w.r(2)), ! direc. cos.y
96 ! * sngl(aTrack.vec.w.r(3)), ! direc. cos.z
97 ! * sngl(aTrack.vec.coszenith) ! cos of zenith angle
98 ! endif
99 ! you may need in some case other information such as
100 ! aTrack.p.subcode ! sub code of the particle integer*2
101 ! aTrack.p.mass ! mass
102 ! aTrack.wgt ! weight of the particle (may not be 1. if
103  ! ThinSampling =T)
104 ! aTrack.p.fm.p(1) ! momentum x component. Note. Momentum is
105 ! given in the Earth xyz system.
106 
107 ! aTrack.p.fm.p(2) ! y
108 ! aTrack.p.fm.p(3) ! z
109 
Definition: Ztrack.h:44
Here is the caller graph for this function:

◆ chooktrace()

subroutine chooktrace ( )

Definition at line 275 of file chook.f.

References ccoordfortr(), charge, code, p, and r.

Referenced by cputtrinfo().

275  implicit none
276 
277 #include "Ztrack.h"
278 #include "Ztrackp.h"
279 #include "Ztrackv.h"
280 #include "Zobs.h"
281 #include "Zobsv.h"
282 
283 
284 ! h1 = TrackBefMove.pos.height- ObsSites(NoOfSites).pos.height
285 ! h2 = MovedTrack.pos.height - ObsSites(NoOfSites).pos.height
286 
287  type(coord):: f, t
288 
289 
290 
291  real*8 xxx/-1.d37/, yyy/-1.d36/, zzz/1.d34/
292  integer kkk/-1000/, chg/-1000/
293  save xxx, yyy, zzz, kkk, chg
294 
295  if( movedtrack.p.charge .eq. 0 ) return
296 ! convert coord.
297  call ccoordfortr( 21, f, t )
298 
299 
300  if(kkk .ne. movedtrack.p.code .or. f.r(1) .ne. xxx
301  * .or. f.r(2) .ne. yyy .or. f.r(3) .ne. zzz .or.
302  * chg .ne. movedtrack.p.charge ) then
303  if(xxx .ne. -1.d37) then
304 ! write(TraceDev, *)
305 ! write(TraceDev, *)
306  write(*, *)
307  write(*, *)
308  endif
309 ! write(TraceDev, '(4g16.8, i3,i3)')
310  write(*, '(4g12.4, i3,i3)')
311  * f.r(1), f.r(2), f.r(3), trackbefmove.t,
312  * trackbefmove.p.code, trackbefmove.p.charge
313 
314  endif
315 ! write(TraceDev, '(4g16.8,i3,i3)')
316  write(*, '(4g12.4,i3,i3)')
317  * t.r(1), t.r(2), t.r(3), movedtrack.t,
318  * movedtrack.p.code, movedtrack.p.charge
319 
320  xxx = t.r(1)
321  yyy = t.r(2)
322  zzz = t.r(3)
323  kkk = movedtrack.p.code
324  chg = movedtrack.p.charge
subroutine ccoordfortr(how, f, t)
Definition: cputTrInfo.f:119
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz r
Definition: ZavoidUnionMap.h:1
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p charge
Definition: ZavoidUnionMap.h:1
nodes t
Definition: Zcoord.h:43
dE dx *! Nuc Int sampling table f
Definition: cblkMuInt.h:130
Here is the call graph for this function:
Here is the caller graph for this function:

◆ time()

subroutine time ( integer  xxx)

Definition at line 5 of file chook.f.

Referenced by __mknrfai.f__(), __mknrfaifromdat.f__(), __reduceeachsize.f__(), __reducesize.f__(), kdcmjd(), kmjd(), kmjdym(), ksided(), and ksidet().

5  integer xxx
6  xxx = 1
Here is the caller graph for this function: