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

Last change on this file since 421 was 403, checked in by franke, 14 years ago

Bugfix in calculation of precipitation_rate

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