COSMOS v7.655  COSMOSv7655
(AirShowerMC)
chook.f
Go to the documentation of this file.
1 #include "cmain.f"
2 #include "chookHybAS.f"
3 #include "ctemplCeren.f"
4  include "kxplsph.f"
5 ! *************************************** hook for Beginning of a Run
6 ! * At this moment, all (system-level) initialization for this run
7 ! * has been ended. After this routine is executed, the system goes into the
8 ! * event creation loop.
9 ! *
10  subroutine chookbgrun
11  implicit none
12 #include "Zmanagerp.h"
13 
14 
15 ! If you feel writing the parameters on stderr is
16 ! a bother, comment out the next or
17 ! use other device than ErrorOut.
18 ! Also you may comment out all output routines below.
19 
20 ! namelist output
21  call cwriteparam(errorout, 0)
22 ! primary information
23  call cprintprim(errorout)
24 ! observation level information
25  call cprintobs(errorout)
26  end
27 #if defined NEXT486
28 #define IMAG_P dimag
29 #elif defined PCLinux
30 #define IMAG_P dimag
31 #else
32 #define IMAG_P imag
33 #endif
34 
35 
36 ! *********************************** hook for Beginning of 1 event
37 ! * All system-level initialization for 1 event generation has been
38 ! * eneded at this moment.
39 ! * After this is executed, event generation starts.
40 ! *
41  subroutine chookbgevent
42  implicit none
43 #include "Zglobalc.h"
44 #include "Ztrack.h"
45 #include "Ztrackp.h"
46 #include "Zobs.h"
47 #include "Zobsp.h"
48 #include "Zobsv.h"
49 #include "Zincidentp.h"
50 
51  type(track):: primary
52  type(coord):: angle1ry
53 
54  common /zprivate/ primary, angle1ry
55  integer ndiscard
56  common /zprivate2/ ndiscard
57 
58 
59  integer icon
60  real*8 leng, xp, yp, zp, oa2, rmax, r
61  save rmax
62  data rmax/0.d0/
63 
64  if(rmax .eq. 0.d0) then
65  oa2 = imag_p(azimuth)/2.0
66  rmax = obssites(noofsites).pos.radiallen* oa2*torad
67  ndiscard = 0
68  endif
69 
70  call cqincident(primary, angle1ry)
71 ! see if the 1ry is directed outside of the
72 ! area covered by the injection area.
73  call kxplsph( primary.pos.xyz.r(1), primary.pos.xyz.r(2),
74  * primary.pos.xyz.r(3),
75  * primary.vec.w.r(1), primary.vec.w.r(2),
76  * primary.vec.w.r(3),
77  * obssites(noofsites).pos.radiallen,
78  * leng, icon )
79 
80 
81  if(icon .eq. 1) then
82  xp = primary.pos.xyz.r(1) + leng*primary.vec.w.r(1)
83  yp = primary.pos.xyz.r(2) + leng*primary.vec.w.r(2)
84  zp = primary.pos.xyz.r(3) + leng*primary.vec.w.r(3)
85  r = sqrt( (xp-obssites(noofsites).pos.xyz.r(1))**2 +
86  * (yp-obssites(noofsites).pos.xyz.r(2))**2 +
87  * (zp-obssites(noofsites).pos.xyz.r(3))**2 )
88  if(r .gt. rmax) icon = -1
89  endif
90  if(icon .ne. 1) then
91 ! clear the stack to discard this 1ry.
92  call cinitstack
93  ndiscard = ndiscard + 1
94  endif
95  end
96 
97 
98 ! ************************************ hook for observation
99 ! * One particle information is brought here by the system.
100 ! * All information of the particle is in aTrack
101 ! *
102  subroutine chookobs(aTrack, id)
103 !
104 ! Note that every real variable is in double precision so
105 ! that you may output it in sigle precision to save the memory.
106 ! In some cases it is essential to put it in sigle (say,
107 ! for gnuplot).
108 !
109  implicit none
110 #include "Ztrack.h"
111  integer id ! input. 1 ==> aTrack is going out from
112 ! outer boundery.
113 ! 2 ==> reached at an observation level
114 ! 3 ==> reached at inner boundery.
115  type(track):: aTrack
116 
117  type(track):: primary
118  type(coord):: angle1ry
119  common /zprivate/ primary, angle1ry
120 
121 
122 !
123 ! For id =2, you need not output the z value, because it is always
124 ! 0 (within the computational accuracy).
125 !
126  if(id .eq. 2 .and. atrack.p.code .ne. 7
127  * .and. atrack.p.code .ne. 8 ) then
128 ! output typical quantities.
129  write(*, '(3i5,1p,g14.6)')
130  * atrack.where, ! observation level. integer*2. 1 is highest.
131  * atrack.p.code, ! ptcl code. integer*2.
132  * atrack.p.charge, ! charge, integer*2
133 ! * sngl(aTrack.t), ! relateive arrival time in nsec (NOT sec).
134 ! ! if TimeStructure is F, nonsense.
135  * sngl( atrack.p.fm.p(4)-atrack.p.mass ) ! kinetic energy in GeV.
136 ! * sngl(aTrack.pos.xyz.r(1)), sngl(aTrack.pos.xyz.r(2)), ! x, y in m
137 ! * sngl(aTrack.pos.xyz.r(3)), ! z
138 ! * sngl(aTrack.vec.w.r(1)), ! direc. cos.x in the current detector system.
139 ! * sngl(aTrack.vec.w.r(2)), ! direc. cos.y
140 ! * sngl(aTrack.vec.w.r(3)), ! direc. cos.z
141 ! * sngl(aTrack.vec.coszenith), ! cos of zenith angle
142 ! * sngl(primary.vec.coszenith)
143  endif
144 ! you may need in some case other information such as
145 ! aTrack.p.subcode ! sub code of the particle integer*2
146 ! aTrack.p.mass ! mass
147 ! aTrack.wgt ! weight of the particle (may not be 1. if
148  ! ThinSampling =T)
149 ! aTrack.p.fm.p(1) ! momentum x component. Note. Momentum is
150 ! given in the Earth xyz system.
151 
152 ! aTrack.p.fm.p(2) ! y
153 ! aTrack.p.fm.p(3) ! z
154 
155  end
156 
157 ! *********************************** hook for end of 1 event
158 ! * At this moment, 1 event generation has been ended.
159 ! *
160  subroutine chookenevent
162  implicit none
163 #include "Ztrack.h"
164 #include "Ztrackv.h"
165 #include "Zobs.h"
166 #include "Zobsp.h"
167 #include "Zobsv.h"
168 
169  integer i
170  if(observeas) then
171 ! electron size in B approx.
172  write(*, *) (asobssites(i).esize, i=1, noofassites)
173 ! size weighted age
174  write(*, *) (asobssites(i).age, i=1, noofassites)
175  endif
176 
177  end
178 
179 
180 ! ********************************* hook for end of a run
181 ! * all events have been created or time lacks
182 ! *
183  subroutine chookenrun
184  implicit none
185  integer ndiscard
186  common /zprivate2/ ndiscard
187 
188  call cprintstatus
189  write(0, *) ' discarded primaries=', ndiscard
190 
191  end
192 ! ********************************* hook for trace
193 ! * This is called only when trace > 60
194 ! * User should manage the trace information here.
195 ! * If you use this, you may need some output for trace
196 ! * at the beginning of 1 event generatio and at the end of 1 event
197 ! * generation so that you can identfy each event.
198 ! *
199 ! *
200  subroutine chooktrace
201  implicit none
202 
203 #include "Ztrack.h"
204 #include "Ztrackv.h"
205 #include "Ztrackp.h"
206 #include "Zobs.h"
207 #include "Zobsv.h"
208 
209  real*4 h1, h2
210 !
211 ! Every time a particle is moved in the atmosphere, this routine is called,
212 ! if trace > 60.
213 ! For a one track segment,
214 ! TrackBefMove has track information at the beginning of the segment.
215 ! MoveTrack has track information at the end of the segment.
216 !
217 ! You can know the information a track contains in the
218 ! chookObs routine. (Note however, no conversion of coordinate
219 ! has been done. The values are in the Earth xyz system.)
220 ! Besides quantities explained there, you can use, for a given 'track'
221 !
222 ! atrack.pos.xyz.x, atrack.pos.xyz.y, atrack.pos.xyz.z (x,y.z)
223 ! atrack.pos.radiallen (distance from the center of the earth)
224 ! atrack.pos.depth (vertical depth)
225 ! atrack.pos.height (vertical heigth from sea level)
226 !
227 
228  h1 = trackbefmove.pos.height- obssites(noofsites).pos.height
229  h2 = movedtrack.pos.height - obssites(noofsites).pos.height
230 
231  end
232 ! ********************* this is the hook called when
233 ! an electron made an interaction.
234 !
235  subroutine chookeint(never)
236  implicit none
237 
238 #include "Ztrack.h"
239 #include "Ztrackv.h"
240 ! #include "Ztrackp.h"
241 
242  integer never ! input & output
243 
244 ! don't make never = 1, if you want to get
245 ! information after an electron made interaction
246 ! if this is made non zero, this routine will never be called.
247 !
248 ! MovedTrack is the electron that made interaction
249 ! Pwork contains produced particles.
250 ! Nproduced has the number of particles in Pwork
251 ! IntInfArray(ProcessNo) contains the type of interaction
252 !
253 ! default setting
254  never = 1
255 !
256 ! IntInfArray(ProcessNo).process will have one of
257 ! 'brems', 'mscat', 'bscat',or 'anihi'
258 !
259  end
260 
261 ! ********************* this is the hook called when
262 ! a gamma ray made an interaction.
263 !
264  subroutine chookgint(never)
265  implicit none
266 
267 #include "Ztrack.h"
268 #include "Ztrackv.h"
269 ! #include "Ztrackp.h"
270 
271  integer never ! input & output
272 
273 ! don't make never = 1, if you want to get
274 ! information after a gamma ray made interaction
275 ! if this is made non zero, this routine will never be called.
276 !
277 ! MovedTrack is the gamma that made interaction
278 ! Pwork contains produced particles.
279 ! Nproduced has the number of particles in Pwork
280 ! IntInfArray(ProcessNo) contains the type of interaction
281 !
282 ! default setting
283  never = 1
284 ! IntInfArray(ProcessNo).process will have one of
285 ! 'pair', 'comp', 'photoe' or 'photop'
286 !
287  end
288 
289 ! ********************* this is the hook called when
290 ! non e-g particle made an interaction.
291 !
292  subroutine chooknepint(never)
293  implicit none
294 
295 #include "Ztrack.h"
296 #include "Ztrackv.h"
297 ! #include "Ztrackp.h"
298 
299  integer never ! input & output
300 
301 ! don't make never = 1, if you want to get
302 ! information after a non-e-g particle made interaction
303 ! if this is made non zero, this routine will never be called.
304 !
305 ! MovedTrack is the particle that made interaction
306 ! Pwork contains produced particles.
307 ! Nproduced has the number of particles in Pwork
308 ! IntInfArray(ProcessNo) contains the type of interaction
309 !
310 ! default setting
311  never = 1
312 !
313 ! IntInfArray(ProcessNo).process will have
314 ! 'col' or 'decay'
315  end
316 
317 
subroutine cprintobs(io)
Definition: cprintObs.f:2
subroutine cqincident(incident, AngleAtObs)
Definition: cmkIncident.f:486
subroutine chookgint(never)
Definition: chook.f:191
subroutine kxplsph(x0, y0, z0, l, m, n, r, el, icon)
Definition: kxplsph.f:2
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
subroutine chookenrun
Definition: chook.f:147
Definition: Ztrack.h:44
subroutine chooknepint(never)
Definition: chook.f:219
subroutine cinitstack
Definition: cstack.f:76
subroutine cprintprim(out)
Definition: cprintPrim.f:3
subroutine chookenevent
Definition: chook.f:116
subroutine cwriteparam(io, force)
Definition: cwriteParam.f:4
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
subroutine chooktrace
Definition: chook.f:275
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
Definition: cblkEvhnp.h:5
*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
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p charge
Definition: ZavoidUnionMap.h:1
subroutine chookobs(aTrack, id)
Definition: chook.f:59
subroutine chookbgevent
Definition: chook.f:39
Definition: Zcoord.h:43
*Zfirst p fm *Zfirst p mass
Definition: ZavoidUnionMap.h:1
subroutine cprintstatus
Definition: cendRun.f:35
subroutine chookbgrun
Definition: chook.f:15
subroutine chookeint(never)
Definition: chook.f:162
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz *Zfirst pos radiallen
Definition: ZavoidUnionMap.h:1