source: palm/trunk/SOURCE/impact_of_latent_heat.f90 @ 1320

Last change on this file since 1320 was 1320, checked in by raasch, 11 years ago

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

  • Property svn:keywords set to Id
File size: 4.3 KB
Line 
1 MODULE impact_of_latent_heat_mod
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2014 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! ONLY-attribute added to USE-statements,
23! kind-parameters added to all INTEGER and REAL declaration statements,
24! kinds are defined in new module kinds,
25! old module precision_kind is removed,
26! revision history before 2012 removed,
27! comment fields (!:) to be used for variable explanations added to
28! all variable declaration statements
29!
30! Former revisions:
31! -----------------
32! $Id: impact_of_latent_heat.f90 1320 2014-03-20 08:40:49Z raasch $
33!
34! 1036 2012-10-22 13:43:42Z raasch
35! code put under GPL (PALM 3.9)
36!
37! Revision 1.1  2000/04/13 14:48:40  schroeter
38! Initial revision
39!
40!
41! Description:
42! ------------
43! Calculate the impact of latent heat due to precipitation
44! (simplified Kessler scheme)
45!------------------------------------------------------------------------------!
46
47    PRIVATE
48    PUBLIC impact_of_latent_heat
49
50    INTERFACE impact_of_latent_heat
51       MODULE PROCEDURE impact_of_latent_heat
52       MODULE PROCEDURE impact_of_latent_heat_ij
53    END INTERFACE impact_of_latent_heat
54 
55 CONTAINS
56
57
58!------------------------------------------------------------------------------!
59! Call for all grid points
60!------------------------------------------------------------------------------!
61    SUBROUTINE impact_of_latent_heat
62
63       USE arrays_3d,                                                          &
64           ONLY:  ql, tend
65           
66       USE cloud_parameters,                                                   &
67           ONLY:  l_d_cp, prec_time_const, pt_d_t, ql_crit
68           
69       USE indices,                                                            &
70           ONLY:  nxl, nxr, nyn, nys, nzb_2d, nzt
71           
72       USE kinds
73
74       IMPLICIT NONE
75
76       INTEGER(iwp) ::  i  !:
77       INTEGER(iwp) ::  j  !:
78       INTEGER(iwp) ::  k  !:
79       
80       REAL(wp) ::  dqdt_precip  !:
81
82 
83       DO  i = nxl, nxr
84          DO  j = nys, nyn
85             DO  k = nzb_2d(j,i)+1, nzt
86
87                IF ( ql(k,j,i) > ql_crit )  THEN
88                   dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit )
89                ELSE
90                   dqdt_precip = 0.0
91                ENDIF
92                tend(k,j,i) = tend(k,j,i) + dqdt_precip * l_d_cp * pt_d_t(k)
93
94             ENDDO
95          ENDDO
96       ENDDO
97
98    END SUBROUTINE impact_of_latent_heat
99
100
101!------------------------------------------------------------------------------!
102! Call for grid point i,j
103!------------------------------------------------------------------------------!
104    SUBROUTINE impact_of_latent_heat_ij( i, j )
105
106       USE arrays_3d,                                                          &
107           ONLY:  ql, tend
108           
109       USE cloud_parameters,                                                   &
110           ONLY:  l_d_cp, prec_time_const, pt_d_t, ql_crit
111           
112       USE indices,                                                            &
113           ONLY:  nzb_2d, nzt
114           
115       USE kinds                                                               
116   
117       IMPLICIT NONE
118
119       INTEGER(iwp) ::  i  !:
120       INTEGER(iwp) ::  j  !:
121       INTEGER(iwp) ::  k  !:
122       
123       REAL(wp) ::  dqdt_precip  !:
124
125
126       DO  k = nzb_2d(j,i)+1, nzt
127
128          IF ( ql(k,j,i) > ql_crit )  THEN
129             dqdt_precip = prec_time_const * ( ql(k,j,i) - ql_crit )
130          ELSE
131             dqdt_precip = 0.0
132          ENDIF
133          tend(k,j,i) = tend(k,j,i) + dqdt_precip * l_d_cp * pt_d_t(k)
134
135       ENDDO
136
137    END SUBROUTINE impact_of_latent_heat_ij
138
139 END MODULE impact_of_latent_heat_mod
Note: See TracBrowser for help on using the repository browser.