source: palm/trunk/SOURCE/calc_precipitation.f90 @ 550

Last change on this file since 550 was 484, checked in by raasch, 14 years ago

typo in file headers removed

  • Property svn:keywords set to Id
File size: 4.2 KB
Line 
1 MODULE calc_precipitation_mod
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Id: calc_precipitation.f90 484 2010-02-05 07:36:54Z maronga $
11!
12! 403 2009-10-22 13:57:16Z franke
13! Bugfix in calculation of precipitation_rate(j,i)
14!
15! 73 2007-03-20 08:33:14Z raasch
16! Precipitation rate and amount are calculated/stored,
17! + module control_parameters
18!
19! 19 2007-02-23 04:53:48Z raasch
20! Calculation extended for gridpoint nzt
21!
22! RCS Log replace by Id keyword, revision history cleaned up
23!
24! Revision 1.5  2004/01/30 10:15:57  raasch
25! Scalar lower k index nzb replaced by 2d-array nzb_2d
26!
27! Revision 1.1  2000/04/13 14:45:22  schroeter
28! Initial revision
29!
30!
31!
32! Description:
33! ------------
34! Calculate the change of total water content due to precipitation
35! (simplified Kessler scheme)
36!------------------------------------------------------------------------------!
37
38    PRIVATE
39    PUBLIC calc_precipitation
40
41    INTERFACE calc_precipitation
42       MODULE PROCEDURE calc_precipitation
43       MODULE PROCEDURE calc_precipitation_ij
44    END INTERFACE calc_precipitation
45
46 CONTAINS
47
48
49!------------------------------------------------------------------------------!
50! Call for all grid points
51!------------------------------------------------------------------------------!
52    SUBROUTINE calc_precipitation
53
54       USE arrays_3d
55       USE cloud_parameters
56       USE constants
57       USE control_parameters
58       USE indices
59
60       IMPLICIT NONE
61
62       INTEGER ::  i, j, k
63       REAL    ::  dqdt_precip
64
65       precipitation_rate = 0.0
66
67       DO  i = nxl, nxr
68          DO  j = nys, nyn
69             DO  k = nzb_2d(j,i)+1, nzt
70
71                IF ( ql(k,j,i) > ql_crit )  THEN
72                   dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit )
73                ELSE
74                   dqdt_precip = 0.0
75                ENDIF
76                tend(k,j,i) = tend(k,j,i) - dqdt_precip
77!
78!--             Precipitation rate in kg / m**2 / s (= mm/s)
79                precipitation_rate(j,i) = precipitation_rate(j,i) + &
80                                          dqdt_precip * dzw(k)
81
82             ENDDO
83!
84!--          Sum up the precipitation amount, unit kg / m**2 (= mm)
85             IF ( intermediate_timestep_count ==         &
86                  intermediate_timestep_count_max  .AND. &
87                  ( dt_do2d_xy-time_do2d_xy ) < precipitation_amount_interval )&
88             THEN
89                precipitation_amount(j,i) = precipitation_amount(j,i) + &
90                                            precipitation_rate(j,i) * dt_3d
91             ENDIF
92          ENDDO
93       ENDDO
94
95    END SUBROUTINE calc_precipitation
96
97
98!------------------------------------------------------------------------------!
99! Call for grid point i,j
100!------------------------------------------------------------------------------!
101    SUBROUTINE calc_precipitation_ij( i, j )
102
103       USE arrays_3d
104       USE cloud_parameters
105       USE constants
106       USE control_parameters
107       USE indices
108
109       IMPLICIT NONE
110
111       INTEGER ::  i, j, k
112       REAL    ::  dqdt_precip
113
114       precipitation_rate(j,i) = 0.0
115
116!
117!--    Ghostpoints are included (although not needed for tend) to avoid a later
118!--    exchange of these data for the precipitation amount/rate arrays
119       DO  k = nzb_2d(j,i)+1, nzt
120
121          IF ( ql(k,j,i) > ql_crit )  THEN
122             dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit )
123          ELSE
124             dqdt_precip = 0.0
125          ENDIF
126          tend(k,j,i) = tend(k,j,i) - dqdt_precip
127
128!
129!--       Precipitation rate in kg / m**2 / s (= mm/s)
130          precipitation_rate(j,i) = precipitation_rate(j,i) + dqdt_precip * &
131                                                              dzw(k)
132
133       ENDDO
134
135!
136!--    Sum up the precipitation amount , unit kg / m**2 (= mm)
137       IF ( intermediate_timestep_count == intermediate_timestep_count_max     &
138            .AND. ( dt_do2d_xy-time_do2d_xy ) < precipitation_amount_interval )&
139       THEN
140          precipitation_amount(j,i) = precipitation_amount(j,i) + &
141                                      precipitation_rate(j,i) * dt_3d
142       ENDIF
143
144    END SUBROUTINE calc_precipitation_ij
145
146 END MODULE calc_precipitation_mod
Note: See TracBrowser for help on using the repository browser.