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

Last change on this file since 72 was 72, checked in by raasch, 17 years ago

preliminary changes for precipitation output

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