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

Last change on this file since 4181 was 4180, checked in by scharf, 5 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

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