FV3 Bundle
Fundamental_Constants.f90
Go to the documentation of this file.
1 !
2 ! Fundamental_Constants
3 !
4 ! Module containing various fundamental mathematical and physical constants.
5 !
6 ! The fundamental constants and equations used are taken from the NIST
7 ! Reference on Constants, Units, and Uncertainty website:
8 !
9 ! http://physics.nist.gov/cuu/Constants/
10 !
11 ! See also:
12 !
13 ! Mohr, P.J. and B.N. Taylor, "CODATA recommended values of the
14 ! fundamental physical constants: 1998", Reviews of Modern Physics,
15 ! Vol.72, No.2, 2000.
16 !
17 !
18 ! CREATION HISTORY:
19 ! Written by: Paul van Delst, 02-May-2000
20 ! paul.vandelst@noaa.gov
21 !
22 
24 
25  ! -----------------
26  ! Environment setup
27  ! -----------------
28  ! Modules used
29  USE type_kinds, ONLY: fp
30  ! Disable implicit typing
31  IMPLICIT NONE
32 
33 
34 
35  ! ------------------
36  ! Default visibility
37  ! ------------------
38  PRIVATE
39  ! Procedures
41 
42 
43 
44  ! -----------------
45  ! Module parameters
46  ! -----------------
47  CHARACTER(*), PARAMETER :: module_version_id = &
48  '$Id: Fundamental_Constants.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
49  ! Numeric literals
50  REAL(fp), PARAMETER :: zero = 0.0_fp
51  REAL(fp), PARAMETER :: one = 1.0_fp
52  REAL(fp), PARAMETER :: two = 2.0_fp
53 
54 
55  !#----------------------------------------------------------------------------#
56  !# -- IRRATIONAL NUMBERS AND ASSOCIATED BITS -- #
57  !#----------------------------------------------------------------------------#
58 
59  ! PI
60  REAL(fp), PARAMETER, PUBLIC :: pi = 3.141592653589793238462643_fp
61  REAL(fp), PARAMETER, PUBLIC :: pi_reciprocal = 0.318309886183790671537767_fp
62  REAL(fp), PARAMETER, PUBLIC :: pi_squared = 9.869604401089358618834491_fp
63  REAL(fp), PARAMETER, PUBLIC :: pi_square_root = 1.772453850905516027298167_fp
64  REAL(fp), PARAMETER, PUBLIC :: pi_ln = 1.144729885849400174143427_fp
65  REAL(fp), PARAMETER, PUBLIC :: pi_log10 = 0.497149872694133854351268_fp
66 
67  ! E
68  REAL(fp), PARAMETER, PUBLIC :: e = 2.718281828459045235360287_fp
69  REAL(fp), PARAMETER, PUBLIC :: e_reciprocal = 0.367879441171442321595523_fp
70  REAL(fp), PARAMETER, PUBLIC :: e_squared = 7.389056098930650227230427_fp
71  REAL(fp), PARAMETER, PUBLIC :: e_log10 = 0.434294481903251827651129_fp
72 
73  ! Other transcendentals
74  REAL(fp), PARAMETER, PUBLIC :: ln2 = 0.693147180559945309417232_fp
75 
76 
77  !#----------------------------------------------------------------------------#
78  !# -- UNIVERAL CONSTANTS -- #
79  !#----------------------------------------------------------------------------#
80 
81  ! ----------------------------------------------
82  ! Speed of light
83  ! Symbol:c, Units:m/s, Rel.Uncert.(ppm): exact
84  ! ----------------------------------------------
85  REAL(fp), PARAMETER, PUBLIC :: speed_of_light = 2.99792458e+08_fp
86 
87  ! --------------------------------------------------
88  ! Permeability of vacuum
89  ! Symbol:mu0, Units:N/A^2, Rel.Uncert.(ppm): exact
90  ! --------------------------------------------------
91  REAL(fp), PARAMETER, PUBLIC :: permeability = pi * 4.0e-07_fp
92 
93  ! -----------------------------------------------------
94  ! Permittivity of vacuum
95  ! Symbol:epsilon0, Units:F/m, Rel.Uncert.(ppm): exact
96  ! -----------------------------------------------------
97  REAL(fp), PARAMETER, PUBLIC :: permittivity = one / &
98  ! ------------------------------------
100 
101  ! ---------------------------------------------
102  ! Planck constant
103  ! Symbol:h, Units:Js, Rel.Uncert.(ppm): 0.078
104  ! ---------------------------------------------
105  REAL(fp), PARAMETER, PUBLIC :: planck_constant = 6.62606876e-34_fp
106 
107  ! ----------------------------------------------------
108  ! Gravitational constant
109  ! Symbol:G, Units:m^3/kg/s^2, Rel.Uncert.(ppm): 1500
110  ! ----------------------------------------------------
111  REAL(fp), PARAMETER, PUBLIC :: gravitational_constant = 6.673e-11_fp
112 
113 
114 
115  !#----------------------------------------------------------------------------#
116  !# -- CONVERSION FACTORS -- #
117  !#----------------------------------------------------------------------------#
118 
119  ! ---------------------------------------------
120  ! Electron volt
121  ! Symbol:eV, Units:J, Rel.Uncert.(ppm): 0.039
122  ! ---------------------------------------------
123  REAL(fp), PARAMETER, PUBLIC :: electron_volt = 1.602176462e-19_fp
124 
125  ! ---------------------------------------------
126  ! Unified atomic mass unit
127  ! Symbol:u, Units:kg, Rel.Uncert.(ppm): 0.079
128  ! ---------------------------------------------
129  REAL(fp), PARAMETER, PUBLIC :: unified_atomic_mass_unit = 1.66053873e-27_fp
130 
131  ! ----------------------------------------------
132  ! Standard atmosphere
133  ! Symbol:P0, Units:Pa, Rel.Uncert.(ppm): exact
134  ! ----------------------------------------------
135  REAL(fp), PARAMETER, PUBLIC :: standard_atmosphere = 101325.0_fp
136 
137  ! ----------------------------------------------------------------------
138  ! Standard temperature
139  ! Symbol:T0, Units:Kelvin, Rel.Uncert.(ppm): exact
140  !
141  ! Note that the unit of thermodynamic temperature, the Kelvin, is the
142  ! fraction 1/273.16 of the thermodynamic temperature of the triple point
143  ! of water. The standard temperature is the ice point of water, NOT the
144  ! triple point, hence the 0.01K difference.
145  ! ----------------------------------------------------------------------
146  REAL(fp), PARAMETER, PUBLIC :: standard_temperature = 273.15_fp
147 
148  ! ------------------------------------------------
149  ! Standard gravity
150  ! Symbol:g, Units:m/s^2, Rel.Uncert.(ppm): exact
151  ! ------------------------------------------------
152  REAL(fp), PARAMETER, PUBLIC :: standard_gravity = 9.80665_fp
153 
154 
155 
156  !#----------------------------------------------------------------------------#
157  !# -- PHYSICOCHEMICAL CONSTANTS -- #
158  !#----------------------------------------------------------------------------#
159 
160  ! -----------------------------------------------------
161  ! Avogadro constant
162  ! Symbol:N(A), Units:mole^-1, Rel.Uncert.(ppm): 0.079
163  ! -----------------------------------------------------
164  REAL(fp), PARAMETER, PUBLIC :: avogadro_constant = 6.02214199e+23_fp
165 
166 
167  ! -------------------------------------------------
168  ! Molar gas constant
169  ! Symbol:R, Units:J/mole/K, Rel.Uncert.(ppm): 1.7
170  ! -------------------------------------------------
171  REAL(fp), PARAMETER, PUBLIC :: molar_gas_constant = 8.314472_fp
172 
173  ! --------------------------------------------
174  ! Boltzmann constant
175  ! Symbol:k, Units:J/K, Rel.Uncert.(ppm): 1.7
176  !
177  ! R
178  ! k = ------
179  ! N(A)
180  !
181  ! = 1.3806503(24)e-23
182  !
183  ! --------------------------------------------
184  REAL(fp), PARAMETER, PUBLIC :: boltzmann_constant = molar_gas_constant / &
185  ! ------------------
187 
188  ! ------------------------------------------------------
189  ! Stefan-Boltzmann constant
190  ! Symbol:sigma, Units:W/m^2/K^4, Rel.Uncert.(ppm): 7.0
191  !
192  ! PI^2
193  ! ----.k^4
194  ! 60 h
195  ! sigma = ------------ ( hbar = ----- )
196  ! hbar^3.c^2 2PI
197  !
198  ! = 5.670400(40)e-08
199  !
200  ! I just placed the value here due to the mathematical
201  ! gymnastics required to calculate it directly.
202  ! ------------------------------------------------------
203  REAL(fp), PARAMETER, PUBLIC :: stefan_boltzmann_constant = 5.670400e-08_fp
204 
205  ! -------------------------------------------------------
206  ! First Planck function constant
207  ! Symbol:c1, Units:W.m^2.sr^-1, Rel.Uncert.(ppm): 0.078
208  !
209  ! c1 = 2.h.c^2
210  !
211  ! = 1.191042722(93)e-16
212  !
213  ! -------------------------------------------------------
214  REAL(fp), PARAMETER, PUBLIC :: c_1 = two * planck_constant * speed_of_light**2
215 
216  ! ---------------------------------------------
217  ! Second Planck function constant
218  ! Symbol:c2, Units:K.m, Rel.Uncert.(ppm): 1.7
219  !
220  ! h.c
221  ! c2 = -----
222  ! k
223  !
224  ! = 1.4387752(25)e-02
225  !
226  ! ---------------------------------------------
227  REAL(fp), PARAMETER, PUBLIC :: c_2 = planck_constant * speed_of_light / &
228  ! ----------------------------------
230 
231  ! -----------------------------------------------------------------
232  ! Molar volume of an ideal gas at standard temperature and pressure
233  ! Symbol:Vm, Units:m^3/mol, Rel.Uncert.(ppm): 1.7
234  !
235  ! R.T0
236  ! Vm = ------
237  ! P0
238  !
239  ! = 2.2413996(39)e-02
240  !
241  ! -----------------------------------------------------------------
242  REAL(fp), PARAMETER, PUBLIC :: stp_molar_volume = ( molar_gas_constant * standard_temperature ) / &
243  ! ---------------------------------------------
245 
246  ! ------------------------------------------------------------------
247  ! Loschmidt constant: The number density of one mole of an ideal gas
248  ! at standard temperature and pressure
249  ! Symbol:n0, Units:m^-3, Rel.Uncert.(ppm): 1.7
250  !
251  ! N(A).P0
252  ! n0 = ---------
253  ! R.T0
254  !
255  ! N(A)
256  ! = ------ .....(1)
257  ! Vm
258  !
259  ! = 2.6867775(47)e+25
260  !
261  ! Alternatively, using the ideal gas law directly, we know,
262  !
263  ! P.V = n.k.T .....(2)
264  !
265  ! For V = 1m^3 (unit volume), and P = P0, T = T0, then eqn.(2)
266  ! becomes,
267  !
268  ! P0 = n0.k.T0
269  !
270  ! which rearranges to
271  !
272  ! P0
273  ! n0 = ------ .....(3)
274  ! k.T0
275  !
276  ! Equation (1) rather than eqn(3) is used here.
277  ! ------------------------------------------------------------------
278  REAL(fp), PARAMETER, PUBLIC :: loschmidt_constant = avogadro_constant / &
279  ! -----------------
281 
282 
283 CONTAINS
284 
285 
286 !--------------------------------------------------------------------------------
287 !:sdoc+:
288 !
289 ! NAME:
290 ! Fundamental_Constants_Version
291 !
292 ! PURPOSE:
293 ! Subroutine to return the module version information.
294 !
295 ! CALLING SEQUENCE:
296 ! CALL Fundamental_Constants_Version( Id )
297 !
298 ! OUTPUTS:
299 ! Id: Character string containing the version Id information
300 ! for the module.
301 ! UNITS: N/A
302 ! TYPE: CHARACTER(*)
303 ! DIMENSION: Scalar
304 ! ATTRIBUTES: INTENT(OUT)
305 !
306 !:sdoc-:
307 !--------------------------------------------------------------------------------
308 
309  SUBROUTINE fundamental_constants_version( Id )
310  CHARACTER(*), INTENT(OUT) :: id
311  id = module_version_id
312  END SUBROUTINE fundamental_constants_version
313 
314 END MODULE fundamental_constants
real(fp), parameter, public pi_square_root
real(fp), parameter, public e_squared
real(fp), parameter, public stefan_boltzmann_constant
real(fp), parameter, public zero
real(fp), parameter, public stp_molar_volume
integer, parameter, public fp
Definition: Type_Kinds.f90:124
real(fp), parameter, public loschmidt_constant
real(fp), parameter, public standard_temperature
real(fp), parameter, public unified_atomic_mass_unit
real(fp), parameter, public c_2
real(fp), parameter, public e
real(fp), parameter, public standard_atmosphere
real(fp), parameter, public avogadro_constant
real(fp), parameter, public pi_squared
real(fp), parameter, public speed_of_light
real(fp), parameter, public e_reciprocal
real(fp), parameter, public e_log10
real(fp), parameter, public one
real(fp), parameter, public boltzmann_constant
real(fp), parameter, public c_1
real(fp), parameter, public two
real(fp), parameter, public gravitational_constant
real(fp), parameter, public pi_log10
real(fp), parameter, public planck_constant
real(fp), parameter, public molar_gas_constant
real(fp), parameter, public permeability
real(fp), parameter, public standard_gravity
real(fp), parameter, public permittivity
real(fp), parameter, public pi_ln
real(fp), parameter, public ln2
real(fp), parameter, public pi_reciprocal
real(fp), parameter, public electron_volt
character(*), parameter module_version_id
subroutine, public fundamental_constants_version(Id)
real(fp), parameter, public pi