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

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

last commit documented

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