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

Go to the source code of this file.

Functions/Subroutines

subroutine csampnepintl
 
subroutine csampmuint (xs, mfp)
 
subroutine csamphadint (xs, mfp)
 
subroutine cknockonh
 

Function/Subroutine Documentation

◆ cknockonh()

subroutine cknockonh ( )

Definition at line 190 of file csampNEPIntL.f.

References cknockp(), csetintinf(), d0, and false.

Referenced by csampnepintl().

190  implicit none
191 #include "Zglobalc.h"
192 #include "Zcode.h"
193 #include "Ztrack.h"
194 #include "Ztrackv.h"
195 #include "Zelemagp.h"
196 #include "Zevhnv.h"
197  real*8 prob, path
198 ! knock on by non e+/e- charged ptcl
199  call cknockp(trackbefmove%p, prob, path) ! path in r%l
200  if(prob .gt. 0.d0) then
201  call csetintinf(path *x0, .false., 'knock')
202  else
203  call csetintinf(infty, .false., 'knock')
204  endif
subroutine csetintinf(lenOrThick, decay, procname)
Definition: csetIntInf.f:4
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
Definition: cblkEvhnp.h:5
subroutine cknockp(aPtcl, prob, path)
Definition: cKnock.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 ! knockon is considered Obsolete *PhotoProd false
Definition: cblkElemag.h:7
Here is the call graph for this function:
Here is the caller graph for this function:

◆ csamphadint()

subroutine csamphadint ( real(8), intent(out)  xs,
real(8), intent(out)  mfp 
)

Definition at line 153 of file csampNEPIntL.f.

References cgetxsec(), csetintinf(), false, and rndc().

Referenced by csampnepintl().

153  use modxsecmedia
154  implicit none
155 #include "Zglobalc.h"
156 #include "Ztrackp.h"
157 #include "Ztrack.h"
158 #include "Ztrackv.h"
159 #include "Zevhnp.h"
160 #include "Zevhnv.h"
161 #include "Zcmuint.h"
162  real(8),intent(out):: xs ! mb
163  real(8),intent(out):: mfp ! kg/m2
164 
165  real*8 prob, path, collkgram, uta, u
166  call cgetxsec(activemdl2, trackbefmove%p, media(1),
167  * xs, mfp)
168 ! for hadronic interaction
169 ! we can fix the fist col. point at the input
170 ! point when Freec=f
171  if(xs .eq. smallxs) then
172  collkgram = infty
173  elseif(.not. freec .and. zfirst%pos%depth .eq. 0. ) then
174 ! forced collision at the inut deth.
175  collkgram = 0.
176  elseif( xs .eq. largexs) then
177 ! say stopping pbar
178  collkgram = 0.
179  else
180 ! sample interaction length
181  call rndc(u)
182  collkgram=-mfp*log(u)
183  endif
184  call csetintinf(collkgram, .false., 'coll')
185 
subroutine rndc(u)
Definition: rnd.f:91
! constants thru Cosmos real ! if multiplied to deg radian Torad ! light velocity m sec ! infinty ! kg m2 *Togpcm2 g cm2 ! g cm2 *Tokgpm2 kg m2 ! cm *Tom m ! m *Tocm cm ! g cm3 *Tokgpm3 kg m3 ! kg m3 *Togpcm3 g cm3 ! sec *Tonsec nsec ! Tesla m ! Avogadro *A2deninv ! mfp *n * xs
Definition: Zglobalc.h:18
subroutine csetintinf(lenOrThick, decay, procname)
Definition: csetIntInf.f:4
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 cgetxsec(modelin, pj, media, xs, mfp)
Definition: cGetXsec.f:23
Here is the call graph for this function:
Here is the caller graph for this function:

◆ csampmuint()

subroutine csampmuint ( real*8  xs,
real*8  mfp 
)

Definition at line 84 of file csampNEPIntL.f.

References cmubrsmpp(), cmunsmpp(), cmuprsmpp(), csetintinf(), and false.

