COSMOS v7.655  COSMOSv7655
(AirShowerMC)
seeSkel.f
Go to the documentation of this file.
1 !
2 ! This is to see the content of a smashed skeleton file
3 !
4 ! make clean
5 ! make -f seeSkel.mk
6 ! ./seeSkel$ARCH < paramDir/param0xx
7 ! will show you the energy of particles etc.
8 !
9 #include "../../cmain.f"
10 #include "../chookHybAS.f"
11 #include "../../ctemplCeren.f"
12 !
13 ! This is to see the smashed skeleton file content.
14 !
15 !
16  subroutine chookbgrun
17  implicit none
18 #include "Zmanagerp.h"
19 #include "../../SkelFlesh/Zprivate.h"
20 
21  real*8 temp
22  character*100 msg
23  integer icon
24  integer i
25  eventno = 0
26 
27 ! namelist output
28  call cwriteparam(errorout, 0)
29 ! primary information
30  call cprintprim(errorout)
31 ! observation level information
32  call cprintobs(errorout)
33 
34  call cquhooki(1, mdev) ! get skeleton memo dev #
35  call cquhookc(1, msg) ! get file name for sekelton data
36  call cgetfname(msg, mskel) ! add host name etc if needed
37  call copenfw2(mdev, mskel, 2, icon)
38  if(icon .ne. 1) then
39  call cerrormsg(mskel,1)
40  call cerrormsg(' could not be opened',0)
41  endif
42 
43 ! call xBgRun
44 
45  end
46 
47 ! *********************************** hook for Beginning of 1 event
48 ! * All system-level initialization for 1 event generation has been
49 ! * eneded at this moment.
50 ! * After this is executed, event generation starts.
51 ! *
52  subroutine chookbgevent
53  implicit none
54 #include "../../SkelFlesh/Zprivate.h"
55 
56 
57  integer nomore
58  call cbegin1ev( nomore )
59  if( nomore .eq. 1) then
60  call cerrormsg('all events have been fleshed', 1)
61  stop !!!!!!!!!!!!
62  endif
63  call cpushinci
64 
65 ! call xBgEvent
66  end
67  subroutine cbegin1ev(nomore)
68  implicit none
69 #include "../../SkelFlesh/Zprivate.h"
70 #include "Ztrack.h"
71 #include "Ztrackv.h"
72 #include "Ztrackp.h"
73 #include "Zobs.h"
74 #include "Zobsp.h"
75 #include "Zobsv.h"
76 #include "Zcode.h"
77 #include "Zmanager.h"
78 #include "Zmanagerp.h"
79 
80  integer nomore ! output. 0 still there are showers
81  ! 1 no more skeleton showers to be fleshed
82 ! event number, primary
83 
84  type(track):: incident, zsave
85  type(coord):: angle
86 
87  integer i
88  integer seed(2)
89  integer cumnum, num, jeof, fin
90  read( mdev, end=1000, err=999 ) cumnum, num, seedsave,zfirst
91 
92  write(*,*) ' Zfirst=',zfirst.pos.depth
93 
94  eventsintherun = eventsintherun + 1
95  eventno = eventno + 1
96 ! reset the seed.
97  call rnd1r(seedsave)
98 ! next incident; confirmed to be the same one as preserved one
99  call cmkincident(incident, fin)
100  if(fin .ne. 0 ) goto 1000
101  zsave = zfirst ! save; this is reset in next
102  call cinitracking( incident )
103 ! set first interaction pos
104  zfirst = zsave
105  call cresettimer(zfirst)
106 
107 
108 
109 ! do your own init for a one event here
110 ! ==========================================================
111 
112 
113 ! ==========================================================
114 !
115 
116  call cgethes(mdev) ! get high energy ptlcs
117  call cobshes ! imitate their observation
118  nomore = 0
119  return
120 
121  1000 continue
122  nomore = 1
123  return
124  999 continue
125  write(0,*) ' Mdev read err'
126  stop 1111
127  end
128 
129 ! ************************************ hook for observation
130 ! * One particel information is brought here by the system.
131 ! * All information of the particle is in aTrack
132 ! *
133  subroutine chookobs(aTrack, id)
134 !
135 ! Note that every real variable is in double precision so
136 ! that you may output it in sigle precision to save the memory.
137 ! In some cases it is essential to put it in sigle (say,
138 ! for gnuplot).
139 !
140  implicit none
141 #include "Zcode.h"
142 #include "Ztrack.h"
143  integer id ! input. 2 ==> reached at an observation level
144 ! 1 ==> aTrack is going out from
145 ! outer boundery.
146 ! 2 ==> reached at an observation level
147 ! 3 ==> reached at inner boundery.
148  type(track):: aTrack
149 !
150 !
151  write(*,*) 'o ', atrack.p.code, atrack.p.fm.p(4)
152 ! call xObs(aTrack, id)
153 
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 
171 ! for Job ='newflesh', we must call cfinTracking ourselves.
172  call cfintracking
173 ! end of 1 event; if you need to do some here is
174 ! the place
175 
176 ! call xEnEvent
177 
178 
179  end
180 
181 
182 ! ********************************* hook for end of a run
183 ! * all events have been created or time lacks
184 ! *
185  subroutine chookenrun
186  implicit none
187 ! call cprintStatus ! if don't like, comment out
188  end
189 ! ********************************* hook for trace
190 ! * This is called only when trace > 100
191 ! * User should manage the trace information here.
192 ! * If you use this, you may need some output for trace
193 ! * at the beginning of 1 event generatio and at the end of 1 event
194 ! * generation so that you can identfy each event.
195 ! *
196 ! *
197  subroutine chooktrace
198  implicit none
199 
200 #include "Ztrack.h"
201 #include "Ztrackv.h"
202 #include "Ztrackp.h"
203 #include "Zobs.h"
204 #include "Zobsv.h"
205 
206  real*4 h1, h2
207 !
208 ! Every time a particle is moved in the atmosphere, this routine is called,
209 ! if trace > 100
210 ! For a one track segment,
211 ! TrackBefMove has track information at the beginning of the segment.
212 ! MoveTrack has track information at the end of the segment.
213 !
214 ! You can know the information a track contains in the
215 ! chookObs routine. (Note however, no conversion of coordinate
216 ! has been done. The values are in the Earth xyz system.)
217 ! Besides quantities explained there, you can use, for a given 'track'
218 !
219 ! atrack.pos.xyz.x, atrack.pos.xyz.y, atrack.pos.xyz.z (x,y.z)
220 ! atrack.pos.radiallen (distance from the center of the earth)
221 ! atrack.pos.depth (vertical depth)
222 ! atrack.pos.height (vertical heigth from sea level)
223 !
224 
225  h1 = trackbefmove.pos.height- obssites(noofsites).pos.height
226  h2 = movedtrack.pos.height - obssites(noofsites).pos.height
227 
228  end
229 ! ********************* this is the hook called when
230 ! an electron made an interaction.
231 !
232  subroutine chookeint(never)
233  implicit none
234  integer never ! input & output
235  never = 1
236  end
237 
238 ! ********************* this is the hook called when
239 ! a gamma ray made an interaction.
240 !
241  subroutine chookgint(never)
242  implicit none
243  integer never ! input & output
244  never = 1
245  end
246 
247 ! ********************* this is the hook called when
248 ! non e-g particle made an interaction.
249 !
250  subroutine chooknepint(never)
251  implicit none
252  integer never ! input & output
253  never = 1
254  end
255 
256 
257  subroutine cgethes(from)
258  implicit none
259 #include "../../SkelFlesh/Zprivate.h"
260  integer from
261 
262  integer i
263 
264  read(from) np
265  do i = 1, np
266  read(from) o(i)
267  write(*,'(a, 4i3, 1pE11.3)' ) ' HE ',
268  * o(i).where, o(i).code, o(i).subcode, o(i).charge,
269  * o(i).erg
270  enddo
271  end
272 
273  subroutine cobshes
274  implicit none
275 #include "../../SkelFlesh/Zprivate.h"
276 #include "Ztrack.h"
277 !
278 ! memorized high energy showers at the skeleton making
279 ! time is put into the chookObs as if they are really observed
280  type(track):: aTrack
281 
282  integer i
283 
284  do i = 1, np
285  atrack.where = o(i).where
286  atrack.p.code = o(i).code
287  atrack.p.subcode = o(i).subcode
288  atrack.p.charge = o(i).charge
289  atrack.t = o(i).atime
290  atrack.p.fm.p(4) = o(i).erg
291  atrack.p.mass = o(i).mass
292  atrack.pos.xyz.r(1) = o(i).x
293  atrack.pos.xyz.r(2) = o(i).y
294  atrack.vec.w.r(1) = o(i).wx
295  atrack.vec.w.r(2) = o(i).wy
296  atrack.vec.w.r(3) = o(i).wz
297  atrack.vec.coszenith = o(i).zenith
298  call chookobs(atrack, 2)
299  enddo
300  end
301 
302 
303 ! wriete all low energy partilces in the skeleton.
304 
305  subroutine cpushinci
306  implicit none
307 #include "../../SkelFlesh/Zprivate.h"
308 #include "Zmaxdef.h"
309 #include "Ztrack.h"
310 #include "Ztrackv.h"
311 #include "Zstackv.h"
312  integer i, remain
313 
314  type(track):: aTrack
315  type(track):: tt(max_stack_size)
316 
317  call cinitstack ! empty the stack
318 
319  read(mdev) nooflowe
320  do i = 1, nooflowe
321  read(mdev) atrack
322  call cpush(atrack)
323  enddo
324 ! sort stack dscendent order
325  call csortstack
326  do i = 1, nooflowe
327  call cpop(tt(i), remain)
328  enddo
329  do i = nooflowe, 1, -1
330  write(*,* ) 'LE', tt(i).p.code, tt(i).p.fm.p(4)
331  enddo
332  call cinitstack ! empty the stack
333  end
subroutine cgetfname(fnin, fn)
Definition: copenf.f:275
*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 cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
subroutine cprintobs(io)
Definition: cprintObs.f:2
subroutine chookgint(never)
Definition: chook.f:191
subroutine cpushinci
Definition: chookFlesh.f:314
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz r
Definition: ZavoidUnionMap.h:1
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 cpop(a, remain)
Definition: cstack.f:38
subroutine cbegin1ev(nomore)
Definition: chookFlesh.f:67
subroutine cinitstack
Definition: cstack.f:76
subroutine cprintprim(out)
Definition: cprintPrim.f:3
subroutine cfintracking
Definition: cfinTracking.f:2
subroutine cmkincident(incident, fin)
Definition: cmkIncident.f:5
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
subroutine copenfw2(io, fnin, form, icon)
Definition: copenf.f:205
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
subroutine chooktrace
Definition: chook.f:275
subroutine cgethes(from)
Definition: chookFlesh.f:322
struct ob o[NpMax]
Definition: Zprivate.h:34
*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
latitude latitude this system is used *****************************************************************! type coord sequence union map real y
Definition: Zcoord.h:25
subroutine cinitracking(incident)
Definition: ciniTracking.f: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 coszenith
Definition: ZavoidUnionMap.h:1
float erg[maxp]
Definition: Zprivate.h:7
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p charge
Definition: ZavoidUnionMap.h:1
subroutine cresettimer(aTrack)
Definition: ctracking.f:302
subroutine chookobs(aTrack, id)
Definition: chook.f:59
subroutine chookbgevent
Definition: chook.f:39
subroutine cquhooki(i, iv)
Definition: cqUHookr.f:15
subroutine csortstack
Definition: cstack.f:102
nodes t
subroutine cquhookc(i, cv)
Definition: cqUHookr.f:28
Definition: Zcoord.h:43
*Zfirst p fm *Zfirst p mass
Definition: ZavoidUnionMap.h:1
subroutine chookbgrun
Definition: chook.f:15
subroutine cpush(a)
Definition: cstack.f:4
subroutine chookeint(never)
Definition: chook.f:162
! 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
subroutine cobshes
Definition: chookFlesh.f:335