source: palm/trunk/SOURCE/calc_precipitation.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: 3.0 KB
Line 
1 MODULE calc_precipitation_mod
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: calc_precipitation.f90,v $
11! Revision 1.5  2004/01/30 10:15:57  raasch
12! Scalar lower k index nzb replaced by 2d-array nzb_2d
13!
14! Revision 1.4  2003/03/12 16:21:23  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 12:38:58  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 05:32:25  raasch
24! Module test_variables removed
25!
26! Revision 1.1  2000/04/13 14:45:22  schroeter
27! Initial revision
28!
29!
30!
31! Description:
32! ------------
33! Calculate the change of total water content due to precipitation
34! (simplified Kessler scheme)
35!------------------------------------------------------------------------------!
36
37    PRIVATE
38    PUBLIC calc_precipitation
39
40    INTERFACE calc_precipitation
41       MODULE PROCEDURE calc_precipitation
42       MODULE PROCEDURE calc_precipitation_ij
43    END INTERFACE calc_precipitation
44 
45 CONTAINS
46
47
48!------------------------------------------------------------------------------!
49! Call for all grid points
50!------------------------------------------------------------------------------!
51    SUBROUTINE calc_precipitation
52
53       USE arrays_3d
54       USE cloud_parameters
55       USE constants
56       USE indices
57
58       IMPLICIT NONE
59
60       INTEGER ::  i, j, k
61       REAL    :: precipitation_rate
62
63 
64       DO  i = nxl, nxr
65          DO  j = nys, nyn
66             DO  k = nzb_2d(j,i)+1, nzt-1   
67
68                IF ( ql(k,j,i) > ql_crit )  THEN
69                   precipitation_rate = prec_time_const * &
70                                        ( ql(k,j,i) - ql_crit )
71                ELSE
72                   precipitation_rate = 0.0
73                ENDIF
74                tend(k,j,i) = tend(k,j,i) - precipitation_rate
75
76             ENDDO
77          ENDDO
78       ENDDO
79
80    END SUBROUTINE calc_precipitation
81
82
83!------------------------------------------------------------------------------!
84! Call for grid point i,j
85!------------------------------------------------------------------------------!
86    SUBROUTINE calc_precipitation_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
107
108       ENDDO
109
110    END SUBROUTINE calc_precipitation_ij
111
112 END MODULE calc_precipitation_mod
Note: See TracBrowser for help on using the repository browser.