source: palm/trunk/SOURCE/impact_of_latent_heat.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: 3.1 KB
RevLine 
[1]1 MODULE impact_of_latent_heat_mod
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: impact_of_latent_heat.f90,v $
11! Revision 1.5  2004/01/30 10:25:59  raasch
12! Scalar lower k index nzb replaced by 2d-array nzb_2d
13!
14! Revision 1.4  2003/03/12 16:32:14  raasch
15! Full code replaced in the call for all gridpoints instead of calling the
16! _ij version (required by NEC, because otherwise no vectorization)
17!
18! Revision 1.3  2002/06/11 13:10:06  raasch
19! Former subroutine changed to a module which allows to be called for all grid
20! points of a single vertical column with index i,j or for all grid points by
21! using function overloading.
22!
23! Revision 1.2  2001/01/22 06:52:34  raasch
24! Module test_variables removed
25!
26! Revision 1.1  2000/04/13 14:48:40  schroeter
27! Initial revision
28!
29!
30! Description:
31! ------------
32! Calculate the impact of latent heat due to precipitation
33! (simplified Kessler scheme)
34!------------------------------------------------------------------------------!
35
36    PRIVATE
37    PUBLIC impact_of_latent_heat
38
39    INTERFACE impact_of_latent_heat
40       MODULE PROCEDURE impact_of_latent_heat
41       MODULE PROCEDURE impact_of_latent_heat_ij
42    END INTERFACE impact_of_latent_heat
43 
44 CONTAINS
45
46
47!------------------------------------------------------------------------------!
48! Call for all grid points
49!------------------------------------------------------------------------------!
50    SUBROUTINE impact_of_latent_heat
51
52       USE arrays_3d
53       USE cloud_parameters
54       USE constants
55       USE indices
56
57       IMPLICIT NONE
58
59       INTEGER ::  i, j, k
60       REAL    :: precipitation_rate
61
62 
63       DO  i = nxl, nxr
64          DO  j = nys, nyn
65             DO  k = nzb_2d(j,i)+1, nzt-1   
66
67                IF ( ql(k,j,i) > ql_crit )  THEN
68                   precipitation_rate = prec_time_const * &
69                                        ( ql(k,j,i) - ql_crit )
70                ELSE
71                   precipitation_rate = 0.0
72                ENDIF
73                tend(k,j,i) = tend(k,j,i) + precipitation_rate * l_d_cp * &
74                                            pt_d_t(k)
75
76             ENDDO
77          ENDDO
78       ENDDO
79
80    END SUBROUTINE impact_of_latent_heat
81
82
83!------------------------------------------------------------------------------!
84! Call for grid point i,j
85!------------------------------------------------------------------------------!
86    SUBROUTINE impact_of_latent_heat_ij( i, j )
87
88       USE arrays_3d
89       USE cloud_parameters
90       USE constants
91       USE indices
92   
93       IMPLICIT NONE
94
95       INTEGER :: i, j, k
96       REAL    :: precipitation_rate
97
98
99       DO  k = nzb_2d(j,i)+1, nzt-1   
100
101          IF ( ql(k,j,i) > ql_crit )  THEN
102             precipitation_rate = prec_time_const * ( ql(k,j,i) - ql_crit )
103          ELSE
104             precipitation_rate = 0.0
105          ENDIF
106          tend(k,j,i) = tend(k,j,i) + precipitation_rate * l_d_cp * pt_d_t(k)
107
108       ENDDO
109
110    END SUBROUTINE impact_of_latent_heat_ij
111
112 END MODULE impact_of_latent_heat_mod
Note: See TracBrowser for help on using the repository browser.