Referenced by csampnepintl().

84  use modxsecmedia
85  implicit none
86 #include "Zglobalc.h"
87 ! #include "Zcode.h"
88 #include "ZbpCnst.h"
89 #include "Ztrackp.h"
90 #include "Ztrack.h"
91 #include "Ztrackv.h"
92 ! #include "Zheavyp.h"
93 #include "Zelemagp.h"
94 #include "Zevhnp.h"
95 ! #include "Zevhnv.h"
96 #include "Zcmuint.h"
97  real*8 xs, mfp, u, csigma, s0
98 
99  real*8 prob, path, collkgram
100 
101  integer::i
102 
103  xs = smallxs
104  if(mupr .ge. 2 .and.
105  * trackbefmove%p%fm%p(4) .gt. mupremin) then
106  call cmuprsmpp(trackbefmove%p%fm%p(4), prob, path)
107 ! prob is /r.l path is in r.l
108 ! prob /r.l /X0 --> prob/ (kg/m2) *10 -> prob/(g/cm2)
109 ! = mb*4.138e-5
110 ! mb2pg = 1.e-27 * Avogn/A = 4.138e-5
111 ! xs =prob*10/X0/mb2pg = prob*10/X0*A/Avogn*1.e27
112 ! = prob/X0*A/Avogn*1.e28
113 ! = prob/X0*A*A2deninv
114 ! ( A2deninv = 1.d28/Avogn )
115 ! xs =max( prob/X0* A2deninv*TargetMassN, smallxs)
116 ! n mfp xs =1
117  xs =max( prob/mbtopx0, smallxs)
118  mfp = 1./(media(1)%mbtoPkgrm* xs)
119  collkgram = path * x0 ! kg/m^2
120  call csetintinf(collkgram, .false., 'mupair')
121  endif
122  if(mubr .ge. 2 .and.
123  * trackbefmove%p%fm%p(4) .gt. mubremin) then
124 
125  call cmubrsmpp(trackbefmove%p%fm%p(4), prob, path)
126  xs =max( prob/mbtopx0, smallxs)
127  mfp = 1./(media(1)%mbtoPkgrm* xs)
128  collkgram = path * x0 ! kg/m^2
129  call csetintinf(collkgram, .false., 'mubrem')
130  endif
131  if(muni .ge. 2 .and.
132  * trackbefmove%p%fm%p(4) .gt. munemin) then
133  call cmunsmpp(trackbefmove%p%fm%p(4), prob, path)
134  xs =max( prob/mbtopx0, smallxs)
135  media(1)%xs = xs ! for MuNI=3
136  mfp = 1./(media(1)%mbtoPkgrm* xs)
137  collkgram = path * x0 ! kg/m^2
138  if( xs .ne. smallxs .and.
139  * .not. freec .and. zfirst%pos%depth .eq. 0. ) then
140  collkgram = 0.
141  endif
142  call csetintinf(collkgram, .false., 'munuci')
143 
144 ! next is postponed after munuci is really selected
145 ! if( xs > smallxs .and. xs .ne. largexs ) then
146 ! call cfixTargetMuNI(media(1))
147 ! endif
148  endif
subroutine cmuprsmpp(Emu, prob, path)
Definition: cmuPrsmp.f:2
nodes i
subroutine cmubrsmpp(Emu, prob, path)
Definition: cmuBrsmp.f:2
subroutine cmunsmpp(Emu, prob, path)
Definition: cmuNsmp.f:2
! constants thru Cosmos real ! if multiplied to deg radian Torad ! light velocity m sec ! infinty ! kg m2 *Togpcm2 g cm2 ! g cm2 *Tokgpm2 kg m2 ! cm *Tom m ! m *Tocm cm ! g cm3 *Tokgpm3 kg m3 ! kg m3 *Togpcm3 g cm3 ! sec *Tonsec nsec ! Tesla m ! Avogadro *A2deninv ! mfp *n * xs
Definition: Zglobalc.h:18
subroutine csetintinf(lenOrThick, decay, procname)
Definition: csetIntInf.f:4
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
Here is the call graph for this function:
Here is the caller graph for this function:

