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

Go to the source code of this file.

Functions/Subroutines

subroutine chookeabsorbi (info)
 
subroutine chookeabsorb (a, b, dE, info)
 
subroutine chookeabsorbd (a, dE, info)
 
subroutine chookeabsorbb (a, info)
 
subroutine chookeabsorbc (a, n, p, info)
 
subroutine chookeabsorbw (a, n, p, Eout, diff)
 

Function/Subroutine Documentation

◆ chookeabsorb()

subroutine chookeabsorb ( type(track a,
type(track b,
real*8  dE,
integer  info 
)

Definition at line 51 of file chookEabsorb.f.

References wgt, and where.

51  implicit none
52 #include "Zmaxdef.h"
53 #include "Zobs.h"
54 #include "Ztrack.h"
55 #include "Zabsorb.h"
56 ! This is called when Eabsorb != 0 and
57 ! when a charged particle runs from a
58 ! to b and deposits energy dE (GeV) to the Air.
59 !
60  type(track):: a ! input. charged particle track info. at a.
61  type(track):: b ! input. charged particle track info. at b.
62  real*8 de ! input. energy deposit in GeV; no weight is applied yet
63  integer info ! in/out. not used now
64 
65  if(a.where .ge. 1) then
66  debydedx(a.where)= debydedx(a.where) + de*a.wgt
67  endif
Definition: Ztrack.h:44
real(4), save a
Definition: cNRLAtmos.f:20
real(4), save b
Definition: cNRLAtmos.f:21
*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 where
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 *Zfirst wgt
Definition: ZavoidUnionMap.h:1

◆ chookeabsorbb()

subroutine chookeabsorbb ( type(track a,
integer  info 
)

Definition at line 137 of file chookEabsorb.f.

References coszenith, false, mass, p, true, and wgt.

137  implicit none
138 #include "Zmaxdef.h"
139 #include "Zcode.h"
140 #include "Ztrack.h"
141 #include "Ztrackp.h"
142 #include "Ztrackv.h"
143 #include "Zobs.h"
144 #include "Zobsp.h"
145 #include "Zobsv.h"
146 #include "Zabsorb.h"
147 ! This is called when Eabsorb(1) !=0 and
148 ! a particle crosses an observation level
149 ! info=2: normal observation level
150 ! =1: upper boundary (whcih is equal to or higher than the injection
151 ! height)
152 ! =3: lower boundary (which is equal to or lower than the last
153 ! observation depth).
154 !
155  type(track):: a ! input. a particle that croses the observation level
156  integer info ! input. see above
157 
158  integer code
159  integer lv
160  logical count
161 
162  count =.false.
163  if(info .eq. 2 .and. a.where .eq. eabsorb(2) ) then
164 ! Eabsorb(2) is the layer number where the user want to
165 ! take sum of particle energy reaching there from above.
166 ! ptcl comes to the specified level OR
167 ! upper boundary. This condition neglect
168 ! ptcles reaching the real lower boundary
169 ! (if Eabosrb(2) is not NoOfSites+1)
170  if( a.vec.coszenith .gt. 0.) then
171 ! if info=2, this is to count energy reaching
172 ! the level from above, we discard going up ptcls
173 ! (but it may come down, so some over count may happen)
174  count = .true.
175  lv = 1
176  endif
177  elseif( info .eq. 1 ) then
178  lv = 2 ! escape to space
179  count = .true.
180  endif
181 !
182 !
183  if(count) then
184  code = a.p.code
185 ! for other ptcls than g,e,mu, pi, K, N, use 7
186  if(code .gt. 7) code=7
187 ! at the last layer we see sum of the particle energy
188 ! what energy we should use here is somewhat annoying
189 ! point. We use total energy here.
190  if(lv .eq. 1) then
191 ! Ecrash(code) = Ecrash(code) + a.p.fm.p(4)*a.wgt
192  ecrash(code) = ecrash(code) + (a.p.fm.p(4)-a.p.mass)*a.wgt
193  else
194 ! Espace(code) = Espace(code) + a.p.fm.p(4)*a.wgt
195  espace(code) = espace(code) + (a.p.fm.p(4)-a.p.mass)*a.wgt
196  endif
197  endif
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
*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
real(4), save a
Definition: cNRLAtmos.f:20
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
*Zfirst p fm *Zfirst p mass
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 *Zfirst wgt
Definition: ZavoidUnionMap.h:1

◆ chookeabsorbc()

subroutine chookeabsorbc ( type(track a,
integer  n,
type(ptcl), dimension(n p,
integer  info 
)

Definition at line 200 of file chookEabsorb.f.

References chookeabsorbw(), masn, and masp.

200  use modxsecmedia
201  implicit none
202 #include "Zmaxdef.h"
203 #include "Zcode.h"
204 #include "Zmass.h"
205 #include "Zobs.h"
206 #include "Ztrack.h"
207 #include "Ztrackv.h"
208 #include "Zabsorb.h"
209 
210  type(track):: a ! input. incident particle track
211  ! that made the collision
212  integer n ! input. number of procuded ptcls in the collision
213  type(ptcl):: p(n) ! input. produced ptpcls.
214  integer info ! input. not used now.
215 
216  real*8 eout, diff, reldiff, ein
217  real*8 diff1, diff2, ein1, ein2
218  integer i
219 ! We check conservation above this energy (GeV).
220  real*8 ebig/5.d3/
221  save
222 ! since target is not well known and nucleon there
223 ! has Fermi momentum, we simply assume rest mass.
224 ! For E>5TeV, Ar mass ~40GeV/5000 < 4/500 < 1 %
225 ! So we can see the conservation neglecting mass term
226 !
227  if( a.p.fm.p(4) .gt. ebig ) then
228  ein1 = a.p.fm.p(4) + masn*(targetnucleonno-targetprotonno) +
229  * masp*targetprotonno
230  ein2 = a.p.fm.p(4) + masp
231  eout = 0.
232  do i = 1, n
233  eout = eout + p(i).fm.p(4)
234  enddo
235 
236  diff1 = eout - ein1
237  diff2 = eout - ein2
238  ein = ein1
239  diff = diff1
240 ! take smaller diff one for Ein
241  if( abs(diff2) .lt. abs(diff1)) then
242  diff = diff2
243  ein = ein2
244  endif
245  reldiff = (eout/ein -1.)
246 
247  if( abs(reldiff) .gt. 0.02 ) then
248  call chookeabsorbw(a, n, p, eout, diff)
249  endif
250 
251  if( abs(diff) .gt. abs(maxebreak(1)) ) then
252  maxebreak(1) = diff
253  maxebreak(2) = reldiff
254  endif
255 
256  if( abs(reldiff) .gt. abs(maxrelebreak(1)) ) then
257  maxrelebreak(1) = reldiff
258  maxrelebreak(2) = diff
259  endif
260 
261  sumediff = sumediff + diff
262  sumabsediff = sumabsediff + abs(diff)
263  endif
subroutine chookeabsorbw(a, n, p, Eout, diff)
Definition: chookEabsorb.f:275
nodes i
masn
Definition: Zmass.h:5
block data cblkIncident data *Za1ry *HeightOfInj d3
Definition: cblkIncident.h:7
Definition: Ztrack.h:44
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
real(4), save a
Definition: cNRLAtmos.f:20
masp
Definition: Zmass.h:5
Definition: Zptcl.h:75
integer n
Definition: Zcinippxc.h:1
Here is the call graph for this function:

◆ chookeabsorbd()

subroutine chookeabsorbd ( type(track a,
real*8  dE,
integer  info 
)

Definition at line 70 of file chookEabsorb.f.

References charge, code, kelec, kkaon, kneue, kneumu, knuc, kphoton, p, regptcl, subcode, wgt, and where.

70  implicit none
71 #include "Zmaxdef.h"
72 #include "Zcode.h"
73 #include "Zobs.h"
74 #include "Ztrack.h"
75 #include "Zabsorb.h"
76 ! This is called when Eabsorb != 0 and
77 ! when a particle energy becomes < Emin (info=0) for
78 ! its traveling time becomes > limit or (info=2)
79 ! its angle relative to the 1ry becomes > limit.(info=4)
80 ! Whether this is called or not depends on the particle
81 ! and bit in Eabsorb. dE is energy that can be regarded
82 ! as absorbed in the Air. (GeV) eventually.
83 ! bit 1 is the LSB of Eabsorb.
84 !
85 ! bit particle
86 ! 1 photon: used to absorb shell energy at
87 ! photoelectric effect. This bit is not used in the Air.
88 ! 2 photon.
89 ! 3 e+/e-
90 ! 4 proton
91 ! 5 neutron
92 ! 6 anti-N
93 ! 7 decaying prtcl
94 ! 8 others
95 !
96 !***** Normally Eabsorb=6 (110 in bit pattarn) is enough.****
97 !
98 !
99  type(track):: a ! input. a particle that is < Emin
100  ! at birth
101  real*8 de ! input. energy which is supposed to be emitted by
102  ! the dying particle
103  integer info ! in/out. not used now.
104  if(a.where .ge. 1) then
105  if(a.p.code .eq. kneue .or. a.p.code .eq. kneumu) then
106  ! neutrino
107  debydeathneu(a.where) = debydeathneu(a.where) + de*a.wgt
108  elseif(a.p.code .eq. knuc .and. a.p.charge .eq. 0 .and.
109  * a.p.subcode .eq. regptcl ) then
110  ! low E nutron
111  debydeathnut(a.where) = debydeathnut(a.where) + de*a.wgt
112  else
113 ! next one and above are kept same as older versions for
114 ! compativilty
115  debydeath(a.where) = debydeath(a.where) + de*a.wgt
116 
117 ! we further put details
118  if(a.p.code .eq. kphoton ) then
119  debydeathg(a.where) = debydeathg(a.where) + de*a.wgt
120  elseif(a.p.code .eq. kelec ) then
121  debydeathe(a.where) = debydeathe(a.where) + de*a.wgt
122  elseif( a.p.code .le. kkaon ) then
123  debydeathmupik(a.where) = debydeathmupik(a.where)
124  * + de*a.wgt
125  elseif(a.p.code .eq. knuc .and. a.p.charge .eq. 1 ) then
126 ! p
127  debydeathp(a.where) = debydeathp(a.where) + de*a.wgt
128  else
129 ! pbar, nbar, heavy, others
130  debydeatho(a.where) = debydeatho(a.where) + de*a.wgt
131  endif
132  endif
133  endif
const int kphoton
Definition: Zcode.h:6
Definition: Ztrack.h:44
max ptcl codes in the kkaon
Definition: Zcode.h:2
max ptcl codes in the kelec
Definition: Zcode.h:2
max ptcl codes in the kneue
Definition: Zcode.h:2
max ptcl codes in the kseethru ! subcode integer regptcl
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
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code knuc
Definition: cblkHeavy.h:7
max ptcl codes in the kneumu
Definition: Zcode.h:2
*Zfirst p fm *Zfirst p Zfirst p Zfirst p *Zfirst p charge
Definition: ZavoidUnionMap.h:1
real(4), save a
Definition: cNRLAtmos.f:20
*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 where
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 *Zfirst wgt
Definition: ZavoidUnionMap.h:1
*Zfirst p fm *Zfirst p Zfirst p Zfirst p subcode
Definition: ZavoidUnionMap.h:1

◆ chookeabsorbi()

subroutine chookeabsorbi ( integer  info)

Definition at line 2 of file chookEabsorb.f.

2 ! init for each event
3  implicit none
4 #include "Zmaxdef.h"
5 #include "Zcode.h"
6 #include "Ztrack.h"
7 #include "Ztrackv.h"
8 #include "Zobs.h"
9 #include "Zobsp.h"
10 #include "Zobsv.h"
11 #include "Zabsorb.h"
12  integer info ! not used now
13  integer i
14  do i = 0, noofsites + 1
15 ! i = 0 and NoOfSite+1 will not be used now.
16  debydedx(i) = 0.
17  debydeath(i) = 0.
18  debydeathg(i) = 0.
19  debydeathe(i) = 0.
20  debydeathmupik(i) = 0.
21  debydeathneu(i) = 0.
22  debydeathp(i) = 0.
23  debydeathnut(i) = 0.
24  debydeatho(i) = 0.
25  enddo
26  do i = 1, 7
27 ! i for g,e,mu,pi,K, n, (neu and others)
28 ! Energy crashing to the given layer
29 ! default is the NoOfSites. Can be changed by Eabosrb(2)
30  ecrash(i) = 0.
31 ! Energy escaping to the upper bound( default is injection
32 ! height + 1m)
33  espace(i) = 0.
34  enddo
35 ! counter used for checking energy conservation
36 ! at the multiple producion.
37 ! negative value is generated energy is < ininial energy
38 ! positive value is generated energy is > initial energy
39  do i = 1, 2
40 ! i=1 for max Ebreak, i=2 Relative Break value for that event
41  maxebreak(i) = 0.
42 ! i=1 for max RelEgreak, i=2 E Break value for that event
43  maxrelebreak(i) = 0.
44  enddo
45 
46  sumediff = 0.
47  sumabsediff = 0.
48 
nodes i

◆ chookeabsorbw()

subroutine chookeabsorbw ( type(track a,
integer  n,
type(ptcl), dimension(n p,
real*8  Eout,
real*8  diff 
)

Definition at line 266 of file chookEabsorb.f.

References code, cqeventno(), depth, height, subcode, and wgt.

266  use modxsecmedia
267  implicit none
268 #include "Zmaxdef.h"
269 #include "Zcode.h"
270 #include "Zmass.h"
271 #include "Zobs.h"
272 #include "Ztrack.h"
273 #include "Ztrackv.h"
274 #include "Zabsorb.h"
275 
276  type(track):: a ! input. incident particle track
277  ! that made the collision
278  integer n ! input. number of procuded ptcls in the collision
279  type(ptcl):: p(n) ! input. produced ptpcls.
280  real*8 eout, diff
281  integer nevent, ntevent
282 
283 
284  call cqeventno(nevent, ntevent)
285 
286  write(0,*) "================= Warning: Ebreak ============="
287  write(0,*) " event #=", nevent, " 1ry Energy=", inci.p.fm.p(4)
288  write(0,*) "incident(not 1ry) code=", a.p.code,
289  * " subcode=", a.p.subcode, " Ein~", a.p.fm.p(4)
290  write(0,*) "Target(A,Z)=", targetnucleonno, targetprotonno
291  write(0,*) "No. of generted particles =", n
292  write(0,*) "Sum of outgoing ptcl Energy:Eout=", eout
293  write(0,*) "dE=(Eout-Ein)=", diff, " dE/Ein~",
294  * diff/a.p.fm.p(4)
295  write(0,*) "(Eout-Ein)/1ryE=", diff/inci.p.fm.p(4)
296  write(0,*) "Height=", a.pos.height," depth=",a.pos.depth/10.
297  write(0,*) " where=", a.where, " weight=", a.wgt
298  write(0,*) "================================================"
299 
*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 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
subroutine cqeventno(num, cumnum)
Definition: cqEventNo.f:3
real(4), save a
Definition: cNRLAtmos.f:20
Definition: Zptcl.h:75
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
*Zfirst p fm *Zfirst p Zfirst p Zfirst p subcode
Definition: ZavoidUnionMap.h:1
Here is the call graph for this function: