source: palm/trunk/SOURCE/basic_constants_and_equations_mod.f90 @ 3361

Last change on this file since 3361 was 3361, checked in by knoop, 5 years ago

Introduced global constant rd_d_rv=0.622

  • Property svn:keywords set to Id
File size: 13.4 KB
Line 
1!> @file basic_constants_and_equations_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: basic_constants_and_equations_mod.f90 3361 2018-10-16 20:39:37Z knoop $
27! New module (introduced with modularization of bulk cloud physics model)
28!
29!
30!
31!
32! Description:
33! ------------
34!> This module contains all basic (physical) constants
35!> and
36!> functions for the calculation of diagnostic quantities.
37!------------------------------------------------------------------------------!
38 MODULE basic_constants_and_equations_mod
39
40
41    USE kinds
42
43    IMPLICIT NONE
44
45    REAL(wp), PARAMETER ::  pi = 3.141592654_wp  !< PI
46
47    REAL(wp), PARAMETER ::  c_p = 1005.0_wp                           !< heat capacity of dry air (J kg-1 K-1)
48    REAL(wp), PARAMETER ::  g = 9.81_wp                               !< gravitational acceleration (m s-2)
49    REAL(wp), PARAMETER ::  kappa = 0.4_wp                            !< von Karman constant
50    REAL(wp), PARAMETER ::  l_m = 0.33E+06_wp                         !< latent heat of water melting (J kg-1)
51    REAL(wp), PARAMETER ::  l_v = 2.5E+06_wp                          !< latent heat of water vaporization (J kg-1)
52    REAL(wp), PARAMETER ::  l_s = l_m + l_v                           !< latent heat of water sublimation (J kg-1)
53    REAL(wp), PARAMETER ::  molecular_weight_of_nacl = 0.05844_wp     !< mol. m. NaCl (kg mol-1)
54    REAL(wp), PARAMETER ::  molecular_weight_of_c3h4o4 = 0.10406_wp   !< mol. m. malonic acid (kg mol-1)
55    REAL(wp), PARAMETER ::  molecular_weight_of_nh4no3 = 0.08004_wp   !< mol. m. ammonium sulfate (kg mol-1)
56    REAL(wp), PARAMETER ::  molecular_weight_of_water = 0.01801528_wp !< mol. m. H2O (kg mol-1)
57    REAL(wp), PARAMETER ::  rho_l = 1.0E3_wp                          !< density of water (kg m-3)
58    REAL(wp), PARAMETER ::  rho_nacl = 2165.0_wp                      !< density of NaCl (kg m-3)
59    REAL(wp), PARAMETER ::  rho_c3h4o4 = 1600.0_wp                    !< density of malonic acid (kg m-3)
60    REAL(wp), PARAMETER ::  rho_nh4no3 = 1720.0_wp                    !< density of ammonium sulfate (kg m-3)
61    REAL(wp), PARAMETER ::  r_d = 287.0_wp                            !< sp. gas const. dry air (J kg-1 K-1)
62    REAL(wp), PARAMETER ::  r_v = 461.51_wp                           !< sp. gas const. water vapor (J kg-1 K-1)
63    REAL(wp), PARAMETER ::  sigma_sb = 5.67E-08_wp                    !< Stefan-Boltzmann constant
64    REAL(wp), PARAMETER ::  solar_constant = 1368.0_wp                !< solar constant at top of atmosphere
65    REAL(wp), PARAMETER ::  vanthoff_nacl = 2.0_wp                    !< van't Hoff factor for NaCl
66    REAL(wp), PARAMETER ::  vanthoff_c3h4o4 = 1.37_wp                 !< van't Hoff factor for malonic acid
67    REAL(wp), PARAMETER ::  vanthoff_nh4no3 = 2.31_wp                 !< van't Hoff factor for ammonium sulfate
68
69    REAL(wp), PARAMETER ::  p_0 = 100000.0_wp                         !< standard pressure reference state
70
71    REAL(wp), PARAMETER ::  g_d_cp  = g   / c_p   !< precomputed g / c_p
72    REAL(wp), PARAMETER ::  lv_d_cp = l_v / c_p   !< precomputed l_v / c_p
73    REAL(wp), PARAMETER ::  lv_d_rd = l_v / r_d   !< precomputed l_v / r_d
74    REAL(wp), PARAMETER ::  rd_d_rv = 0.622_wp !r_d / r_v  !< precomputed r_d / r_v
75    REAL(wp), PARAMETER ::  rd_d_cp = 0.286_wp !r_d / c_p  !< precomputed r_d / c_p
76    REAL(wp), PARAMETER ::  cp_d_rd = 1.0_wp/0.286_wp !c_p / r_d  !< precomputed c_p / r_d
77
78    REAL(wp) ::  molecular_weight_of_solute = molecular_weight_of_nacl  !< mol. m. NaCl (kg mol-1)
79    REAL(wp) ::  rho_s = rho_nacl                                       !< density of NaCl (kg m-3)
80    REAL(wp) ::  vanthoff = vanthoff_nacl                               !< van't Hoff factor for NaCl
81
82
83    SAVE
84
85    PRIVATE magnus_0d, &
86            magnus_1d, &
87            ideal_gas_law_rho_0d, &
88            ideal_gas_law_rho_1d, &
89            ideal_gas_law_rho_pt_0d, &
90            ideal_gas_law_rho_pt_1d, &
91            exner_function_0d, &
92            exner_function_1d, &
93            exner_function_invers_0d, &
94            exner_function_invers_1d, &
95            barometric_formula_0d, &
96            barometric_formula_1d
97
98    INTERFACE magnus
99       MODULE PROCEDURE magnus_0d
100       MODULE PROCEDURE magnus_1d
101    END INTERFACE magnus
102
103    INTERFACE ideal_gas_law_rho
104       MODULE PROCEDURE ideal_gas_law_rho_0d
105       MODULE PROCEDURE ideal_gas_law_rho_1d
106    END INTERFACE ideal_gas_law_rho
107
108    INTERFACE ideal_gas_law_rho_pt
109       MODULE PROCEDURE ideal_gas_law_rho_pt_0d
110       MODULE PROCEDURE ideal_gas_law_rho_pt_1d
111    END INTERFACE ideal_gas_law_rho_pt
112
113    INTERFACE exner_function
114       MODULE PROCEDURE exner_function_0d
115       MODULE PROCEDURE exner_function_1d
116    END INTERFACE exner_function
117
118    INTERFACE exner_function_invers
119       MODULE PROCEDURE exner_function_invers_0d
120       MODULE PROCEDURE exner_function_invers_1d
121    END INTERFACE exner_function_invers
122
123    INTERFACE barometric_formula
124       MODULE PROCEDURE barometric_formula_0d
125       MODULE PROCEDURE barometric_formula_1d
126    END INTERFACE barometric_formula
127
128 CONTAINS
129
130!------------------------------------------------------------------------------!
131! Description:
132! ------------
133!> This function computes the magnus formula (Press et al., 1992).
134!> The magnus formula is needed to calculate the saturation vapor pressure
135!------------------------------------------------------------------------------!
136    FUNCTION magnus_0d( t )
137
138       IMPLICIT NONE
139
140       REAL(wp), INTENT(IN) ::  t  !< temperature (K)
141
142       REAL(wp) ::  magnus_0d
143!
144!--    Saturation vapor pressure for a specific temperature:
145       magnus_0d =  611.2_wp * EXP( 17.62_wp * ( t - 273.15_wp ) /             &
146                                                   ( t - 29.65_wp  ) )
147
148    END FUNCTION magnus_0d
149
150!------------------------------------------------------------------------------!
151! Description:
152! ------------
153!> This function computes the magnus formula (Press et al., 1992).
154!> The magnus formula is needed to calculate the saturation vapor pressure
155!------------------------------------------------------------------------------!
156    FUNCTION magnus_1d( t )
157
158       IMPLICIT NONE
159
160       REAL(wp), INTENT(IN), DIMENSION(:) ::  t  !< temperature (K)
161
162       REAL(wp), DIMENSION(size(t)) ::  magnus_1d
163!
164!--    Saturation vapor pressure for a specific temperature:
165       magnus_1d =  611.2_wp * EXP( 17.62_wp * ( t - 273.15_wp ) /             &
166                                               ( t - 29.65_wp  ) )
167
168    END FUNCTION magnus_1d
169
170!------------------------------------------------------------------------------!
171! Description:
172! ------------
173!> Compute the ideal gas law for scalar arguments.
174!------------------------------------------------------------------------------!
175    FUNCTION ideal_gas_law_rho_0d( p, t )
176
177       IMPLICIT NONE
178
179       REAL(wp), INTENT(IN) ::  p  !< pressure (Pa)
180       REAL(wp), INTENT(IN) ::  t  !< temperature (K)
181
182       REAL(wp) ::  ideal_gas_law_rho_0d
183!
184!--    compute density according to ideal gas law:
185       ideal_gas_law_rho_0d = p / (r_d * t)
186
187    END FUNCTION ideal_gas_law_rho_0d
188
189!------------------------------------------------------------------------------!
190! Description:
191! ------------
192!> Compute the ideal gas law for 1-D array arguments.
193!------------------------------------------------------------------------------!
194    FUNCTION ideal_gas_law_rho_1d( p, t )
195
196       IMPLICIT NONE
197
198       REAL(wp), INTENT(IN), DIMENSION(:) ::  p  !< pressure (Pa)
199       REAL(wp), INTENT(IN), DIMENSION(:) ::  t  !< temperature (K)
200
201       REAL(wp), DIMENSION(size(p)) ::  ideal_gas_law_rho_1d
202!
203!--    compute density according to ideal gas law:
204       ideal_gas_law_rho_1d = p / (r_d * t)
205
206    END FUNCTION ideal_gas_law_rho_1d
207
208!------------------------------------------------------------------------------!
209! Description:
210! ------------
211!> Compute the ideal gas law for scalar arguments.
212!------------------------------------------------------------------------------!
213    FUNCTION ideal_gas_law_rho_pt_0d( p, t )
214
215       IMPLICIT NONE
216
217       REAL(wp), INTENT(IN) ::  p  !< pressure (Pa)
218       REAL(wp), INTENT(IN) ::  t  !< temperature (K)
219
220       REAL(wp) ::  ideal_gas_law_rho_pt_0d
221!
222!--    compute density according to ideal gas law:
223       ideal_gas_law_rho_pt_0d = p / (r_d * (1.0_wp / exner_function_invers(p)) * t)
224
225    END FUNCTION ideal_gas_law_rho_pt_0d
226
227!------------------------------------------------------------------------------!
228! Description:
229! ------------
230!> Compute the ideal gas law for 1-D array arguments.
231!------------------------------------------------------------------------------!
232    FUNCTION ideal_gas_law_rho_pt_1d( p, t )
233
234       IMPLICIT NONE
235
236       REAL(wp), INTENT(IN), DIMENSION(:) ::  p  !< pressure (Pa)
237       REAL(wp), INTENT(IN), DIMENSION(:) ::  t  !< temperature (K)
238
239       REAL(wp), DIMENSION(size(p)) ::  ideal_gas_law_rho_pt_1d
240!
241!--    compute density according to ideal gas law:
242       ideal_gas_law_rho_pt_1d = p / (r_d * (1.0_wp / exner_function_invers(p)) * t)
243
244    END FUNCTION ideal_gas_law_rho_pt_1d
245
246!------------------------------------------------------------------------------!
247! Description:
248! ------------
249!> Compute the exner function for scalar arguments.
250!------------------------------------------------------------------------------!
251    FUNCTION exner_function_0d( p )
252
253       IMPLICIT NONE
254
255       REAL(wp), INTENT(IN) ::  p    !< pressure (Pa)
256
257       REAL(wp) ::  exner_function_0d
258!
259!--    compute exner function:
260       exner_function_0d = ( p / p_0 )**( rd_d_cp )
261
262    END FUNCTION exner_function_0d
263
264!------------------------------------------------------------------------------!
265! Description:
266! ------------
267!> Compute the exner function for 1-D array arguments.
268!------------------------------------------------------------------------------!
269    FUNCTION exner_function_1d( p )
270
271       IMPLICIT NONE
272
273       REAL(wp), INTENT(IN), DIMENSION(:) ::  p  !< pressure (Pa)
274
275       REAL(wp), DIMENSION(size(p)) ::  exner_function_1d
276!
277!--    compute exner function:
278       exner_function_1d = ( p / p_0 )**( rd_d_cp )
279
280    END FUNCTION exner_function_1d
281
282!------------------------------------------------------------------------------!
283! Description:
284! ------------
285!> Compute the exner function for scalar arguments.
286!------------------------------------------------------------------------------!
287    FUNCTION exner_function_invers_0d( p )
288
289       IMPLICIT NONE
290
291       REAL(wp), INTENT(IN) ::  p    !< pressure (Pa)
292
293       REAL(wp) ::  exner_function_invers_0d
294!
295!--    compute exner function:
296       exner_function_invers_0d = ( p_0 / p )**( rd_d_cp )
297
298    END FUNCTION exner_function_invers_0d
299
300!------------------------------------------------------------------------------!
301! Description:
302! ------------
303!> Compute the exner function for 1-D array arguments.
304!------------------------------------------------------------------------------!
305    FUNCTION exner_function_invers_1d( p )
306
307       IMPLICIT NONE
308
309       REAL(wp), INTENT(IN), DIMENSION(:) ::  p  !< pressure (Pa)
310
311       REAL(wp), DIMENSION(size(p)) ::  exner_function_invers_1d
312!
313!--    compute exner function:
314       exner_function_invers_1d = ( p_0 / p )**( rd_d_cp )
315
316    END FUNCTION exner_function_invers_1d
317
318!------------------------------------------------------------------------------!
319! Description:
320! ------------
321!> Compute the barometric formula for scalar arguments.
322!------------------------------------------------------------------------------!
323    FUNCTION barometric_formula_0d( z, t_0, p_0)
324
325       IMPLICIT NONE
326
327       REAL(wp), INTENT(IN) ::  z    !< height (m)
328       REAL(wp), INTENT(IN) ::  t_0  !< temperature reference state (K)
329       REAL(wp), INTENT(IN) ::  p_0  !< surface pressure (Pa)
330
331       REAL(wp) ::  barometric_formula_0d
332!
333!--    compute barometric formula:
334       barometric_formula_0d =  p_0 * ( (t_0 - g_d_cp * z) / t_0 )**( cp_d_rd )
335
336    END FUNCTION barometric_formula_0d
337
338!------------------------------------------------------------------------------!
339! Description:
340! ------------
341!> Compute the barometric formula for 1-D array arguments.
342!------------------------------------------------------------------------------!
343    FUNCTION barometric_formula_1d( z, t_0, p_0)
344
345       IMPLICIT NONE
346
347       REAL(wp), INTENT(IN), DIMENSION(:) ::  z  !< height (m)
348       REAL(wp), INTENT(IN) ::  t_0              !< temperature reference state (K)
349       REAL(wp), INTENT(IN) ::  p_0              !< surface pressure (Pa)
350
351       REAL(wp), DIMENSION(size(z)) ::  barometric_formula_1d
352!
353!--    compute barometric formula:
354       barometric_formula_1d =  p_0 * ( (t_0 - g_d_cp * z) / t_0 )**( cp_d_rd )
355
356    END FUNCTION barometric_formula_1d
357
358 END MODULE basic_constants_and_equations_mod
Note: See TracBrowser for help on using the repository browser.