◆ csampnepintl()

subroutine csampnepintl ( )

Definition at line 11 of file csampNEPIntL.f.

References cdecayleng(), cknockonh(), csamphadint(), csampmuint(), csetintinf(), kmuon, and true.

Referenced by csampintl().

11  use modxsecmedia
12  implicit none
13 #include "Zglobalc.h"
14 #include "Zcode.h"
15 #include "Ztrack.h"
16 #include "Ztrackv.h"
17 #include "Zevhnp.h"
18 
19 ! **************************************************
20 !
21  real*8 mfp, xs, length
22 
23 !
24 ! m.f.p (kg/m**2) = abn /xsec(mb)
25 #if defined (LOOPCHK)
26  integer ksave/0/, esave/-1./, ncount/0/
27  integer ka
28  save
29  ka = trackbefmove%p%code
30 
31  if(ksave .eq. ka .and. esave .eq.
32  * trackbefmove%p%fm%p(4)) then
33  ncount = ncount +1
34  if(ncount .gt. 10) then
35  write(0,*)' ncount=',ncount,
36  * ' ka=',ka, ' e=',esave, ' mass=',
37  * trackbefmove%p%mass
38  endif
39  else
40  ksave =ka
41  esave = trackbefmove%p%fm%p(4)
42  ncount =0
43  endif
44 !///////////////////
45 #endif
46 
47  call cdecayleng(trackbefmove, length)
48 
49  if(length .ne. infty) then
50  call csetintinf(length, .true., 'decay')
51  endif
52 ! nnb ddb rho phi omega ---> length=0 (instant decay)
53 ! or stopping mu pi etc -> length=0
54  if(length .gt. 0.) then
55  if(trackbefmove%p%charge .ne. 0) then
56 ! heavy (non e+/e-) knockon
57 ! if Freec and mu or had makes first hadronic
58 ! interaction, this call will be non-effective
59  call cknockonh
60  endif
61 ! non stopping-decay paticle
62  if( trackbefmove%p%code .eq. kmuon) then
63 ! muon; pair, brems, n.i
64  call csampmuint(xs, mfp)
65  else
66 ! hadronic collisions
67  call csamphadint(xs, mfp)
68 
69 ! fixing target will be done after collision
70 ! is really selected.
71 ! if(xs > smallxs .and. xs .ne. largexs) then
72 ! fix target
73 ! call cfixTarget(media(1))
74 ! elseif( xs == largexs ) then
75 ! call cfixTarget(media(1)) ! use big xs
76  ! to fix the target. pbar annihilation
77  ! probably A independent.
78 ! endif
79  endif
80  endif
subroutine cknockonh
Definition: csampNEPIntL.f:190
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
! constants thru Cosmos real ! if multiplied to deg radian Torad ! light velocity m sec ! infinty ! kg m2 *Togpcm2 g cm2 ! g cm2 *Tokgpm2 kg m2 ! cm *Tom m ! m *Tocm cm ! g cm3 *Tokgpm3 kg m3 ! kg m3 *Togpcm3 g cm3 ! sec *Tonsec nsec ! Tesla m ! Avogadro *A2deninv ! mfp *n * xs
Definition: Zglobalc.h:18
subroutine csampmuint(xs, mfp)
Definition: csampNEPIntL.f:84
subroutine csetintinf(lenOrThick, decay, procname)
Definition: csetIntInf.f:4
subroutine csamphadint(xs, mfp)
Definition: csampNEPIntL.f:153
subroutine cdecayleng(aTrack, length)
Definition: cdecayLeng.f:11
max ptcl codes in the kmuon
Definition: Zcode.h:2
Here is the call graph for this function:
Here is the caller graph for this function: