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

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

Changed precomputed fractions from basic constants to be variable based

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