MODULE impact_of_latent_heat_mod !------------------------------------------------------------------------------! ! Actual revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Log: impact_of_latent_heat.f90,v $ ! Revision 1.5 2004/01/30 10:25:59 raasch ! Scalar lower k index nzb replaced by 2d-array nzb_2d ! ! Revision 1.4 2003/03/12 16:32:14 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 13:10:06 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 06:52:34 raasch ! Module test_variables removed ! ! Revision 1.1 2000/04/13 14:48:40 schroeter ! Initial revision ! ! ! Description: ! ------------ ! Calculate the impact of latent heat due to precipitation ! (simplified Kessler scheme) !------------------------------------------------------------------------------! PRIVATE PUBLIC impact_of_latent_heat INTERFACE impact_of_latent_heat MODULE PROCEDURE impact_of_latent_heat MODULE PROCEDURE impact_of_latent_heat_ij END INTERFACE impact_of_latent_heat CONTAINS !------------------------------------------------------------------------------! ! Call for all grid points !------------------------------------------------------------------------------! SUBROUTINE impact_of_latent_heat 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 * l_d_cp * & pt_d_t(k) ENDDO ENDDO ENDDO END SUBROUTINE impact_of_latent_heat !------------------------------------------------------------------------------! ! Call for grid point i,j !------------------------------------------------------------------------------! SUBROUTINE impact_of_latent_heat_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 * l_d_cp * pt_d_t(k) ENDDO END SUBROUTINE impact_of_latent_heat_ij END MODULE impact_of_latent_heat_mod