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

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

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

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