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

Go to the source code of this file.

Functions/Subroutines

subroutine chookbgrun
 
subroutine chookbgevent
 
subroutine cbegin1ev (nomore)
 
subroutine chookobs (aTrack, id)
 
subroutine chookenevent
 
subroutine chookenrun
 
subroutine chooktrace
 
subroutine chookeint (never)
 
subroutine chookgint (never)
 
subroutine chooknepint (never)
 
subroutine cgethes (from)
 
subroutine cobshes
 
subroutine cpushinci
 

Function/Subroutine Documentation

◆ cbegin1ev()

subroutine cbegin1ev ( integer  nomore)

Definition at line 67 of file chookFlesh.f.

References cgethes(), cinitracking(), cmkincident(), and cobshes().

67  implicit none
68 #include "../../SkelFlesh/Zprivate.h"
69 #include "Ztrack.h"
70 #include "Ztrackv.h"
71 #include "Ztrackp.h"
72 #include "Zobs.h"
73 #include "Zobsp.h"
74 #include "Zobsv.h"
75 #include "Zcode.h"
76 #include "Zmanager.h"
77 #include "Zmanagerp.h"
78 
79  integer nomore ! output. 0 still there are showers
80  ! 1 no more skeleton showers to be fleshed
81 ! event number, primary
82 
83  type(track):: incident, zsave
84  type(coord):: angle
85 
86  integer i
87  integer seed(2)
88  integer cumnum, num, jeof, fin
89  read( mdev, end=1000, err=999 ) cumnum, num, seedsave, zfirst
90 
91  eventsintherun = eventsintherun + 1
92  eventno = eventno + 1
93 ! reset the seed.
94  call rnd1r(seedsave)
95 ! next incident; confirmed to be the same one as preserved one
96  call cmkincident(incident, fin)
97  if(fin .ne. 0 ) goto 1000
98  zsave = zfirst ! save; this is reset in next
99  call cinitracking( incident )
100 ! set first interaction pos
101  zfirst = zsave
102 ! call cresetTimer(Zfirst)
103 
104 
105 
106 ! do your own init for a one event here
107 ! ==========================================================
108 
109 
110 ! ==========================================================
111 !
112 
113  call cgethes(mdev) ! get high energy ptlcs
114  call cobshes ! imitate their observation
115  nomore = 0
116  return
117 
118  1000 continue
119  nomore = 1
120  return
121  999 continue
122  write(0,*) ' Mdev read err'
123  stop 1111
nodes i
Definition: Ztrack.h:44
real(8), dimension(:,:,:,:), allocatable, save num
Definition: chook.f:40
subroutine cmkincident(incident, fin)
Definition: cmkIncident.f:5
subroutine cgethes(from)
Definition: chookFlesh.f:322
subroutine cinitracking(incident)
Definition: ciniTracking.f:2
Definition: Zcoord.h:43
subroutine cobshes
Definition: chookFlesh.f:335
Here is the call graph for this function:

◆ cgethes()

subroutine cgethes ( integer  from)

Definition at line 270 of file chookFlesh.f.

References o.

270  implicit none
271 #include "../../SkelFlesh/Zprivate.h"
272  integer from
273 
274  integer i
275 
276  read(from) np
277  do i = 1, np
278  read(from) o(i)
279  enddo
nodes i
struct ob o[NpMax]
Definition: Zprivate.h:34
integer maxbin nregion c minsave drx2 ! drawing region real maxdep integer maxpos integer from
Definition: Zfit.h:15

◆ chookbgevent()

subroutine chookbgevent ( )

Definition at line 51 of file chookFlesh.f.

References cbegin1ev(), cerrormsg(), and cpushinci().

51  implicit none
52 #include "../../SkelFlesh/Zprivate.h"
53 
54 
55  integer nomore
56  call cbegin1ev( nomore )
57  if( nomore .eq. 1) then
58  call cerrormsg('all events have been fleshed', 1)
59  stop !!!!!!!!!!!!
60  endif
61  call cpushinci
62 
63  call xbgevent
64  return
subroutine cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
subroutine cpushinci
Definition: chookFlesh.f:314
subroutine cbegin1ev(nomore)
Definition: chookFlesh.f:67
Here is the call graph for this function:

◆ chookbgrun()

subroutine chookbgrun ( )

Definition at line 15 of file chookFlesh.f.

References cerrormsg(), cgetfname(), copenfw2(), cprintobs(), cprintprim(), cquhookc(), cquhooki(), cwriteparam(), and xbgrun().

