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

Last change on this file since 2716 was 2716, checked in by kanani, 6 years ago

Correction of "Former revisions" section

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