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

Last change on this file since 3255 was 3241, checked in by raasch, 6 years ago

various changes to avoid compiler warnings (mainly removal of unused variables)

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