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

Go to the source code of this file.

Functions/Subroutines

subroutine cdecayleng (aTrack, length)
 
subroutine cdecaywel (pin, g, x)
 

Function/Subroutine Documentation

◆ cdecayleng()

subroutine cdecayleng ( type(track aTrack,
real*8  length 
)

Definition at line 11 of file cdecayLeng.f.

References cgetctau(), d0, and rndc().

Referenced by csampnepintl().

11  implicit none
12 #include "Zglobalc.h"
13 #include "Ztrack.h"
14 #include "Ztrackv.h"
15 
16 
17 
18  type(track)::atrack ! input%a track of a decaying particle
19  real*8 length ! output. length to wthich the decay takes place (m).
20 
21  real*8 g, u, gbeta, dedt, dedtf, dedl, ctau, rho
22  real*8 a, x, p, gmin, ctaumax, pmin, cvh2den
23  type(fmom)::gb
24 
25  data gmin/200.d0/, ctaumax/50.d0/, pmin/10.d0/
26 
27  if(atrack%p%fm%p(4) .lt. atrack%p%mass) then
28  atrack%p%fm%p(4) = atrack%p%mass
29  endif
30 
31  call cgetctau(atrack%p, ctau)
32  if(ctau .eq. infty) then
33  length = infty
34  else
35  g = atrack%p%fm%p(4)/atrack%p%mass
36  if(g .gt. gmin) then
37  call rndc(u)
38  length = - ctau* g *log(u)
39  else
40  gbeta = sqrt(g**2-1.d0)
41 ! call cgetlf(aTrack.p, gb)
42 ! gbeta = sqrt(gb.p(1)**2 + gb.p(2)**2 + gb.p(3)**2)
43  if(atrack%p%charge .eq. 0 .or. ctau .lt. ctaumax) then
44  call rndc(u)
45  length = - ctau * gbeta * log(u)
46  elseif(fromepics) then
47 ! no need to consider energy loss.
48 ! this may not be good for rock of large length
49 ! In that case we must consider decay length
50 ! in Epics. (don't call cdecayLeng and manage
51 ! decay in Epics).
52  call rndc(u)
53  length = - ctau * gbeta * log(u)
54  else
55  call rndc(u)
56  length = - ctau * gbeta * log(u)
57 ! eloss consideration somethat wrong.
58 ! rho = cvh2den(aTrack.pos.height)
59 ! call cdedxInAir(aTrack.p, rho, dedt, dedtf) ! dedt in GeV/(kg/m^2)
60 ! dedl= dedt*rho ! GeV/m
61 ! a = dedl/aTrack.p.fm.p(4) ! 1/m
62 ! p =1.0d0/( a * ctau * g )
63 ! if( p .gt. pmin) then
64 ! call rndc(u)
65 ! length = - ctau* gbeta *log(u)
66 ! else
67 ! call cdecayWEL(p, g, x)
68 ! length =(1.0d0 - x/g)/a
69 ! if(length .lt. 0.) then
70 ! may happpen when a <<< 1.
71 ! length = 0.d0
72 ! endif
73 ! endif
74  endif
75  endif
76  endif
Definition: Ztrack.h:44
subroutine rndc(u)
Definition: rnd.f:91
Definition: Zptcl.h:72
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
Definition: cblkEvhnp.h:5
subroutine cgetctau(proj, ctau)
Definition: cgetctau.f:6
real *8 function cvh2den(z)
Definition: ciniSegAtoms.f:54
real(4), save a
Definition: cNRLAtmos.f:20
dE dx *! Nuc Int sampling table g
Definition: cblkMuInt.h:130
! 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
Here is the call graph for this function:
Here is the caller graph for this function:

◆ cdecaywel()

subroutine cdecaywel ( real*8  pin,
real*8  g,
real*8  x 
)

Definition at line 90 of file cdecayLeng.f.

References cerrormsg(), d0, e, rndc(), and true.

90  implicit none
91  real*8 pin ! input. see above. should be 0.1<pin<10.
92  real*8 g ! input. E0/m. 1<= g
93  real*8 x ! output. sampled x. decay length 'l' is related to this
94  ! by x=g(1-al) where a is dE/dl/E0 (/m).
95 !
96 ! Method:
97 ! If x > 5, we use p(x)=(2x)**p/x
98 ! x < 5, we use (2x)**p/x + 1/sqrt(2(x-1)) and rejection
99 ! To decide which side, we compare int(x=1 to 5) of p(x)dx and
100 ! int(x=5 to g) of (2x)**p/x
101 !
102 ! if g< 5, we use rejection method only.
103 !
104 ! log( int(x=1 to 5)) is approximated by 4-th order polynomial:
105 ! sum c_i p**i (i=0 to 4)
106 !
107 !
108 ! c0 .77099
109 ! c1 1.3470
110 ! c2 .12049
111 ! c3 -.57001E-02
112 !
113  real*4 int1, int2, ans, xm, tf, rf, p
114  real*8 u
115 
116  p = pin
117  if(p .gt. 10.) then
118  call cerrormsg('p> 10 for cdecayWEL', 0)
119  endif
120  if(g .gt. 5.) then
121  if(p .le. 0.1d0) then
122  ans = 0.771
123  else
124  ans =((-0.57001e-02*p + 0.12049 )*p+1.3470)*p
125  * +0.77099
126  endif
127  xm= 5.
128 ! int(1 to 5) of p(x)dx
129  int1 = exp(ans)
130 ! int(5 to g) of p(x)dx~ (2x)**p/xdx
131  int2 = 2.0**p/p * (g**p - xm**p)
132  else
133  int1 = 1. ! dummy value
134  int2 = 0. ! // so that int1 > int2
135  xm = g
136  endif
137  call rndc(u)
138  if(u .lt. int1/(int1+int2)) then
139 ! use rejection.
140 ! integral of 1/sqrt(2(x-1)) from 1 to xm
141  int1 = sqrt(2.0*(xm-1.0))
142 ! integral of (2x)**p/x from (1 to xm)
143  int2 = 2.0**p/p *(xm**p-1.0)
144 ! xm**p = 1.0
145  if(int1 .eq. 0. .and. int2 .eq. 0.) then
146  x = 1.0
147  return ! **********
148  endif
149 
150  do while (.true.)
151 !
152  call rndc(u)
153  if(u .lt. int1 /(int1+int2)) then
154 ! use dx/sqrt(2(x-1))
155  call rndc(u)
156  x = (u*int1)**2/2.0+1.0
157  else
158 ! use dx(2x)**p/x
159  call rndc(u)
160  x =( p*int2*u/2.0**p+ 1.)**(1./p)
161  endif
162  if(x .eq. 1.0) goto 10
163  call rndc(u)
164  tf = 1./(x-sqrt(x*x-1.0))**p/sqrt(x*x-1.0)
165  rf = (2.0*x)**p/x + 1.0/sqrt(2*(x-1.0))
166  if(u .lt. tf/rf) goto 10
167  enddo
168  10 continue
169  else
170 ! use (2x)**p/x dx
171  call rndc(u)
172  x =( p*int2*u/2.0**p+ xm**p)**(1./p)
173  endif
subroutine cerrormsg(msg, needrtn)
Definition: cerrorMsg.f:4
dE dx *! Nuc Int sampling table e
Definition: cblkMuInt.h:130
integer nfrac tf(nfrac) data frac/0.05d0
atmos%rho(atmos%nodes) **exp(-(z-atmos%z(atmos%nodes))/Hinf) elseif(z .lt. atmos%z(1)) then ans=atmos%rho(1) **exp((atmos%z(1) -z)/atmos%H(1)) else call kdwhereis(z, atmos%nodes, atmos%z, 1, i) a=atmos%a(i) if(a .ne. 0.d0) then ans=atmos%rho(i) **(1+a *(z-atmos%z(i))/atmos%H(i)) **(-1.0d0-1.d0/a) else ans=*atmos%rho(i) *exp(-(z-atmos%z(i))/atmos%H(i)) endif endif ! zsave=z ! endif cvh2den=ans end ! ---------------------------------- real *8 function cvh2temp(z) implicit none ! vettical height to temperatur(Kelvin) real *8 z ! input. vertical height in m ! output is temperature of the atmospher in Kelvin real *8 ans integer i if(z .gt. atmos%z(atmos%nodes)) then ans=atmos%T(atmos%nodes) elseif(z .lt. atmos%z(1)) then ans=atmos%T(1)+atmos%b(1) *(z - atmos%z(1)) else call kdwhereis(z, atmos%nodes, atmos%z, 1, i) ans=atmos%T(i)+atmos%b(i) *(z-atmos%z(i)) endif cvh2temp=ans end !--------------------------------------------- real *8 function cthick2h(t) implicit none real *8 t ! input. air thickness in kg/m^2 real *8 logt, ans integer i real *8 dod0, fd, a logt=log(t) if(t .ge. atmos%cumd(1)) then ans=atmos%z(1) - *(logt - atmos%logcumd(1)) *atmos%H(1) elseif(t .le. atmos%cumd(atmos%nodes)) then ans=atmos%z(atmos%nodes) - *Hinf *log(t/atmos%cumd(atmos%nodes)) else call kdwhereis(t, atmos%nodes, atmos%cumd, 1, i) ! i is such that X(i) > x >=x(i+1) ans
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 rndc(u)
Definition: rnd.f:91
********************block data cblkHeavy ********************integer j data *HeavyG2symbol p
Definition: cblkHeavy.h:7
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
Definition: cblkEvhnp.h:5
dE dx *! Nuc Int sampling table g
Definition: cblkMuInt.h:130
! 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
Here is the call graph for this function: