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

Last change on this file since 1807 was 1692, checked in by maronga, 8 years ago

last commit documented

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