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

Last change on this file since 1329 was 1323, checked in by raasch, 10 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 5.0 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-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! ------------------
26! $Id: init_cloud_physics.f90 1323 2014-03-20 17:09:54Z raasch $
27!
28! 1322 2014-03-20 16:38:49Z raasch
29! REAL constants defined as wp-kind
30!
31! 1320 2014-03-20 08:40:49Z raasch
32! ONLY-attribute added to USE-statements,
33! kind-parameters added to all INTEGER and REAL declaration statements,
34! kinds are defined in new module mod_kinds,
35! revision history before 2012 removed,
36! comment fields (!:) to be used for variable explanations added to
37! all variable declaration statements
38!
39! 1065 2012-11-22 17:42:36Z hoffmann
40! The Courant number of sedimentation can be controlled with c_sedimentation.
41!
42! 1053 2012-11-13 17:11:03Z hoffmann
43! calculation of the maximum timestep according to the terminal velocity of rain
44! drops in the two moment cloud scheme
45!
46! calculation of frequently used constants (pirho_l, dpirho_l, schmidt_p_1d3,
47! hyrho)
48!
49! 1036 2012-10-22 13:43:42Z raasch
50! code put under GPL (PALM 3.9)
51!
52! 824 2012-02-17 09:09:57Z raasch
53! calculation of b_cond replaced by calculation of bfactor
54!
55! Revision 1.1  2000/04/13 14:37:22  schroeter
56! Initial revision
57!
58!
59! Description:
60! ------------
61! Initialization of parameters for handling cloud-physics
62!------------------------------------------------------------------------------!
63
64    USE arrays_3d,                                                             &
65        ONLY:  dzu, hyp, pt_init, zu
66       
67    USE cloud_parameters,                                                      &
68        ONLY:  bfactor, cp, c_sedimentation, dpirho_l, dt_precipitation,       &
69               hyrho, l_d_cp, l_d_r, l_d_rv, l_v, mass_of_solute,              &
70               molecular_weight_of_solute, molecular_weight_of_water, pirho_l, &
71               pt_d_t, rho_l, r_d, r_v, schmidt, schmidt_p_1d3, t_d_pt,        &
72               vanthoff, w_precipitation
73       
74    USE constants,                                                             &
75        ONLY:  pi
76       
77    USE control_parameters,                                                    &
78        ONLY:  g, icloud_scheme, message_string, precipitation, pt_surface,    &
79               rho_surface, surface_pressure
80   
81    USE indices,                                                               &
82        ONLY:  nzb, nzt
83   
84    USE kinds
85
86    IMPLICIT NONE
87
88    INTEGER(iwp) ::  k      !:
89   
90    REAL(wp) ::  t_surface  !:
91
92    ALLOCATE( hyp(nzb:nzt+1), pt_d_t(nzb:nzt+1), t_d_pt(nzb:nzt+1),  &
93              hyrho(nzb:nzt+1) )
94
95!
96!-- Calculate frequently used parameters
97    l_d_cp = l_v / cp
98    l_d_r  = l_v / r_d
99    l_d_rv = l_v / r_v
100
101    schmidt_p_1d3 = schmidt**( 1.0_wp / 3.0_wp )
102
103    pirho_l  = pi * rho_l / 6.0
104    dpirho_l = 1.0 / pirho_l 
105!
106!-- Calculate timestep according to precipitation
107    IF ( icloud_scheme == 0  .AND.  precipitation )  THEN
108       dt_precipitation = c_sedimentation * MINVAL( dzu(nzb+2:nzt) ) /        &
109                          w_precipitation
110    ENDIF
111!
112!-- Calculate factor used in equation for droplet growth by condensation
113    bfactor = 3.0 * vanthoff * mass_of_solute * molecular_weight_of_water &
114              / ( 4.0 * pi * rho_l * molecular_weight_of_solute )
115!
116!-- Calculate:
117!-- pt / t : ratio of potential and actual temperature (pt_d_t)
118!-- t / pt : ratio of actual and potential temperature (t_d_pt)
119!-- p_0(z) : vertical profile of the hydrostatic pressure (hyp)
120    t_surface = pt_surface * ( surface_pressure / 1000.0 )**0.286
121    DO  k = nzb, nzt+1
122!
123!--    Check temperature in case of too large domain height
124       IF ( ( t_surface - g/cp * zu(k) ) < 0.0 )  THEN
125          WRITE( message_string, * )  'absolute temperature < 0.0 at zu(', k, &
126                                      ') = ', zu(k)
127          CALL message( 'init_cloud_physics', 'PA0142', 1, 2, 0, 6, 0 )
128       ENDIF
129       hyp(k)    = surface_pressure * 100.0 * &
130                   ( (t_surface - g/cp * zu(k)) / t_surface )**(1.0_wp/0.286_wp)
131       pt_d_t(k) = ( 100000.0 / hyp(k) )**0.286
132       t_d_pt(k) = 1.0 / pt_d_t(k)
133       hyrho(k)  = hyp(k) / ( r_d * t_d_pt(k) * pt_init(k) )       
134    ENDDO
135
136!
137!-- Compute reference density
138    rho_surface = surface_pressure * 100.0 / ( r_d * t_surface )
139
140
141 END SUBROUTINE init_cloud_physics
Note: See TracBrowser for help on using the repository browser.