source: palm/trunk/SOURCE/calc_liquid_water_content.f90 @ 1

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

Initial repository layout and content

File size: 2.3 KB
RevLine 
[1]1 SUBROUTINE calc_liquid_water_content
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: calc_liquid_water_content.f90,v $
11! Revision 1.5  2005/03/26 15:22:06  raasch
12! Arguments for non-cyclic boundary conditions added to argument list of
13! routine exchange_horiz,
14! ql calculated for the ghost points, exchange of ghost points removed
15!
16! Revision 1.4  2004/01/30 10:15:13  raasch
17! Scalar lower k index nzb replaced by 2d-array nzb_2d
18!
19! Revision 1.3  2001/01/22 05:30:59  raasch
20! Module test_variables removed
21!
22! Revision 1.2  2000/06/13 07:49:32  schroeter
23! Horizontal boundary conditions (cyclic) of ql will be set now
24!
25! Revision 1.1  2000/04/13 14:50:45  schroeter
26! Initial revision
27!
28!
29!
30! Description:
31! ------------
32! Calculation of the liquid water content (0%-or-100%-scheme)
33!------------------------------------------------------------------------------!
34
35
36    USE arrays_3d
37    USE cloud_parameters
38    USE constants
39    USE grid_variables
40    USE indices
41    USE pegrid
42
43    IMPLICIT NONE
44
45    INTEGER :: i, j, k
46
47    REAL :: alpha, e_s, q_s, t_l
48
49    DO  i = nxl-1, nxr+1
50       DO  j = nys-1, nyn+1
51          DO  k = nzb_2d(j,i)+1, nzt
52
53!
54!--          Compute the liquid water temperature
55             t_l = t_d_pt(k) * pt(k,j,i)
56
57!
58!--          Compute saturation water vapor pressure at t_l
59             e_s = 610.78 * EXP( 17.269 * ( t_l - 273.16 ) / &
60                                          ( t_l - 35.86 ) )
61
62!
63!--          Compute approximation of saturation humidity
64             q_s = 0.622 * e_s / &
65                   ( hydro_press(k) - 0.378 * e_s )
66
67!
68!--          Correction factor
69             alpha = 0.622 * l_d_r * l_d_cp / ( t_l * t_l )
70
71!
72!--          Correction of the approximated value
73!--          (see: Cuijpers + Duynkerke, 1993, JAS, 23)
74             q_s = q_s * ( 1.0 + alpha * q(k,j,i) ) / ( 1.0 + alpha * q_s )
75
76!
77!--          Compute the liquid water content
78             IF ( ( q(k,j,i) - q_s ) > 0.0 ) THEN
79                ql(k,j,i) = q(k,j,i) - q_s
80             ELSE
81                ql(k,j,i) = 0.0 
82             ENDIF
83
84          ENDDO
85       ENDDO
86    ENDDO
87   
88!
89!-- Setting boundary values of ql
90!    CALL exchange_horiz( ql, 0, 0 )   
91
92 END SUBROUTINE calc_liquid_water_content
Note: See TracBrowser for help on using the repository browser.