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

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

  • Property svn:keywords set to Id
File size: 5.7 KB
Line 
1!> @file init_cloud_physics.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2014 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21! Code annotations made doxygen readable
22!
23! Former revisions:
24! ------------------
25! $Id: init_cloud_physics.f90 1682 2015-10-07 23:56:08Z knoop $
26!
27! 1361 2014-04-16 15:17:48Z hoffmann
28! sed_qc_const is now calculated here (2-moment microphysics)
29!
30! 1353 2014-04-08 15:21:23Z heinze
31! REAL constants provided with KIND-attribute
32!
33! 1334 2014-03-25 12:21:40Z heinze
34! Bugfix: REAL constants provided with KIND-attribute
35!
36! 1322 2014-03-20 16:38:49Z raasch
37! REAL constants defined as wp-kind
38!
39! 1320 2014-03-20 08:40:49Z raasch
40! ONLY-attribute added to USE-statements,
41! kind-parameters added to all INTEGER and REAL declaration statements,
42! kinds are defined in new module mod_kinds,
43! revision history before 2012 removed,
44! comment fields (!:) to be used for variable explanations added to
45! all variable declaration statements
46!
47! 1065 2012-11-22 17:42:36Z hoffmann
48! The Courant number of sedimentation can be controlled with c_sedimentation.
49!
50! 1053 2012-11-13 17:11:03Z hoffmann
51! calculation of the maximum timestep according to the terminal velocity of rain
52! drops in the two moment cloud scheme
53!
54! calculation of frequently used constants (pirho_l, dpirho_l, schmidt_p_1d3,
55! hyrho)
56!
57! 1036 2012-10-22 13:43:42Z raasch
58! code put under GPL (PALM 3.9)
59!
60! 824 2012-02-17 09:09:57Z raasch
61! calculation of b_cond replaced by calculation of bfactor
62!
63! Revision 1.1  2000/04/13 14:37:22  schroeter
64! Initial revision
65!
66!
67! Description:
68! ------------
69!> Initialization of parameters for handling cloud-physics
70!------------------------------------------------------------------------------!
71 SUBROUTINE init_cloud_physics
72 
73
74    USE arrays_3d,                                                             &
75        ONLY:  dzu, hyp, pt_init, zu
76       
77    USE cloud_parameters,                                                      &
78        ONLY:  bfactor, cp, c_sedimentation, dpirho_l, dt_precipitation,       &
79               hyrho, k_st, l_d_cp, l_d_r, l_d_rv, l_v, mass_of_solute,  &
80               molecular_weight_of_solute, molecular_weight_of_water, pirho_l, &
81               pt_d_t, rho_l, r_d, r_v, sed_qc_const, schmidt, schmidt_p_1d3,  &
82               sigma_gc, t_d_pt, vanthoff, w_precipitation
83       
84    USE constants,                                                             &
85        ONLY:  pi
86       
87    USE control_parameters,                                                    &
88        ONLY:  g, icloud_scheme, message_string, precipitation, pt_surface,    &
89               rho_surface, surface_pressure
90   
91    USE indices,                                                               &
92        ONLY:  nzb, nzt
93   
94    USE kinds
95
96    IMPLICIT NONE
97
98    INTEGER(iwp) ::  k      !<
99   
100    REAL(wp) ::  t_surface  !<
101
102    ALLOCATE( hyp(nzb:nzt+1), pt_d_t(nzb:nzt+1), t_d_pt(nzb:nzt+1),            &
103              hyrho(nzb:nzt+1) )
104
105!
106!-- Calculate frequently used parameters
107    l_d_cp = l_v / cp
108    l_d_r  = l_v / r_d
109    l_d_rv = l_v / r_v
110
111    schmidt_p_1d3 = schmidt**( 1.0_wp / 3.0_wp )
112
113    pirho_l  = pi * rho_l / 6.0_wp
114    dpirho_l = 1.0_wp / pirho_l
115!
116!-- constant fot the sedimentation of cloud water (2-moment cloud physics)
117    sed_qc_const = k_st * ( 3.0_wp / ( 4.0_wp * pi * rho_l )                   &
118                          )**( 2.0_wp / 3.0_wp ) *                             &
119                   EXP( 5.0_wp * LOG( sigma_gc )**2 )
120!
121!-- Calculate timestep according to precipitation
122    IF ( icloud_scheme == 0  .AND.  precipitation )  THEN
123       dt_precipitation = c_sedimentation * MINVAL( dzu(nzb+2:nzt) ) /         &
124                          w_precipitation
125    ENDIF
126!
127!-- Calculate factor used in equation for droplet growth by condensation
128    bfactor = 3.0_wp * vanthoff * mass_of_solute * molecular_weight_of_water   &
129              / ( 4.0_wp * pi * rho_l * molecular_weight_of_solute )
130!
131!-- Calculate:
132!-- pt / t : ratio of potential and actual temperature (pt_d_t)
133!-- t / pt : ratio of actual and potential temperature (t_d_pt)
134!-- p_0(z) : vertical profile of the hydrostatic pressure (hyp)
135    t_surface = pt_surface * ( surface_pressure / 1000.0_wp )**0.286_wp
136    DO  k = nzb, nzt+1
137!
138!--    Check temperature in case of too large domain height
139       IF ( ( t_surface - g/cp * zu(k) ) < 0.0_wp )  THEN
140          WRITE( message_string, * )  'absolute temperature < 0.0 at zu(', k, &
141                                      ') = ', zu(k)
142          CALL message( 'init_cloud_physics', 'PA0142', 1, 2, 0, 6, 0 )
143       ENDIF
144       hyp(k)    = surface_pressure * 100.0_wp * &
145                   ( (t_surface - g/cp * zu(k)) / t_surface )**(1.0_wp/0.286_wp)
146       pt_d_t(k) = ( 100000.0_wp / hyp(k) )**0.286_wp
147       t_d_pt(k) = 1.0_wp / pt_d_t(k)
148       hyrho(k)  = hyp(k) / ( r_d * t_d_pt(k) * pt_init(k) )       
149    ENDDO
150
151!
152!-- Compute reference density
153    rho_surface = surface_pressure * 100.0_wp / ( r_d * t_surface )
154
155
156 END SUBROUTINE init_cloud_physics
Note: See TracBrowser for help on using the repository browser.