15  implicit none
16 #include "Zmanagerp.h"
17 #include "../../SkelFlesh/Zprivate.h"
18 
19  real*8 temp
20  character*100 msg
21  integer icon
22  integer i
23  eventno = 0
24 
25 ! namelist output
26  call cwriteparam(errorout, 0)
27 ! primary information
28  call cprintprim(errorout)
29 ! observation level information
30  call cprintobs(errorout)
31 
32  call cquhooki(1, mdev) ! get skeleton memo dev #
33  call cquhookc(1, msg) ! get file name for sekelton data
34  call cgetfname(msg, mskel) ! add host name etc if needed
35  call copenfw2(mdev, mskel, 2, icon)
36  if(icon .ne. 1) then
37  call cerrormsg(mskel,1)
38  call cerrormsg(' could not be opened',0)
39  endif
40 
41  call xbgrun
42  call ihist ! instanciate histogram
subroutine cgetfname(fnin, fn)
Definition: copenf.f:275
subroutine cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
subroutine cprintobs(io)
Definition: cprintObs.f:2
nodes i
subroutine cprintprim(out)
Definition: cprintPrim.f:3
subroutine cwriteparam(io, force)
Definition: cwriteParam.f:4
subroutine copenfw2(io, fnin, form, icon)
Definition: copenf.f:205
real(4), dimension(:), allocatable, save temp
Definition: cNRLAtmos.f:29
subroutine cquhooki(i, iv)
Definition: cqUHookr.f:15
subroutine cquhookc(i, cv)
Definition: cqUHookr.f:28
subroutine xbgrun
Definition: interface.f:10
Here is the call graph for this function:

◆ chookeint()

subroutine chookeint ( integer  never)

Definition at line 245 of file chookFlesh.f.

245  implicit none
246  integer never ! input & output
247  never = 1

◆ chookenevent()

subroutine chookenevent ( )

Definition at line 173 of file chookFlesh.f.

References cfintracking().

173 
174  implicit none
175 #include "Ztrack.h"
176 #include "Ztrackv.h"
177 #include "Zobs.h"
178 #include "Zobsp.h"
179 #include "Zobsv.h"
180 
181  integer i
182 
183 ! for Job ='newflesh', we must call cfinTracking ourselves.
184  call cfintracking
185 ! end of 1 event; if you need to do some here is
186 ! the place
187 
188  call xenevent
189 
190 
nodes i
subroutine cfintracking
Definition: cfinTracking.f:2
Here is the call graph for this function:

◆ chookenrun()

subroutine chookenrun ( )

Definition at line 198 of file chookFlesh.f.

References cprintstatus().

198  implicit none
199  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 254 of file chookFlesh.f.

254  implicit none
255  integer never ! input & output
256  never = 1

◆ chooknepint()

subroutine chooknepint ( integer  never)

Definition at line 263 of file chookFlesh.f.

263  implicit none
264  integer never ! input & output
265  never = 1

◆ chookobs()

