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

Last change on this file since 1612 was 1362, checked in by hoffmann, 10 years ago

last commit documented

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