source: palm/trunk/SOURCE/impact_of_latent_heat.f90 @ 20

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

preliminary version of modified boundary conditions at top

  • Property svn:keywords set to Id
File size: 2.6 KB
Line 
1 MODULE impact_of_latent_heat_mod
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! Calculation extended for gridpoint nzt
7!
8! Former revisions:
9! -----------------
10! $Id: impact_of_latent_heat.f90 19 2007-02-23 04:53:48Z raasch $
11! RCS Log replace by Id keyword, revision history cleaned up
12!
13! Revision 1.5  2004/01/30 10:25:59  raasch
14! Scalar lower k index nzb replaced by 2d-array nzb_2d
15!
16! Revision 1.1  2000/04/13 14:48:40  schroeter
17! Initial revision
18!
19!
20! Description:
21! ------------
22! Calculate the impact of latent heat due to precipitation
23! (simplified Kessler scheme)
24!------------------------------------------------------------------------------!
25
26    PRIVATE
27    PUBLIC impact_of_latent_heat
28
29    INTERFACE impact_of_latent_heat
30       MODULE PROCEDURE impact_of_latent_heat
31       MODULE PROCEDURE impact_of_latent_heat_ij
32    END INTERFACE impact_of_latent_heat
33 
34 CONTAINS
35
36
37!------------------------------------------------------------------------------!
38! Call for all grid points
39!------------------------------------------------------------------------------!
40    SUBROUTINE impact_of_latent_heat
41
42       USE arrays_3d
43       USE cloud_parameters
44       USE constants
45       USE indices
46
47       IMPLICIT NONE
48
49       INTEGER ::  i, j, k
50       REAL    :: precipitation_rate
51
52 
53       DO  i = nxl, nxr
54          DO  j = nys, nyn
55             DO  k = nzb_2d(j,i)+1, nzt
56
57                IF ( ql(k,j,i) > ql_crit )  THEN
58                   precipitation_rate = prec_time_const * &
59                                        ( ql(k,j,i) - ql_crit )
60                ELSE
61                   precipitation_rate = 0.0
62                ENDIF
63                tend(k,j,i) = tend(k,j,i) + precipitation_rate * l_d_cp * &
64                                            pt_d_t(k)
65
66             ENDDO
67          ENDDO
68       ENDDO
69
70    END SUBROUTINE impact_of_latent_heat
71
72
73!------------------------------------------------------------------------------!
74! Call for grid point i,j
75!------------------------------------------------------------------------------!
76    SUBROUTINE impact_of_latent_heat_ij( i, j )
77
78       USE arrays_3d
79       USE cloud_parameters
80       USE constants
81       USE indices
82   
83       IMPLICIT NONE
84
85       INTEGER :: i, j, k
86       REAL    :: precipitation_rate
87
88
89       DO  k = nzb_2d(j,i)+1, nzt
90
91          IF ( ql(k,j,i) > ql_crit )  THEN
92             precipitation_rate = prec_time_const * ( ql(k,j,i) - ql_crit )
93          ELSE
94             precipitation_rate = 0.0
95          ENDIF
96          tend(k,j,i) = tend(k,j,i) + precipitation_rate * l_d_cp * pt_d_t(k)
97
98       ENDDO
99
100    END SUBROUTINE impact_of_latent_heat_ij
101
102 END MODULE impact_of_latent_heat_mod
Note: See TracBrowser for help on using the repository browser.