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 c1by1
 
subroutine embedas
 
subroutine cmove_c_stack
 

Function/Subroutine Documentation

◆ c1by1()

subroutine c1by1 ( )

Definition at line 367 of file chookFlesh.f.

References asflag, c, cinitstack(), cmove_c_stack(), embedas(), false, p, and true.

Referenced by chookbgevent().

367  implicit none
368 #include "Zprivate.h"
369 #include "Ztrack.h"
370 #include "Ztrackv.h"
371 
372  character*100 msg
373 
374  call cinitstack ! empty the stack
375 
376  if( topofnode ) then
377  read(mdev) nooflowe, p
378  if( p.asflag .eq. -1 .and. observeas ) then
379  call embedas
380  endif
381  nlowcounter = 0
382  if( nooflowe .eq. -1 ) then
383  realend = .true.
384  realbegin = .true.
385  return ! ************
386  endif
387  endif
388 
389  realbegin = .false.
390  realend = .false.
391 
392 
393  if( nlowcounter .eq. nooflowe ) then
394  topofnode =.true.
395  return
396  endif
397 
398  topofnode = .false.
399 ! still not the end of 1 event
400 
401  read(mdev) c
402 
403  nlowcounter = nlowcounter + 1
404  call cmove_c_stack ! move c into stack
405 
subroutine embedas
Definition: chookFlesh.f:409
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
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 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 Zfirst Zfirst asflag
Definition: ZavoidUnionMap.h:1
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
subroutine cmove_c_stack
Definition: chookFlesh.f:429
dE dx *! Nuc Int sampling table c
Definition: cblkMuInt.h:130
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cbegin1ev()

subroutine cbegin1ev ( integer  nomore)

Definition at line 67 of file chookFlesh.f.

References cgethes(), charge, cinitracking(), cmkincident(), cobshes(), code, cqincident(), cresettimer(), depth, e, false, p, r, subcode, and x.

Referenced by chookbgevent().

67  implicit none
68 #include "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
84  type(track)::zsave
85  type(coord)::angle
86 
87  integer i
88  integer seed(2)
89  integer cumnum, num, jeof, fin
90  read( mdev, end=1000 ) cumnum, num, seedsave, zfirst
91 
92  eventsintherun = eventsintherun + 1
93  eventno = eventno + 1
94 ! get random seed at skelton making; this can work
95 ! if seed file is supplied
96 ! call creadSeed(SeedSave, EventNo, jeof)
97 ! if( jeof .ne. 0 ) goto 1000
98 
99 ! reset the seed.
100  call rnd1r(seedsave)
101 
102 ! next incident; confirmed to be the same one as preserved one
103  call cmkincident(incident, fin)
104 
105  if(fin .ne. 0 ) goto 1000
106  zsave = zfirst ! save; this is reset in next
107  call cinitracking( incident )
108 ! set first interaction pos
109  zfirst = zsave
110  call cresettimer(zfirst)
111 
112  realbegin = .false.
113 
114 ! do your own init for a one event here
115 ! ==========================================================
116  call cqincident( incident, angle)
117  do i = 1, noofsites
118  write(*, 999)
119  * sngl(obssites(i).pos.depth),
120  * eventno,
121  * incident.p.code,
122  * incident.p.subcode,
123  * incident.p.charge,
124  * incident.p.fm.e,
125  * -angle.r(1),
126  * -angle.r(2),
127  * -angle.r(3)
128  999 format(f10.3,i9,3i4,e15.5,3(1x,f12.8))
129  enddo
130 
131 ! ==========================================================
132 !
133 
134  call cgethes(mdev) ! get high energy ptlcs
135  call cobshes ! imitate their observation
136  nomore = 0
137  return
138 
139  1000 continue
140  nomore = 1
*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 cqincident(incident, AngleAtObs)
Definition: cmkIncident.f:486
dE dx *! Nuc Int sampling table e
Definition: cblkMuInt.h:130
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz r
Definition: ZavoidUnionMap.h:1
nodes i
Definition: Ztrack.h:44
real(8), dimension(:,:,:,:), allocatable, save num
Definition: chook.f:40
subroutine cmkincident(incident, fin)
Definition: cmkIncident.f:5
********************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 cgethes(from)
Definition: chookFlesh.f:322
subroutine cinitracking(incident)
Definition: ciniTracking.f:2
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p charge
Definition: ZavoidUnionMap.h:1
subroutine cresettimer(aTrack)
Definition: ctracking.f:302
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
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 subcode
Definition: ZavoidUnionMap.h:1
subroutine cobshes
Definition: chookFlesh.f:335
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cgethes()

