source: palm/trunk/SOURCE/init_cloud_physics.f90 @ 1061

Last change on this file since 1061 was 1054, checked in by hoffmann, 12 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 3.9 KB
Line 
1 SUBROUTINE init_cloud_physics
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later 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-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23! Former revisions:
24! ------------------
25! $Id: init_cloud_physics.f90 1054 2012-11-13 17:30:09Z raasch $
26!
27! 1053 2012-11-13 17:11:03Z hoffmann
28! calculation of the maximum timestep according to the terminal velocity of rain
29! drops in the two moment cloud scheme
30!
31! calculation of frequently used constants (pirho_l, dpirho_l, schmidt_p_1d3,
32! hyrho)
33!
34! 1036 2012-10-22 13:43:42Z raasch
35! code put under GPL (PALM 3.9)
36!
37! 824 2012-02-17 09:09:57Z raasch
38! calculation of b_cond replaced by calculation of bfactor
39!
40! 221 2009-01-12 15:32:23Z raasch
41! Bugfix: abort in case that absolute temperature is below zero
42!
43! 95 2007-06-02 16:48:38Z raasch
44! hydro_press renamed hyp
45!
46! February 2007
47! RCS Log replace by Id keyword, revision history cleaned up
48!
49! Revision 1.5  2005/06/26 19:55:58  raasch
50! Initialization of cloud droplet constants, gas_constant renamed r_d,
51! latent_heat renamed l_v
52!
53! Revision 1.1  2000/04/13 14:37:22  schroeter
54! Initial revision
55!
56!
57! Description:
58! ------------
59! Initialization of parameters for handling cloud-physics
60!------------------------------------------------------------------------------!
61
62    USE arrays_3d
63    USE cloud_parameters
64    USE constants
65    USE control_parameters
66    USE grid_variables
67    USE indices
68
69    IMPLICIT NONE
70
71    INTEGER ::  k
72    REAL    ::  t_surface
73
74    ALLOCATE( hyp(nzb:nzt+1), pt_d_t(nzb:nzt+1), t_d_pt(nzb:nzt+1),  &
75              hyrho(nzb:nzt+1) )
76
77!
78!-- Calculate frequently used parameters
79    l_d_cp = l_v / cp
80    l_d_r  = l_v / r_d
81    l_d_rv = l_v / r_v
82
83    schmidt_p_1d3 = schmidt**( 1.0 / 3.0 )
84
85    pirho_l  = pi * rho_l / 6.0
86    dpirho_l = 1.0 / pirho_l 
87!
88!-- Calculate timestep according to precipitation
89    IF ( icloud_scheme == 0  .AND.  precipitation )  THEN
90       dt_precipitation = MINVAL( dzu(nzb+2:nzt) ) / w_precipitation
91    ENDIF
92!
93!-- Calculate factor used in equation for droplet growth by condensation
94    bfactor = 3.0 * vanthoff * mass_of_solute * molecular_weight_of_water &
95              / ( 4.0 * pi * rho_l * molecular_weight_of_solute )
96!
97!-- Calculate:
98!-- pt / t : ratio of potential and actual temperature (pt_d_t)
99!-- t / pt : ratio of actual and potential temperature (t_d_pt)
100!-- p_0(z) : vertical profile of the hydrostatic pressure (hyp)
101    t_surface = pt_surface * ( surface_pressure / 1000.0 )**0.286
102    DO  k = nzb, nzt+1
103!
104!--    Check temperature in case of too large domain height
105       IF ( ( t_surface - g/cp * zu(k) ) < 0.0 )  THEN
106          WRITE( message_string, * )  'absolute temperature < 0.0 at zu(', k, &
107                                      ') = ', zu(k)
108          CALL message( 'init_cloud_physics', 'PA0142', 1, 2, 0, 6, 0 )
109       ENDIF
110       hyp(k)    = surface_pressure * 100.0 * &
111                   ( (t_surface - g/cp * zu(k)) / t_surface )**(1.0/0.286)
112       pt_d_t(k) = ( 100000.0 / hyp(k) )**0.286
113       t_d_pt(k) = 1.0 / pt_d_t(k)
114       hyrho(k)  = hyp(k) / ( r_d * t_d_pt(k) * pt_init(k) )       
115    ENDDO
116
117!
118!-- Compute reference density
119    rho_surface = surface_pressure * 100.0 / ( r_d * t_surface )
120
121
122 END SUBROUTINE init_cloud_physics
Note: See TracBrowser for help on using the repository browser.