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

Last change on this file since 1834 was 1823, checked in by hoffmann, 8 years ago

last commit documented

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