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

Last change on this file since 1046 was 1037, checked in by raasch, 11 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 5.1 KB
Line 
1 MODULE calc_precipitation_mod
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: calc_precipitation.f90 484 2010-02-05 07:36:54Z raasch
27!
28! 1036 2012-10-22 13:43:42Z raasch
29! code put under GPL (PALM 3.9)
30!
31! 403 2009-10-22 13:57:16Z franke
32! Bugfix in calculation of precipitation_rate(j,i)
33!
34! 73 2007-03-20 08:33:14Z raasch
35! Precipitation rate and amount are calculated/stored,
36! + module control_parameters
37!
38! 19 2007-02-23 04:53:48Z raasch
39! Calculation extended for gridpoint nzt
40!
41! RCS Log replace by Id keyword, revision history cleaned up
42!
43! Revision 1.5  2004/01/30 10:15:57  raasch
44! Scalar lower k index nzb replaced by 2d-array nzb_2d
45!
46! Revision 1.1  2000/04/13 14:45:22  schroeter
47! Initial revision
48!
49!
50!
51! Description:
52! ------------
53! Calculate the change of total water content due to precipitation
54! (simplified Kessler scheme)
55!------------------------------------------------------------------------------!
56
57    PRIVATE
58    PUBLIC calc_precipitation
59
60    INTERFACE calc_precipitation
61       MODULE PROCEDURE calc_precipitation
62       MODULE PROCEDURE calc_precipitation_ij
63    END INTERFACE calc_precipitation
64
65 CONTAINS
66
67
68!------------------------------------------------------------------------------!
69! Call for all grid points
70!------------------------------------------------------------------------------!
71    SUBROUTINE calc_precipitation
72
73       USE arrays_3d
74       USE cloud_parameters
75       USE constants
76       USE control_parameters
77       USE indices
78
79       IMPLICIT NONE
80
81       INTEGER ::  i, j, k
82       REAL    ::  dqdt_precip
83
84       precipitation_rate = 0.0
85
86       DO  i = nxl, nxr
87          DO  j = nys, nyn
88             DO  k = nzb_2d(j,i)+1, nzt
89
90                IF ( ql(k,j,i) > ql_crit )  THEN
91                   dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit )
92                ELSE
93                   dqdt_precip = 0.0
94                ENDIF
95                tend(k,j,i) = tend(k,j,i) - dqdt_precip
96!
97!--             Precipitation rate in kg / m**2 / s (= mm/s)
98                precipitation_rate(j,i) = precipitation_rate(j,i) + &
99                                          dqdt_precip * dzw(k)
100
101             ENDDO
102!
103!--          Sum up the precipitation amount, unit kg / m**2 (= mm)
104             IF ( intermediate_timestep_count ==         &
105                  intermediate_timestep_count_max  .AND. &
106                  ( dt_do2d_xy-time_do2d_xy ) < precipitation_amount_interval )&
107             THEN
108                precipitation_amount(j,i) = precipitation_amount(j,i) + &
109                                            precipitation_rate(j,i) * dt_3d
110             ENDIF
111          ENDDO
112       ENDDO
113
114    END SUBROUTINE calc_precipitation
115
116
117!------------------------------------------------------------------------------!
118! Call for grid point i,j
119!------------------------------------------------------------------------------!
120    SUBROUTINE calc_precipitation_ij( i, j )
121
122       USE arrays_3d
123       USE cloud_parameters
124       USE constants
125       USE control_parameters
126       USE indices
127
128       IMPLICIT NONE
129
130       INTEGER ::  i, j, k
131       REAL    ::  dqdt_precip
132
133       precipitation_rate(j,i) = 0.0
134
135!
136!--    Ghostpoints are included (although not needed for tend) to avoid a later
137!--    exchange of these data for the precipitation amount/rate arrays
138       DO  k = nzb_2d(j,i)+1, nzt
139
140          IF ( ql(k,j,i) > ql_crit )  THEN
141             dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit )
142          ELSE
143             dqdt_precip = 0.0
144          ENDIF
145          tend(k,j,i) = tend(k,j,i) - dqdt_precip
146
147!
148!--       Precipitation rate in kg / m**2 / s (= mm/s)
149          precipitation_rate(j,i) = precipitation_rate(j,i) + dqdt_precip * &
150                                                              dzw(k)
151
152       ENDDO
153
154!
155!--    Sum up the precipitation amount , unit kg / m**2 (= mm)
156       IF ( intermediate_timestep_count == intermediate_timestep_count_max     &
157            .AND. ( dt_do2d_xy-time_do2d_xy ) < precipitation_amount_interval )&
158       THEN
159          precipitation_amount(j,i) = precipitation_amount(j,i) + &
160                                      precipitation_rate(j,i) * dt_3d
161       ENDIF
162
163    END SUBROUTINE calc_precipitation_ij
164
165 END MODULE calc_precipitation_mod
Note: See TracBrowser for help on using the repository browser.