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

Last change on this file since 2 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 2.4 KB
Line 
1 SUBROUTINE init_cloud_physics
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! ------------------
10! $Log: init_cloud_physics.f90,v $
11! Revision 1.5  2005/06/26 19:55:58  raasch
12! Initialization of cloud droplet constants, gas_constant renamed r_d,
13! latent_heat renamed l_v
14!
15! Revision 1.4  2001/03/30 07:26:30  raasch
16! Translation of remaining German identifiers (variables, subroutines, etc.),
17! surface_pressure keeps unit hPa and is not converted to Pa
18!
19! Revision 1.3  2001/01/25 07:03:10  raasch
20! Module test_variables removed
21!
22! Revision 1.2  2001/01/22 09:16:57  schroeter
23! To calculate verticle pressure profile use actual surface-temperature in
24! place of potential temperature as reference value.
25!
26! Revision 1.1  2000/04/13 14:37:22  schroeter
27! Initial revision
28!
29!
30! Description:
31! ------------
32! Initialization of parameters for handling cloud-physics
33!------------------------------------------------------------------------------!
34
35    USE arrays_3d
36    USE cloud_parameters
37    USE control_parameters
38    USE grid_variables
39    USE indices
40
41    IMPLICIT NONE
42
43    INTEGER ::  k
44    REAL    ::  t_surface
45
46    ALLOCATE( hydro_press(nzb:nzt+1), pt_d_t(nzb:nzt+1), t_d_pt(nzb:nzt+1) )
47
48!
49!-- Compute frequently used parameters
50    l_d_cp = l_v / cp
51    l_d_r  = l_v / r_d
52    l_d_rv = l_v / r_v
53
54!
55!-- Constant b in equation for droplet growth by condensation / evaporation.
56!-- Factor 1E-3 is needed because formula is in cgs units
57    mass_of_solute = 1.0E-17            ! in kg
58    molecular_weight_of_solute = 58.5   ! NaCl
59    b_cond = 4.3 * 2.0 * mass_of_solute / molecular_weight_of_solute * 1.0E-6
60
61!
62!-- Calculate:
63!-- pt / t : ratio of potential and actual temperature (pt_d_t)
64!-- t / pt : ratio of actual and potential temperature (t_d_pt)
65!-- p_0(z) : vertical profile of the hydrostatic pressure (hydro_press)
66    t_surface = pt_surface * ( surface_pressure / 1000.0 )**0.286
67    DO  k = nzb, nzt+1
68       hydro_press(k) = surface_pressure * 100.0 * &
69                        ( (t_surface - g/cp * zu(k)) / t_surface )**(1.0/0.286)
70       pt_d_t(k)      = ( 100000.0 / hydro_press(k) )**0.286
71       t_d_pt(k)      = 1.0 / pt_d_t(k)       
72    ENDDO
73
74!
75!-- Compute reference density
76    rho_surface = surface_pressure * 100.0 / ( r_d * t_surface )
77
78
79 END SUBROUTINE init_cloud_physics
Note: See TracBrowser for help on using the repository browser.