subroutine chookobs ( type(track aTrack,
integer  id 
)

Definition at line 131 of file chookFlesh.f.

References rndc(), and wgt.

131 !
132 ! Note that every real variable is in double precision so
133 ! that you may output it in sigle precision to save the memory.
134 ! In some cases it is essential to put it in sigle (say,
135 ! for gnuplot).
136 !
137  implicit none
138 #include "Zcode.h"
139 #include "Ztrack.h"
140 
141 
142  integer id ! input. 2 ==> reached at an observation level
143 ! 1 ==> aTrack is going out from
144 ! outer boundery.
145 ! 2 ==> reached at an observation level
146 ! 3 ==> reached at inner boundery.
147  type(track):: atrack
148 !
149 !
150  integer n, i
151  real*8 eps, u
152 
153  if(atrack.wgt .gt. 1.) then
154  n=atrack.wgt
155  eps = atrack.wgt - n
156  call rndc(u)
157  if(u .lt. eps) then
158  n = n + 1
159  endif
160  else
161  n = 1
162  endif
163  do i = 1, n
164  call xobs(atrack, id)
165  enddo
166 
nodes i
Definition: Ztrack.h:44
subroutine rndc(u)
Definition: rnd.f:91
integer n
Definition: Zcinippxc.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 wgt
Definition: ZavoidUnionMap.h:1
Here is the call graph for this function:

◆ chooktrace()

subroutine chooktrace ( )

Definition at line 210 of file chookFlesh.f.

References height.

210  implicit none
211 
212 #include "Ztrack.h"
213 #include "Ztrackv.h"
214 #include "Ztrackp.h"
215 #include "Zobs.h"
216 #include "Zobsv.h"
217 
218  real*4 h1, h2
219 !
220 ! Every time a particle is moved in the atmosphere, this routine is called,
221 ! if trace > 100
222 ! For a one track segment,
223 ! TrackBefMove has track information at the beginning of the segment.
224 ! MoveTrack has track information at the end of the segment.
225 !
226 ! You can know the information a track contains in the
227 ! chookObs routine. (Note however, no conversion of coordinate
228 ! has been done. The values are in the Earth xyz system.)
229 ! Besides quantities explained there, you can use, for a given 'track'
230 !
231 ! atrack.pos.xyz.x, atrack.pos.xyz.y, atrack.pos.xyz.z (x,y.z)
232 ! atrack.pos.radiallen (distance from the center of the earth)
233 ! atrack.pos.depth (vertical depth)
234 ! atrack.pos.height (vertical heigth from sea level)
235 !
236 
237  h1 = trackbefmove.pos.height- obssites(noofsites).pos.height
238  h2 = movedtrack.pos.height - obssites(noofsites).pos.height
239 
*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

◆ cobshes()

subroutine cobshes ( )

Definition at line 283 of file chookFlesh.f.

References charge, chookobs(), code, coszenith, erg, false, mass, o, p, r, subcode, t, true, x, xyz, and y.

283  implicit none
284 #include "../../SkelFlesh/Zprivate.h"
285 #include "Ztrack.h"
286 !
287 ! memorized high energy showers at the skeleton making
288 ! time is put into the chookObs as if they are really observed
289  type(track):: atrack
290 
291  integer i
292  logical heobs ! if T, currently observing
293  common /zheobs/ heobs ! particles those obsrved at skeelton making time
294 
295  heobs = .true.
296  do i = 1, np
297  atrack.where = o(i).where
298  atrack.p.code = o(i).code
299  atrack.p.subcode = o(i).subcode
300  atrack.p.charge = o(i).charge
301  atrack.t = o(i).atime
302  atrack.p.fm.p(4) = o(i).erg
303  atrack.p.mass = o(i).mass
304  atrack.pos.xyz.r(1) = o(i).x
305  atrack.pos.xyz.r(2) = o(i).y
306  atrack.vec.w.r(1) = o(i).wx
307  atrack.vec.w.r(2) = o(i).wy
308  atrack.vec.w.r(3) = o(i).wz
309  atrack.vec.coszenith = o(i).zenith
310  call chookobs(atrack, 2)
311  enddo
312  heobs = .false.
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz r
Definition: ZavoidUnionMap.h:1
nodes i
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
block data cblkElemag data *AnihiE ! Eposi< 1 TeV, anihilation considered *X0/365.667/, ! radiation length of air in kg/m2 *Ecrit/81.e-3/, ! critical energy of air in GeV *MaxComptonE/1./, ! compton is considered below 1 GeV *MaxPhotoE/1.e-3/, ! above this, PhotoElectric effect neg. *MinPhotoProdE/153.e-3/, ! below 153 MeV, no gp --> hadrons ! scattering const not MeV *Knockon true
Definition: cblkElemag.h:7
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
struct ob o[NpMax]
Definition: Zprivate.h:34
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 *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 chookobs(aTrack, id)
Definition: chook.f:59
block data cblkElemag data *AnihiE ! Eposi< 1 TeV, anihilation considered *X0/365.667/, ! radiation length of air in kg/m2 *Ecrit/81.e-3/, ! critical energy of air in GeV *MaxComptonE/1./, ! compton is considered below 1 GeV *MaxPhotoE/1.e-3/, ! above this, PhotoElectric effect neg. *MinPhotoProdE/153.e-3/, ! below 153 MeV, no gp --> hadrons ! scattering const not MeV *Knockon ! knockon is considered Obsolete *PhotoProd false
Definition: cblkElemag.h:7
nodes t
*Zfirst p fm *Zfirst p mass
Definition: ZavoidUnionMap.h:1
! 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
Here is the call graph for this function:

◆ cpushinci()

subroutine cpushinci ( )

Definition at line 319 of file chookFlesh.f.

References charge, cinitstack(), code, cpush(), csortstack(), depth, mass, and p.

319  implicit none
320 #include "../../SkelFlesh/Zprivate.h"
321 #include "Ztrack.h"
322 #include "Ztrackv.h"
323  integer i
324 
325  type(track)::atrack
326 
327  call cinitstack ! empty the stack
328 
329  read(mdev) nooflowe
330  do i = 1, nooflowe
331  read(mdev) atrack
332 ! aTrack is already complete track so push it directly.
333  call cpush(atrack)
334  write(*,'(2i4,g13.4, g13.4)')
335  * atrack.p.code, atrack.p.charge,
336  * atrack.p.fm.p(4)-atrack.p.mass, atrack.pos.depth*0.1
337  enddo
338  stop
339 ! sort stack dscendent order
340  call csortstack
341 
*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 i
Definition: Ztrack.h:44
subroutine cinitstack
Definition: cstack.f:76
********************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
subroutine csortstack
Definition: cstack.f:102
*Zfirst p fm *Zfirst p mass
Definition: ZavoidUnionMap.h:1
subroutine cpush(a)
Definition: cstack.f:4
Here is the call graph for this function: