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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 53 - (show annotations)
Fri Oct 7 13:11:58 2011 UTC (12 years, 7 months ago) by guez
File size: 4778 byte(s)


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

  ViewVC Help
Powered by ViewVC 1.1.21