source: palm/tags/release-3.1c/SOURCE/calc_liquid_water_content.f90 @ 4011

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

comments prepared for 3.1c

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