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

Go to the source code of this file.

Functions/Subroutines

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

Function/Subroutine Documentation

◆ chookbgevent()

subroutine chookbgevent ( )

Definition at line 37 of file chook.f.

References cqincident(), radiallen, x, xyz, y, and z.

37  implicit none
38 
39 #include "Ztrack.h"
40 #include "Zmanagerp.h"
41 
42  type(track):: inci
43  type(coord):: angle
44  real*8 rl
45 
46 ! write(*, *) ' bigin event generation'
47  call cqincident(inci, angle)
48  rl = inci.pos.radiallen
49 
50  write(*,'(6g15.4)')
51  * sngl(inci.vec.w.x), sngl(inci.vec.w.y), sngl(inci.vec.w.z),
52  * sngl(inci.pos.xyz.x/rl), sngl(inci.pos.xyz.y/rl),
53  * sngl(inci.pos.xyz.z/rl)
nodes z
subroutine cqincident(incident, AngleAtObs)
Definition: cmkIncident.f:486
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
latitude latitude this system is used *****************************************************************! type coord sequence union map real y
Definition: Zcoord.h:25
Definition: Zcoord.h:43
! 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 *Zfirst p *Zfirst pos xyz Zfirst pos xyz *Zfirst pos radiallen
Definition: ZavoidUnionMap.h:1
Here is the call graph for this function:

◆ chookbgrun()

subroutine chookbgrun ( )

Definition at line 13 of file chook.f.

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

13  implicit none
14 #include "Zmanagerp.h"
15 
16 ! If you feel writing the parameters on stderr is
17 ! a bother, comment out the next or
18 ! use other device than ErrorOut.
19 ! Also you may comment out all output routines below.
20 
21 !
22 ! namelist output
23  call cwriteparam(errorout, 0)
24 ! primary information
25  call cprintprim(errorout)
26 ! observation level information
27  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:

◆ chookeint()

subroutine chookeint ( integer  never)

Definition at line 190 of file chook.f.

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

◆ chookenevent()

subroutine chookenevent ( )

Definition at line 115 of file chook.f.

References cwriteseed().

115 
116  implicit none
117 #include "Ztrack.h"
118 #include "Ztrackv.h"
119 #include "Zobs.h"
120 #include "Zobsp.h"
121 #include "Zobsv.h"
122 #include "Zmanagerp.h"
123 
124  integer i
125  if(observeas) then
126 ! electron size in B approx.
127  write(*, *) (asobssites(i).esize, i=1, noofassites)
128 ! size weighted age
129  write(*, *) (asobssites(i).age, i=1, noofassites)
130  endif
131 ! ************ if you want to flesh this event later
132 ! you may keep the random no. seed by the following
133  if(job .eq. 'skeleton') then
134  call cwriteseed ! SeedFile
135  endif
nodes i
subroutine cwriteseed
Definition: cwriteSeed.f:15
Here is the call graph for this function:

◆ chookenrun()

subroutine chookenrun ( )

Definition at line 143 of file chook.f.

References cprintstatus().

143  implicit none
144  call cprintstatus ! if don't like, comment out
subroutine cprintstatus
Definition: cendRun.f:35
Here is the call graph for this function:

◆ chookgint()

subroutine chookgint ( integer  never)

Definition at line 219 of file chook.f.

219  implicit none
220 
221 #include "Ztrack.h"
222 #include "Ztrackv.h"
223 ! #include "Ztrackp.h"
224 
225  integer never ! input & output
226 
227 ! don't make never = 1, if you want to get
228 ! information after a gamma ray made interaction
229 ! if this is made non zero, this routine will never be called.
230 !
231 ! MovedTrack is the gamma that made interaction
232 ! Pwork contains produced particles.
233 ! Nproduced has the number of particles in Pwork
234 ! IntInfArray(ProcessNo) contains the type of interaction
235 !
236 ! default setting
237  never = 1
238 ! IntInfArray(ProcessNo).process will have one of
239 ! 'pair', 'comp', 'photoe' 'photop' 'mpair'
240 !

◆ chooknepint()

subroutine chooknepint ( integer  never)

Definition at line 247 of file chook.f.

