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

Last change on this file since 3622 was 3449, checked in by suehring, 5 years ago

Branch resler -r 3439 re-integrated into current trunk: RTM 3.0, transpiration of plant canopy, output fixes in USM

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