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

Go to the source code of this file.

Functions/Subroutines

subroutine kdexpintf (func, a, b, eps, ans, error, icon)
 

Function/Subroutine Documentation

◆ kdexpintf()

subroutine kdexpintf ( real*8  func,
real*8  a,
real*8  b,
real*8  eps,
real*8  ans,
real*8  error,
integer  icon 
)

Definition at line 55 of file kdexpIntF.f.

References d0, false, kdmachmnmx(), and parameter().

Referenced by cprimacceptance(), funczen(), and primdn().

55 ! *******************************************************
56  implicit none
57 !
58 ! Numerical integration in a finite range by Takahashi-Mori's
59 ! double exponential integraton method.
60 ! The method gives accurate result even if there are singularities
61 ! at the integration limits. If there is a very sharp peak in the
62 ! midst of the integration region, the method will not give
63 ! a good result.
64 !
65 !
66  real*8 func ! input. integrand function name with 1 argument
67  ! you have to declare 'external'
68  ! Argument is real*8 xx(2).
69  ! xx(1) is x,
70  ! Let aa=min(a, b), bb=max(a,b)
71  ! xx(2) = aa - x if aa<= x < (aa+bb)/2
72  ! = bb - x if bb> x >= (aa+bb)/2
73  ! So you should use xx(2) if at aa and/or bb
74  ! func is singular;
75  ! x(2) < 0 ==> f(aa-x(2))
76  ! x(2) >=0 ==> f(bb-x(2))
77 
78  real*8 a ! input. lower limit of the integration region
79  real*8 b ! input. upper //
80  ! b may be <=a.
81  real*8 eps ! input. relative or absolute error of the
82  ! intetegration you want to get.
83  ! if |ans| is > 1, used for relative error
84  ! else used for absolute error.
85  ! eps ~> 1.d-9 may be a good choice.
86  real*8 ans ! output. approximate integration value.
87  real*8 error ! output. estimated error (relative or absolute)
88  ! depending on |ans|.
89  integer icon ! output. 0 --> ans is reliable.
90  ! 1 --> ans may have a larger error than
91  ! your request.
92  ! 2 --> input error so that ans is undef.
93 !
94 !
95 !
96 
97  integer halventime ! if the integration accuracy is not enough
98  ! halve the equi-step of trapezoidal rule.
99  ! halving is tried upto halveNtime times.
100  integer pointsinunit ! see graph below
101  integer blocks ! we take 10 blocks
102  integer totalpoints ! (max number of points)-1 where function
103  ! is evaluated.
104 !
105 ! integration bin; unit is
106 !
107 ! 1 2 3 .. 2**halveNtime = pointsInUnit
108 ! | | | ... |
109 ! blocks of units are max number of points where the function is
110 ! evaluated.
111 !
112 ! 0 1 2 3 .. pointsInUnit (note 0 at the top)
113 ! | | | | ... | | ..... | | | | .. | | | | | | | ...|
114 ! 1 2.... pointsInUnit
115 !
116 !
117 ! 1 2 3 bloks units
118 !
119 ! for the first integration use points marked O as below (bloks points)
120 ! O O O O c
121 ! That is, if pointsInUnit = 32, in each block O is used
122 !
123 !
124 ! 0 1 2 16 32
125 ! | | | | | | | | | | | | | |... | | | | | | ... | | | | | |
126 ! O O
127 ! halving this
128 !
129 ! 0 1 2 16 32
130 ! | | | | | | | | | | | | | | | | | | | | ... | | | | | | | | | | |
131 ! O x O
132 ! halving this
133 !
134 !
135 ! 0 1 2 3 4 5 6 7 8 9 10 12 13 14 16 18 20 22 24 26 28 30 32
136 ! | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | |
137 ! O + x + O
138 ! halving this
139 !
140 ! 0 1 2 3 4 5 6 7 8 9 10 12 14 16 18 20 22 24 26 28 30 32
141 ! | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | |
142 ! O # + # x # + # O
143 !
144 ! halving this
145 ! 0 1 2 3 4 5 6 7 8 9 10 12 14 16 18 20 22 24 26 28 30 32
146 ! | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | |
147 ! O $ # $ + $ # $ x $ # $ + $ # $ O
148 !
149 ! halving this is the final step
150 !
151  parameter(halventime = 5, pointsinunit = 32)
152 ! must be 2**halveNtime
153  parameter( blocks = 10,
154  * totalpoints = blocks * pointsinunit + 1 )
155 !
156 ! mapping: y(0), y(1), y(32), y(33), ... corresponds to the
157 ! above nodal points. y(0) is very close to -1 and y(totalpoints)
158 ! is very close to 1. (actually, they are -1, and 1 due to
159 ! finite accuracy of double precision. so 1+y and 1-y is
160 ! tabulated specially.
161 !
162 
163  real*8 y(0:totalpoints), w(0:totalpoints)
164  real*8 opy(0:totalpoints),omy(0:totalpoints)
165  real*8 f(0:totalpoints)
166  real*8 machmin, machmax ! machine min, and max values
167  real*8 halfpi
168  real*8 tmax ! max |t| where transformation
169  ! y = tanh(pi/2 *sinh(t)) has no over/under flow.
170  ! |y| < 1
171  real*8 h ! minimum step of trapezoidal rule.
172  real*8 t, c1, ans1, ans2, step, f2, ytox, ytoxn, ytoxp
173  real*8 temp, xa(2), expm, expp
174  integer i, j, jstep, k
175 
176  logical first /.true./
177 
178  save first, y, w, halfpi, tmax, h, opy, omy, temp
179 
180  ytox(k) = c1*(y(k) + 1) + a
181  ytoxn(k) = -c1*opy(k) ! -c1(1+y)
182  ytoxp(k) = c1*omy(k) ! c1(1-y)
183 
184  if( first ) then
185 ! approx machine min, max
186  call kdmachmnmx(machmin, machmax)
187  halfpi = asin(1.d0) ! pi/2
188 
189 ! tmax = log(log(machmax/1.d5)/halfpi )
190 !
191 ! The next choice is rather from trial and error
192 ! log(log(1.d-75 ~ 1.d150).. ) is o.k
193 !
194  tmax = log(log(sqrt(machmin)/2)/(-2))
195 
196  h = 2*tmax/totalpoints ! width of (-tmax, tmax) is devided
197  ! by totalpoints
198 !
199 ! compute nodal points and weight there.
200 !
201  do i = 0, totalpoints
202  t = -tmax + i * h
203  temp = halfpi * sinh(t)
204  expm = exp(-temp)
205  expp = exp( temp)
206 
207  y(i) = tanh( temp )
208 
209  opy(i) = 2*expp/(expp + expm) ! 1+y
210  omy(i) = 2*expm/(expp + expm) ! 1-y
211 
212  w(i) = cosh(t) / cosh( halfpi*sinh(t) )**2
213 
214  enddo
215  first = .false.
216  endif
217 
218  if(a .eq. b) then
219  ans = 0.d0
220  icon = 0.
221  else
222  c1 = (b-a)/2.0d0
223  ans1 = 0.
224 
225  jstep = pointsinunit
226  do i = 1, halventime
227  step = jstep*h
228  ans2 = 0.
229  do j = 0, totalpoints, jstep
230  if( i.gt. 1 .and.
231  * mod( mod(j, pointsinunit), jstep*2) .eq. 0) then
232  f2 = f(j)
233  else
234  xa(1) = ytox(j)
235  if(y(j) .lt. 0. ) then
236  xa(2) = ytoxn(j)
237  else
238  xa(2) = ytoxp(j)
239  endif
240  f2 = func( xa ) * w(j)
241  f(j) = f2
242  endif
243  ans2 = ans2 + f2
244  enddo
245  ans2 = ans2 * step
246  if(i .gt. 1) then
247  if(abs(ans2) .gt. 1.d0) then
248  error =abs( abs(ans1/ans2)-1.d0 )
249  if(error .le. eps) then
250  icon = 0
251  goto 1000
252  endif
253  else
254 ! error = abs(ans2-ans1)
255  error =abs( abs(ans1/ans2)-1.d0 )
256  if(error .le. eps) then
257  icon = 0
258  goto 1000
259  endif
260  endif
261  endif
262  ans1 = ans2
263  jstep = jstep/2
264  enddo
265  icon = 1
266  1000 continue
267  ans = ans2 * halfpi *c1
268  endif
integer npitbl real *nx parameter(n=101, npitbl=46, nx=n-1) real *8 uconst
subroutine kdmachmnmx(xmin, xmax)
Definition: kdmachmnmx.f:8
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
logical, save first
Definition: cNRLAtmos.f:8
nodes i
common ZdedxAir tmax
Definition: ZdedxAir.h: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
real(4), dimension(:), allocatable, save h
Definition: cNRLAtmos.f:28
********************block data cblkHeavy ********************integer j data *HeavyG2symbol *data *HeavyG2code kiron data j
Definition: cblkHeavy.h:36
real(4), dimension(:), allocatable, save temp
Definition: cNRLAtmos.f:29
block data cblkEvhnp ! currently usable models data RegMdls ad *special data *Cekaon d0
Definition: cblkEvhnp.h:5
latitude latitude this system is used *****************************************************************! type coord sequence union map real y
Definition: Zcoord.h:25
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
nodes t
real(4), save b
Definition: cNRLAtmos.f:21
dE dx *! Nuc Int sampling table f
Definition: cblkMuInt.h:130
Here is the call graph for this function:
Here is the caller graph for this function: