MODULE calc_precipitation_mod !------------------------------------------------------------------------------! ! Actual revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Log: calc_precipitation.f90,v $ ! Revision 1.5 2004/01/30 10:15:57 raasch ! Scalar lower k index nzb replaced by 2d-array nzb_2d ! ! Revision 1.4 2003/03/12 16:21:23 raasch ! Full code replaced in the call for all gridpoints instead of calling the ! _ij version (required by NEC, because otherwise no vectorization) ! ! Revision 1.3 2002/06/11 12:38:58 raasch ! Former subroutine changed to a module which allows to be called for all grid ! points of a single vertical column with index i,j or for all grid points by ! using function overloading. ! ! Revision 1.2 2001/01/22 05:32:25 raasch ! Module test_variables removed ! ! 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 indices IMPLICIT NONE INTEGER :: i, j, k REAL :: precipitation_rate DO i = nxl, nxr DO j = nys, nyn DO k = nzb_2d(j,i)+1, nzt-1 IF ( ql(k,j,i) > ql_crit ) THEN precipitation_rate = prec_time_const * & ( ql(k,j,i) - ql_crit ) ELSE precipitation_rate = 0.0 ENDIF tend(k,j,i) = tend(k,j,i) - precipitation_rate ENDDO 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 indices IMPLICIT NONE INTEGER :: i, j, k REAL :: precipitation_rate DO k = nzb_2d(j,i)+1, nzt-1 IF ( ql(k,j,i) > ql_crit ) THEN precipitation_rate = prec_time_const * ( ql(k,j,i) - ql_crit ) ELSE precipitation_rate = 0.0 ENDIF tend(k,j,i) = tend(k,j,i) - precipitation_rate ENDDO END SUBROUTINE calc_precipitation_ij END MODULE calc_precipitation_mod