subroutine cgethes ( integer  from)

Definition at line 322 of file chookFlesh.f.

References o.

Referenced by __randomsel.f__(), __ranseeascii.f__(), __reanal.f__(), __seeascii.f__(), __select.f__(), and cbegin1ev().

322  implicit none
323 #include "Zprivate.h"
324  integer from
325 
326  integer i
327 
328  read(from) np
329  do i = 1, np
330  read(from) o(i)
331  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
Here is the caller graph for this function:

◆ chookbgevent()

subroutine chookbgevent ( )

Definition at line 49 of file chookFlesh.f.

References c1by1(), cbegin1ev(), cerrormsg(), and true.

49  implicit none
50 #include "Zprivate.h"
51 
52 
53  integer nomore
54  if( realbegin ) then
55  call cbegin1ev( nomore )
56  if( nomore .eq. 1) then
57  call cerrormsg('all events are fleshed', 1)
58  stop !!!!!!!!!!!!
59  endif
60  topofnode = .true.
61  endif
62  call c1by1
63 
64 
subroutine cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
subroutine cbegin1ev(nomore)
Definition: chookFlesh.f:67
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
subroutine c1by1
Definition: chookFlesh.f:367
Here is the call graph for this function:

◆ chookbgrun()

subroutine chookbgrun ( )

Definition at line 11 of file chookFlesh.f.

References cgetfname(), cprintobs(), cprintprim(), cquhookc(), cquhooki(), cwriteparam(), and true.

11  implicit none
12 #include "Zmanagerp.h"
13 #include "Zprivate.h"
14 
15  real*8 temp
16  character*100 msg
17  integer klena
18 ! ==================================================
19 
20  integer seed(2)
21 ! ==================================================
22 
23  eventno = 0
24  realbegin = .true.
25  topofnode = .true.
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 memo
36  call cgetfname(msg, mskel) ! add host name etc if needed
37 
38  open(mdev, file=mskel(1:klena(mskel)), form='unformatted',
39  * status='old' )
40 
subroutine cgetfname(fnin, fn)
Definition: copenf.f:275
subroutine cprintobs(io)
Definition: cprintObs.f:2
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
subroutine cprintprim(out)
Definition: cprintPrim.f:3
subroutine cwriteparam(io, force)
Definition: cwriteParam.f:4
real(4), dimension(:), allocatable, save temp
Definition: cNRLAtmos.f:29
integer function klena(cha)
Definition: klena.f:20
subroutine cquhooki(i, iv)
Definition: cqUHookr.f:15
subroutine cquhookc(i, cv)
Definition: cqUHookr.f:28
Here is the call graph for this function:

◆ chookeint()

subroutine chookeint ( integer  never)

Definition at line 297 of file chookFlesh.f.

297  implicit none
298  integer never ! input & output
299  never = 1

◆ chookenevent()

subroutine chookenevent ( )

Definition at line 206 of file chookFlesh.f.

References cfintracking().

206 
207  implicit none
208 #include "Zprivate.h"
209 #include "Ztrack.h"
210 #include "Ztrackv.h"
211 #include "Zobs.h"
212 #include "Zobsp.h"
213 #include "Zobsv.h"
214 
215  integer i
216 
217  if(realend) then
218  call cfintracking
219 ! real end of 1 event; if you need to do some here is
220 ! the place
221 ! ========================================================
222 
223  if(observeas) then
224 ! electron size in B approx.
225  do i = 1, noofassites
226  write(*, *) asobssites(i).age, asobssites(i).esize
227  enddo
228  endif
229 
230 
231 
232 ! ========================================================
233 !
234  else
235 ! there is still low energy skeleton ptcls
236 ! nothing to do here
237  endif
238 
nodes i
subroutine cfintracking
Definition: cfinTracking.f:2
Here is the call graph for this function:

◆ chookenrun()

subroutine chookenrun ( )

Definition at line 246 of file chookFlesh.f.

References cprintstatus().

246  implicit none
247 #include "Zprivate.h"
248 ! =========================================================
249 
250 ! =========================================================
251  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 306 of file chookFlesh.f.

306  implicit none
307  integer never ! input & output
308  never = 1

◆ chooknepint()

subroutine chooknepint ( integer  never)

Definition at line 315 of file chookFlesh.f.

315  implicit none
316  integer never ! input & output
317  never = 1

◆ chookobs()

