source: JEM-EUSO/esaf_lal/tags/v1_r0/esaf/packages/simulation/externals/slast/src/atm/depth_integral.F @ 117

Last change on this file since 117 was 117, checked in by moretto, 11 years ago

ESAF version compilable on mac OS

File size: 993 bytes
Line 
1      REAL FUNCTION DEPTH_INTEGRAL(TH,H)
2#include "detector.inc"
3#include "event.inc"
4      COMMON/DEPTH_INT/THET,HEIGHT
5      PARAMETER (zero=0., one=1., NSEG = 1, RELTOL = 1.e-3, ABSTOL = 0.)
6      EXTERNAL FunDEPTH
7      REAL A,B,TH,H
8      REAL*8 A8,B8,RES8
9*
10      THET   = TH
11      HEIGHT = H
12      A = zero
13      B = one
14      A8 = 0.d0
15      B8 = 1.d0
16      CALL RADAPT(FunDEPTH,A,B,NSEG,RELTOL,ABSTOL,RES,ERR)
17      DEPTH_INTEGRAL = RES
18 1000 CONTINUE
19      END
20
21      REAL FUNCTION FunDEPTH(t)
22#include "detector.inc"
23      COMMON/DEPTH_INT/THET,HEIGHT
24      H0 = 0.029269967*TEMP     ! in km
25      h = HEIGHT - H0*log(t)
26      p = ATM(h)
27 1    CONTINUE
28      IF(CURV.EQ.1) THEN
29         f = 1.-sin(THET)**2*(R_EARTH+HEIGHT)**2/(R_EARTH+h)**2
30         f = sqrt(f)
31      ELSEIF(CURV.EQ.2) THEN
32         f = cos(THET)
33      ELSE
34         CURV = 1
35         GOTO 1
36      ENDIF
37      IF(f.NE.0.) THEN
38         FunDEPTH = H0*p/f/t
39      ELSE
40         FunDEPTH = 0.
41      ENDIF
42      END
Note: See TracBrowser for help on using the repository browser.