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

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

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

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