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

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

Bugfix in calculation of precipitation_rate

  • Property svn:keywords set to Id
File size: 4.1 KB
RevLine 
[1]1 MODULE calc_precipitation_mod
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
[403]6! Bugfix in calculation of precipitation_rate(j,i)
[1]7!
8! Former revisions:
9! -----------------
[3]10! $Id: calc_precipitation.f90 403 2009-10-22 13:57:16Z franke $
[39]11!
[77]12! 73 2007-03-20 08:33:14Z raasch
13! Precipitation rate and amount are calculated/stored,
14! + module control_parameters
15!
[39]16! 19 2007-02-23 04:53:48Z raasch
17! Calculation extended for gridpoint nzt
18!
[3]19! RCS Log replace by Id keyword, revision history cleaned up
20!
[1]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
[403]42
[1]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
[72]54       USE control_parameters
[1]55       USE indices
56
57       IMPLICIT NONE
58
59       INTEGER ::  i, j, k
[72]60       REAL    ::  dqdt_precip
[1]61
[403]62       precipitation_rate = 0.0
[72]63
[1]64       DO  i = nxl, nxr
65          DO  j = nys, nyn
[19]66             DO  k = nzb_2d(j,i)+1, nzt
[1]67
68                IF ( ql(k,j,i) > ql_crit )  THEN
[72]69                   dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit )
[1]70                ELSE
[72]71                   dqdt_precip = 0.0
[1]72                ENDIF
[72]73                tend(k,j,i) = tend(k,j,i) - dqdt_precip
74!
[73]75!--             Precipitation rate in kg / m**2 / s (= mm/s)
[72]76                precipitation_rate(j,i) = precipitation_rate(j,i) + &
[73]77                                          dqdt_precip * dzw(k)
[1]78
79             ENDDO
[72]80!
[73]81!--          Sum up the precipitation amount, unit kg / m**2 (= mm)
[72]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
[1]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
[72]103       USE control_parameters
[1]104       USE indices
[403]105
[1]106       IMPLICIT NONE
107
[72]108       INTEGER ::  i, j, k
109       REAL    ::  dqdt_precip
[1]110
[403]111       precipitation_rate(j,i) = 0.0
[1]112
[72]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
[19]116       DO  k = nzb_2d(j,i)+1, nzt
[1]117
118          IF ( ql(k,j,i) > ql_crit )  THEN
[72]119             dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit )
[1]120          ELSE
[72]121             dqdt_precip = 0.0
[1]122          ENDIF
[72]123          tend(k,j,i) = tend(k,j,i) - dqdt_precip
[1]124
[72]125!
[403]126!--       Precipitation rate in kg / m**2 / s (= mm/s)
127          precipitation_rate(j,i) = precipitation_rate(j,i) + dqdt_precip * &
128                                                              dzw(k)
[72]129
[1]130       ENDDO
131
[72]132!
[403]133!--    Sum up the precipitation amount , unit kg / m**2 (= mm)
[72]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
[1]141    END SUBROUTINE calc_precipitation_ij
142
143 END MODULE calc_precipitation_mod
Note: See TracBrowser for help on using the repository browser.