subroutine chookobs ( type(track aTrack,
integer  id 
)

Definition at line 148 of file chookFlesh.f.

References code, kneue, kneumu, and p.

148 !
149 ! Note that every real variable is in double precision so
150 ! that you may output it in sigle precision to save the memory.
151 ! In some cases it is essential to put it in sigle (say,
152 ! for gnuplot).
153 !
154  implicit none
155 #include "Zcode.h"
156 #include "Ztrack.h"
157 #include "Zprivate.h"
158  integer id ! input. 2 ==> reached at an observation level
159 ! 1 ==> aTrack is going out from
160 ! outer boundery.
161 ! 2 ==> reached at an observation level
162 ! 3 ==> reached at inner boundery.
163  type(track)::atrack
164 !
165 ! For id =2, you need not output the z value, because it is always
166 ! 0 (within the computational accuracy).
167 !
168  if(id .eq. 2 .and. atrack.p.code .ne. kneumu .and.
169  * atrack.p.code .ne. kneue) then
170 
171 ! ===================================================
172 
173  if( atrack.p.code .le. 6 .and. atrack.p.code .ne. 3 ) then
174 ! write(*, 959)
175 ! * aTrack.where,
176 ! * aTrack.p.code,
177 ! * aTrack.p.charge,
178 ! * sngl( aTrack.p.fm.p(4) - aTrack.p.mass ),
179 ! * sngl( aTrack.pos.xyz.r(1) ),
180 ! * sngl( aTrack.pos.xyz.r(2) ) ,
181 ! * sngl( aTrack.vec.w.r(1) ),
182 ! * sngl( aTrack.vec.w.r(2) ),
183 ! * sngl( aTrack.vec.w.r(3) ),
184 ! * sngl( aTrack.vec.coszenith )
185 ! 959 format(3i3,f12.3,2f16.6,4(1x,f12.8))
186  endif
187 
188 ! ===================================================
189 
190 ! write(*,'(4i5, g15.4,g15.3)')
191 ! * aTrack.where, aTrack.p.code, aTrack.p.subcode,
192 ! * aTrack.p.charge, sngl( aTrack.t ),
193 ! * sngl( aTrack.p.fm.p(4) - aTrack.p.mass)
194 ! * sngl( aTrack.pos.xyz.r(1) ), sngl( aTrack.pos.xyz.r(2) ),
195 ! * sngl( aTrack.vec.w.r(1) ), sngl(aTrack.vec.w.r(2) ),
196 ! * sngl(aTrack.vec.w.r(3) ),
197 ! * sngl(aTrack.vec.coszenith)
198 
199  endif
Definition: Ztrack.h:44
max ptcl codes in the kneue
Definition: Zcode.h:2
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
*Zfirst p fm *Zfirst p Zfirst p code
Definition: ZavoidUnionMap.h:1
max ptcl codes in the kneumu
Definition: Zcode.h:2

◆ chooktrace()

subroutine chooktrace ( )

Definition at line 262 of file chookFlesh.f.

References height.

262  implicit none
263 
264 #include "Ztrack.h"
265 #include "Ztrackv.h"
266 #include "Ztrackp.h"
267 #include "Zobs.h"
268 #include "Zobsv.h"
269 
270  real*4 h1, h2
271 !
272 ! Every time a particle is moved in the atmosphere, this routine is called,
273 ! if trace > 100
274 ! For a one track segment,
275 ! TrackBefMove has track information at the beginning of the segment.
276 ! MoveTrack has track information at the end of the segment.
277 !
278 ! You can know the information a track contains in the
279 ! chookObs routine. (Note however, no conversion of coordinate
280 ! has been done. The values are in the Earth xyz system.)
281 ! Besides quantities explained there, you can use, for a given 'track'
282 !
283 ! atrack.pos.xyz.x, atrack.pos.xyz.y, atrack.pos.xyz.z (x,y.z)
284 ! atrack.pos.radiallen (distance from the center of the earth)
285 ! atrack.pos.depth (vertical depth)
286 ! atrack.pos.height (vertical heigth from sea level)
287 !
288 
289  h1 = trackbefmove.pos.height- obssites(noofsites).pos.height
290  h2 = movedtrack.pos.height - obssites(noofsites).pos.height
291 
*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

◆ cmove_c_stack()

subroutine cmove_c_stack ( )

Definition at line 429 of file chookFlesh.f.

References asflag, c, charge, code, colheight, cpush(), cresetdirec(), depth, height, mass, p, r, radiallen, subcode, sys, t, wgt, and xyz.

Referenced by c1by1().

429  implicit none
430 
431 #include "Zprivate.h"
432 #include "Ztrack.h"
433 #include "Zearth.h"
434 
435  type(track)::atrack
436 !
437 ! a child of the current parent is moved to stack
438 ! as a track info.
439 !
440  atrack.pos.xyz.r(1) = p.posx
441  atrack.pos.xyz.r(2) = p.posy
442  atrack.pos.xyz.r(3) = p.posz
443  atrack.pos.depth = p.depth
444  atrack.pos.height = p.height
445  atrack.pos.colheight = p.colheight
446  atrack.t = p.atime
447 
448  atrack.where = p.where
449 
450  atrack.p.code = c.code
451  atrack.p.subcode = c.subcode
452  atrack.p.charge = c.charge
453  atrack.p.fm.p(1) = c.fm(1)
454  atrack.p.fm.p(2) = c.fm(2)
455  atrack.p.fm.p(3) = c.fm(3)
456  atrack.p.fm.p(4) = c.fm(4)
457  atrack.p.mass = c.mass
458 
459 ! --------------- next must be compute here
460 
461  atrack.pos.radiallen = eradius +atrack.pos.height
462  atrack.pos.xyz.sys = 'xyz'
463  atrack.vec.w.sys = 'xyz'
464  atrack.wgt = 1.0
465  atrack.asflag = 0
466 
467  call cresetdirec( atrack ) ! set vec.w and coszenith
468 
469  call cpush(atrack)
*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
*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 colheight
Definition: ZavoidUnionMap.h:1
*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
Definition: Ztrack.h:44
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz sys
Definition: ZavoidUnionMap.h:1
subroutine cresetdirec(aTrack)
Definition: cresetDirec.f:5
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
*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 Zfirst Zfirst asflag
Definition: ZavoidUnionMap.h:1
*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 height
Definition: ZavoidUnionMap.h:1
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p charge
Definition: ZavoidUnionMap.h:1
nodes t
*Zfirst p fm *Zfirst p mass
Definition: ZavoidUnionMap.h:1
subroutine cpush(a)
Definition: cstack.f:4
*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
*Zfirst p fm *Zfirst p Zfirst p Zfirst p subcode
Definition: ZavoidUnionMap.h:1
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p *Zfirst pos xyz Zfirst pos xyz *Zfirst pos radiallen
Definition: ZavoidUnionMap.h:1
dE dx *! Nuc Int sampling table c
Definition: cblkMuInt.h:130
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cobshes()

subroutine cobshes ( )

Definition at line 335 of file chookFlesh.f.

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

Referenced by cbegin1ev().

335  implicit none
336 #include "Zprivate.h"
337 #include "Ztrack.h"
338 !
339 ! memorized high energy showers at the skeleton making
340 ! time is put into the chookObs as if they are really observed
341  type(track)::atrack
342 
343  integer i
344 
345  do i = 1, np
346  atrack.where = o(i).where
347  atrack.p.code = o(i).code
348  atrack.p.subcode = o(i).subcode
349  atrack.p.charge = o(i).charge
350  atrack.t = o(i).atime
351  atrack.p.fm.p(4) = o(i).erg
352  atrack.p.mass = o(i).mass
353  atrack.pos.xyz.r(1) = o(i).x
354  atrack.pos.xyz.r(2) = o(i).y
355  atrack.vec.w.r(1) = o(i).wx
356  atrack.vec.w.r(2) = o(i).wy
357  atrack.vec.w.r(3) = o(i).wz
358  atrack.vec.coszenith = o(i).zenith
359  call chookobs(atrack, 2)
360  enddo
*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 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
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:
Here is the caller graph for this function:

◆ embedas()

subroutine embedas ( )

Definition at line 409 of file chookFlesh.f.

References cobas(), coszenith, depth, erg, height, p, radiallen, and wgt.

Referenced by c1by1().

409  implicit none
410 #include "Zprivate.h"
411 #include "Ztrack.h"
412 #include "Zearth.h"
413 
414  type(track)::el
415 
416  el.pos.depth = p.depth
417  el.vec.coszenith = p.coszenith
418  el.pos.radiallen = p.height + eradius
419  el.pos.height = p.height
420  el.p.fm.p(4) = p.erg
421  el.wgt = 1.0
422  call cobas(el)
*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
Definition: Ztrack.h:44
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
*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 *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 *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
subroutine cobas(el)
Definition: cobAS.f:9
*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:
Here is the caller graph for this function: