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

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