247  implicit none
248 
249 #include "Ztrack.h"
250 #include "Ztrackv.h"
251 ! #include "Ztrackp.h"
252 
253  integer never ! input & output
254 
255 ! don't make never = 1, if you want to get
256 ! information after a non-e-g particle made interaction
257 ! if this is made non zero, this routine will never be called.
258 !
259 ! MovedTrack is the particle that made interaction
260 ! Pwork contains produced particles.
261 ! Nproduced has the number of particles in Pwork
262 ! IntInfArray(ProcessNo) contains the type of interaction
263 !
264 ! default setting
265  never = 1
266 !
267 ! IntInfArray(ProcessNo).process will have
268 ! 'col' or 'decay'

◆ chookobs()

subroutine chookobs ( type(track aTrack,
integer  id 
)

Definition at line 62 of file chook.f.

References charge, code, coszenith, and p.

62 !
63 ! Note that every real variable is in double precision so
64 ! that you may output it in sigle precision to save the memory.
65 ! In some cases it is essential to put it in sigle (say,
66 ! for gnuplot).
67 !
68  implicit none
69 #include "Ztrack.h"
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. 9) then
80 ! output typical quantities.
81 
82  write(*, *) id,
83  * atrack.where, ! observation level. integer*2. 1 is highest.
84  * atrack.p.code, ! ptcl code. integer*2.
85  * atrack.p.charge, ! charge, integer*2
86 ! * sngl(aTrack.t), ! relateive arrival time in nsec (NOT sec).
87  ! if TimeStructure is F, nonsense.
88 ! * sngl(aTrack.p.fm.p(4)-aTrack.p.mass) ! total energy in GeV.
89 ! * sngl(aTrack.pos.xyz.r(1)), sngl(aTrack.pos.xyz.r(2)), ! x, y in m
90 ! * sngl(aTrack.vec.w.r(1)), ! direc. cos.x in the current detector system.
91 ! * sngl(aTrack.vec.w.r(2)), ! direc. cos.y
92 ! * sngl(aTrack.vec.w.r(3)), ! direc. cos.z
93  * sngl(atrack.vec.coszenith) ! cos of zenith angle
94 ! * aTrack.wgt ! weight of the particle (may not be 1. if
95  ! ThinSampling =T)
96  endif
97 ! you may need in some case other information such as
98 ! aTrack.p.subcode ! sub code of the particle integer*2
99 ! aTrack.p.mass ! mass
100 
101 
102 ! aTrack.p.fm.p(1) ! momentum x component. Note. Momentum is
103 ! given in the Earth xyz system.
104 ! aTrack.p.fm.p(2) ! y
105 ! aTrack.p.fm.p(3) ! z
106 ! To convert the momentum into the observational
107 ! coordinate system, you may call
108 ! call cresetMom(aTrack)
Definition: Ztrack.h:44
********************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 *Zfirst pos xyz Zfirst pos xyz *Zfirst pos *Zfirst pos Zfirst pos *Zfirst pos *Zfirst Zfirst vec w *Zfirst vec w Zfirst vec coszenith
Definition: ZavoidUnionMap.h:1
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p charge
Definition: ZavoidUnionMap.h:1

◆ chooktrace()

subroutine chooktrace ( )

Definition at line 155 of file chook.f.

References height.

155  implicit none
156 
157 #include "Ztrack.h"
158 #include "Ztrackv.h"
159 #include "Ztrackp.h"
160 #include "Zobs.h"
161 #include "Zobsv.h"
162 
163  real*4 h1, h2
164 !
165 ! Every time a particle is moved in the atmosphere, this routine is called,
166 ! if trace > 100
167 ! For a one track segment,
168 ! TrackBefMove has track information at the beginning of the segment.
169 ! MoveTrack has track information at the end of the segment.
170 !
171 ! You can know the information a track contains in the
172 ! chookObs routine. (Note however, no conversion of coordinate
173 ! has been done. The values are in the Earth xyz system.)
174 ! Besides quantities explained there, you can use, for a given 'track'
175 !
176 ! atrack.pos.xyz.x, atrack.pos.xyz.y, atrack.pos.xyz.z (x,y.z)
177 ! atrack.pos.radiallen (distance from the center of the earth)
178 ! atrack.pos.depth (vertical depth)
179 ! atrack.pos.height (vertical heigth from sea level)
180 !
181 
182  h1 = trackbefmove.pos.height- obssites(noofsites).pos.height
183  h2 = movedtrack.pos.height - obssites(noofsites).pos.height
184 
*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