/[lmdze]/trunk/libf/phylmd/suphec.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/suphec.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 47 - (show annotations)
Fri Jul 1 15:00:48 2011 UTC (12 years, 10 months ago) by guez
File size: 4640 byte(s)
Split "thermcell.f" and "cv3_routines.f".
Removed copies of files that are now in "L_util".
Moved "mva9" and "diagetpq" to their own files.
Unified variable names across procedures.

1 module suphec_m
2
3 implicit none
4
5 ! A1.0 Fundamental constants
6 REAL RPI
7 real, parameter:: RCLUM = 299792458.
8 real, parameter:: RHPLA = 6.6260755E-34
9 real, parameter:: RKBOL = 1.380658E-23 ! Boltzmann constant, in J K-1
10 real, parameter:: RNAVO = 6.0221367E+23 ! Avogadro number, in mol-1
11
12 ! A1.1 Astronomical constants
13 REAL RSIYEA, RSIDAY, ROMEGA
14 real, parameter:: RDAY = 86400.
15 real, parameter:: REA = 149597870000.
16 real, parameter:: REPSM = 0.409093
17
18 ! A1.2 Geoide
19 real, parameter:: RG = 9.80665 ! acceleration of gravity, in m s-2
20 real, parameter:: RA = 6371229.
21
22 ! A1.3 Radiation
23 REAL RSIGMA
24
25 ! A1.4 Thermodynamic gas phase
26 REAL, parameter:: R = RNAVO * RKBOL ! ideal gas constant, in J K-1 mol-1
27 real RV, RCPD, RCPV, RCVD, RCVV
28 real, parameter:: RMD = 28.9644 ! molar mass of dry air, in g mol-1
29
30 real, parameter:: RD = 1000. * R / RMD
31 ! specific ideal gas constant for dry air, in J K-1 kg-1
32
33 real, parameter:: RMO3 = 47.9942
34 real, parameter:: RMV = 18.0153
35 REAL RKAPPA, RETV
36
37 ! A1.5, 6 Thermodynamic liquid, solid phases
38 REAL RCW, RCS
39
40 ! A1.7 Thermodynamic transition of phase
41 REAL RLMLT
42 real, parameter:: RTT = 273.16
43 real, parameter:: RLVTT = 2.5008E+6
44 real, parameter:: RLSTT = 2.8345E+6
45 real, parameter:: RATM = 100000.
46
47 ! A1.8 Curve of saturation
48 REAL RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS
49 real, parameter:: RESTT = 611.14
50 REAL RALPD, RBETD, RGAMD
51
52 save
53
54 contains
55
56 SUBROUTINE suphec
57
58 ! From phylmd/suphec.F, v 1.2 2005/06/06 13:16:33
59 ! Initialise certaines constantes et parametres physiques.
60
61 !------------------------------------------
62
63 PRINT *, 'Call sequence information: suphec'
64
65 ! 1. DEFINE FUNDAMENTAL CONSTANTS
66
67 print *, 'Constants of the ICM'
68 RPI = 2.*ASIN(1.)
69 print *, 'Fundamental constants '
70 print '('' PI = '', E13.7, '' -'')', RPI
71 print '('' c = '', E13.7, ''m s-1'')', RCLUM
72 print '('' h = '', E13.7, ''J s'')', RHPLA
73 print '('' K = '', E13.7, ''J K-1'')', RKBOL
74 print '('' N = '', E13.7, ''mol-1'')', RNAVO
75
76 ! 2. DEFINE ASTRONOMICAL CONSTANTS
77
78 RSIYEA = 365.25*RDAY*2.*RPI/6.283076
79 RSIDAY = RDAY/(1.+RDAY/RSIYEA)
80 ROMEGA = 2.*RPI/RSIDAY
81
82 print *, 'Astronomical constants '
83 print '('' day = '', E13.7, '' s'')', RDAY
84 print '('' half g. axis = '', E13.7, '' m'')', REA
85 print '('' mean anomaly = '', E13.7, '' -'')', REPSM
86 print '('' sideral year = '', E13.7, '' s'')', RSIYEA
87 print '('' sideral day = '', E13.7, '' s'')', RSIDAY
88 print '('' omega = '', E13.7, '' s-1'')', ROMEGA
89
90 ! 3. DEFINE GEOIDE.
91
92 print *, ' Geoide '
93 print '('' Gravity = '', E13.7, '' m s-2'')', RG
94 print '('' Earth radius = '', E13.7, '' m'')', RA
95
96 ! 4. DEFINE RADIATION CONSTANTS.
97
98 rsigma = 2.*rpi**5 * (rkbol/rhpla)**3 * rkbol/rclum/rclum/15.
99 print *, ' Radiation '
100 print '('' Stefan-Bol. = '', E13.7, '' W m-2 K-4'')', RSIGMA
101
102 ! 5. DEFINE THERMODYNAMIC CONSTANTS, GAS PHASE.
103
104 RV = 1000.*R/RMV
105 RCPD = 3.5*RD
106 RCVD = RCPD-RD
107 RCPV = 4. *RV
108 RCVV = RCPV-RV
109 RKAPPA = RD/RCPD
110 RETV = RV/RD-1.
111 print *, 'Thermodynamic, gas '
112 print '('' Perfect gas = '', e13.7)', R
113 print '('' Ozone mass = '', e13.7)', RMO3
114 print '('' Vapour mass = '', e13.7)', RMV
115 print '('' Dry air constant = '', e13.7)', RD
116 print '('' Vapour constant = '', e13.7)', RV
117 print '('' Cpd = '', e13.7)', RCPD
118 print '('' Cvd = '', e13.7)', RCVD
119 print '('' Cpv = '', e13.7)', RCPV
120 print '('' Cvv = '', e13.7)', RCVV
121 print '('' Rd/Cpd = '', e13.7)', RKAPPA
122 print '('' Rv/Rd-1 = '', e13.7)', RETV
123
124 ! 6. DEFINE THERMODYNAMIC CONSTANTS, LIQUID PHASE.
125
126 RCW = RCPV
127 print *, 'Thermodynamic, liquid '
128 print '('' Cw = '', E13.7)', RCW
129
130 ! 7. DEFINE THERMODYNAMIC CONSTANTS, SOLID PHASE.
131
132 RCS = RCPV
133 print *, 'thermodynamic, solid'
134 print '('' Cs = '', E13.7)', RCS
135
136 ! 8. DEFINE THERMODYNAMIC CONSTANTS, TRANSITION OF PHASE.
137
138 RLMLT = RLSTT-RLVTT
139 print *, 'Thermodynamic, trans. '
140 print '('' Fusion point = '', E13.7)', RTT
141 print '('' RLvTt = '', E13.7)', RLVTT
142 print '('' RLsTt = '', E13.7)', RLSTT
143 print '('' RLMlt = '', E13.7)', RLMLT
144 print '('' Normal press. = '', E13.7)', RATM
145
146 ! 9. SATURATED VAPOUR PRESSURE.
147
148 RGAMW = (RCW-RCPV)/RV
149 RBETW = RLVTT/RV+RGAMW*RTT
150 RALPW = LOG(RESTT)+RBETW/RTT+RGAMW*LOG(RTT)
151 RGAMS = (RCS-RCPV)/RV
152 RBETS = RLSTT/RV+RGAMS*RTT
153 RALPS = LOG(RESTT)+RBETS/RTT+RGAMS*LOG(RTT)
154 RGAMD = RGAMS-RGAMW
155 RBETD = RBETS-RBETW
156 RALPD = RALPS-RALPW
157
158 END SUBROUTINE suphec
159
160 end module suphec_m

  ViewVC Help
Powered by ViewVC 1.1.21