forked from KuangLab-Harvard/SAM_SRCv6.11
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathatmosphere.f90
71 lines (64 loc) · 3.48 KB
/
atmosphere.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
SUBROUTINE Atmosphere(alt, sigma, delta, theta)
! -------------------------------------------------------------------------
! PURPOSE - Compute the properties of the 1976 standard atmosphere to 86 km.
! AUTHOR - Ralph Carmichael, Public Domain Aeronautical Software
! NOTE - If alt > 86, the values returned will not be correct, but they will
! not be too far removed from the correct values for density.
! The reference document does not use the terms pressure and temperature
! above 86 km.
IMPLICIT NONE
!============================================================================
! A R G U M E N T S |
!============================================================================
REAL,INTENT(IN):: alt ! geometric altitude, km.
REAL,INTENT(OUT):: sigma! density/sea-level standard density
REAL,INTENT(OUT):: delta! pressure/sea-level standard pressure
REAL,INTENT(OUT):: theta! temperature/sea-level standard temperature
!============================================================================
! L O C A L C O N S T A N T S |
!============================================================================
REAL,PARAMETER:: REARTH = 6369.0 ! radius of the Earth (km)
REAL,PARAMETER:: GMR = 34.163195 ! gas constant
INTEGER,PARAMETER:: NTAB=8! number of entries in the defining tables
!============================================================================
! L O C A L V A R I A B L E S |
!============================================================================
INTEGER:: i,j,k ! counters
REAL:: h ! geopotential altitude (km)
REAL:: tgrad, tbase! temperature gradient and base temp of this layer
REAL:: tlocal ! local temperature
REAL:: deltah ! height above base of this layer
!============================================================================
! L O C A L A R R A Y S ( 1 9 7 6 S T D. A T M O S P H E R E ) |
!============================================================================
REAL,DIMENSION(NTAB),PARAMETER:: htab= (/0.0, 11.0, 20.0, 32.0, 47.0, 51.0, 71.0,84.852/)
REAL,DIMENSION(NTAB),PARAMETER:: ttab= (/288.15, 216.65, 216.65, 228.65, 270.65, 270.65, 214.65, 186.946/)
REAL,DIMENSION(NTAB),PARAMETER:: ptab= (/1.0, 2.233611e-1, &
5.403295e-2, 8.5666784e-3, 1.0945601e-3, 6.6063531e-4, 3.9046834e-5, 3.68501e-6/)
REAL,DIMENSION(NTAB),PARAMETER:: gtab= (/-6.5, 0.0, 1.0, 2.8, 0.0, -2.8, -2.0, 0.0/)
!----------------------------------------------------------------------------
h=alt*REARTH/(alt+REARTH)! convert geometric to geopotential altitude
i=1
j=NTAB ! setting up for=binary search
DO
k=(i+j)/2
IF (h < htab(k)) THEN
j=k
ELSE
i=k
END IF
IF (j <= i+1) EXIT
END DO
tgrad=gtab(i) ! i will be in 1...NTAB-1
tbase=ttab(i)
deltah=h-htab(i)
tlocal=tbase+tgrad*deltah
theta=tlocal/ttab(1) ! temperature ratio
IF (tgrad == 0.0) THEN ! pressure ratio
delta=ptab(i)*EXP(-GMR*deltah/tbase)
ELSE
delta=ptab(i)*(tbase/tlocal)**(GMR/tgrad)
END IF
sigma=delta/theta ! density ratio
RETURN
END Subroutine Atmosphere