MODULE calc_precipitation_mod !------------------------------------------------------------------------------! ! Current revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: calc_precipitation.f90 484 2010-02-05 07:36:54Z maronga $ ! ! 403 2009-10-22 13:57:16Z franke ! Bugfix in calculation of precipitation_rate(j,i) ! ! 73 2007-03-20 08:33:14Z raasch ! Precipitation rate and amount are calculated/stored, ! + module control_parameters ! ! 19 2007-02-23 04:53:48Z raasch ! Calculation extended for gridpoint nzt ! ! RCS Log replace by Id keyword, revision history cleaned up ! ! Revision 1.5 2004/01/30 10:15:57 raasch ! Scalar lower k index nzb replaced by 2d-array nzb_2d ! ! Revision 1.1 2000/04/13 14:45:22 schroeter ! Initial revision ! ! ! ! Description: ! ------------ ! Calculate the change of total water content due to precipitation ! (simplified Kessler scheme) !------------------------------------------------------------------------------! PRIVATE PUBLIC calc_precipitation INTERFACE calc_precipitation MODULE PROCEDURE calc_precipitation MODULE PROCEDURE calc_precipitation_ij END INTERFACE calc_precipitation CONTAINS !------------------------------------------------------------------------------! ! Call for all grid points !------------------------------------------------------------------------------! SUBROUTINE calc_precipitation USE arrays_3d USE cloud_parameters USE constants USE control_parameters USE indices IMPLICIT NONE INTEGER :: i, j, k REAL :: dqdt_precip precipitation_rate = 0.0 DO i = nxl, nxr DO j = nys, nyn DO k = nzb_2d(j,i)+1, nzt IF ( ql(k,j,i) > ql_crit ) THEN dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit ) ELSE dqdt_precip = 0.0 ENDIF tend(k,j,i) = tend(k,j,i) - dqdt_precip ! !-- Precipitation rate in kg / m**2 / s (= mm/s) precipitation_rate(j,i) = precipitation_rate(j,i) + & dqdt_precip * dzw(k) ENDDO ! !-- Sum up the precipitation amount, unit kg / m**2 (= mm) IF ( intermediate_timestep_count == & intermediate_timestep_count_max .AND. & ( dt_do2d_xy-time_do2d_xy ) < precipitation_amount_interval )& THEN precipitation_amount(j,i) = precipitation_amount(j,i) + & precipitation_rate(j,i) * dt_3d ENDIF ENDDO ENDDO END SUBROUTINE calc_precipitation !------------------------------------------------------------------------------! ! Call for grid point i,j !------------------------------------------------------------------------------! SUBROUTINE calc_precipitation_ij( i, j ) USE arrays_3d USE cloud_parameters USE constants USE control_parameters USE indices IMPLICIT NONE INTEGER :: i, j, k REAL :: dqdt_precip precipitation_rate(j,i) = 0.0 ! !-- Ghostpoints are included (although not needed for tend) to avoid a later !-- exchange of these data for the precipitation amount/rate arrays DO k = nzb_2d(j,i)+1, nzt IF ( ql(k,j,i) > ql_crit ) THEN dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit ) ELSE dqdt_precip = 0.0 ENDIF tend(k,j,i) = tend(k,j,i) - dqdt_precip ! !-- Precipitation rate in kg / m**2 / s (= mm/s) precipitation_rate(j,i) = precipitation_rate(j,i) + dqdt_precip * & dzw(k) ENDDO ! !-- Sum up the precipitation amount , unit kg / m**2 (= mm) IF ( intermediate_timestep_count == intermediate_timestep_count_max & .AND. ( dt_do2d_xy-time_do2d_xy ) < precipitation_amount_interval )& THEN precipitation_amount(j,i) = precipitation_amount(j,i) + & precipitation_rate(j,i) * dt_3d ENDIF END SUBROUTINE calc_precipitation_ij END MODULE calc_precipitation_mod