source: palm/trunk/SOURCE/interaction_droplets_ptq.f90 @ 2365

Last change on this file since 2365 was 2233, checked in by suehring, 7 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 5.6 KB
Line 
1!> @file interaction_droplets_ptq.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! 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-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: interaction_droplets_ptq.f90 2233 2017-05-30 18:08:54Z kanani $
27!
28! 2232 2017-05-30 17:47:52Z suehring
29! Adjustments to new topography concept
30!
31! 2000 2016-08-20 18:09:15Z knoop
32! Forced header and separation lines into 80 columns
33!
34! 1873 2016-04-18 14:50:06Z maronga
35! Module renamed (removed _mod)
36!
37!
38! 1850 2016-04-08 13:29:27Z maronga
39! Module renamed
40!
41!
42! 1845 2016-04-08 08:29:13Z raasch
43! nzb_2d replaced by nzb_s_inner
44!
45! 1822 2016-04-07 07:49:42Z hoffmann
46! Unused variables removed.
47!
48! 1779 2016-03-03 08:01:28Z raasch
49! bugfix: module procedure names shortened to avoid Intel compiler warnings
50! about too long names
51!
52! 1682 2015-10-07 23:56:08Z knoop
53! Code annotations made doxygen readable
54!
55! 1320 2014-03-20 08:40:49Z raasch
56! ONLY-attribute added to USE-statements,
57! kind-parameters added to all INTEGER and REAL declaration statements,
58! kinds are defined in new module kinds,
59! revision history before 2012 removed,
60! comment fields (!:) to be used for variable explanations added to
61! all variable declaration statements
62!
63! 1036 2012-10-22 13:43:42Z raasch
64! code put under GPL (PALM 3.9)
65!
66! 799 2011-12-21 17:48:03Z franke
67! Bugfix: pt_d_t(k) was missing in calculation of pt_p
68!
69! RCS Log replace by Id keyword, revision history cleaned up
70!
71! Revision 1.1  2005/06/26 19:57:47  raasch
72! Initial revision
73!
74!
75! Description:
76! ------------
77!> Release of latent heat and change of specific humidity due to condensation /
78!> evaporation of droplets.
79!------------------------------------------------------------------------------!
80 MODULE interaction_droplets_ptq_mod
81 
82
83    PRIVATE
84    PUBLIC interaction_droplets_ptq
85
86    INTERFACE interaction_droplets_ptq
87!
88!--    Internal names shortened in order ro avoid Intel compiler messages
89!--    about too long names
90       MODULE PROCEDURE i_droplets_ptq
91       MODULE PROCEDURE i_droplets_ptq_ij
92    END INTERFACE interaction_droplets_ptq
93 
94 CONTAINS
95
96
97!------------------------------------------------------------------------------!
98! Description:
99! ------------
100!> Call for all grid points
101!------------------------------------------------------------------------------!
102    SUBROUTINE i_droplets_ptq
103
104       USE arrays_3d,                                                          &
105           ONLY:  pt_p, ql_c, q_p
106           
107       USE cloud_parameters,                                                   &
108           ONLY:  l_d_cp, pt_d_t
109           
110       USE indices,                                                            &
111           ONLY:  nxl, nxr, nyn, nys, nzb, nzt, wall_flags_0
112           
113       USE kinds
114
115       USE pegrid
116
117       IMPLICIT NONE
118
119       INTEGER(iwp) ::  i    !< running index x direction
120       INTEGER(iwp) ::  j    !< running index y direction
121       INTEGER(iwp) ::  k    !< running index z direction
122
123       REAL(wp) ::  flag     !< flag to mask topography grid points
124 
125       DO  i = nxl, nxr
126          DO  j = nys, nyn
127             DO  k = nzb+1, nzt
128!
129!--             Predetermine flag to mask topography
130                flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
131
132                q_p(k,j,i)  = q_p(k,j,i)  - ql_c(k,j,i) * flag
133                pt_p(k,j,i) = pt_p(k,j,i) + l_d_cp * ql_c(k,j,i) * pt_d_t(k)   &
134                                                        * flag
135             ENDDO
136          ENDDO
137       ENDDO
138
139    END SUBROUTINE i_droplets_ptq
140
141
142!------------------------------------------------------------------------------!
143! Description:
144! ------------
145!> Call for grid point i,j
146!------------------------------------------------------------------------------!
147    SUBROUTINE i_droplets_ptq_ij( i, j )
148
149       USE arrays_3d,                                                          &
150           ONLY:  pt_p, ql_c, q_p
151
152       USE cloud_parameters,                                                   &
153           ONLY:  l_d_cp, pt_d_t
154
155       USE indices,                                                            &
156           ONLY:  nzb, nzt, wall_flags_0
157
158       USE kinds,                                                              &
159           ONLY:  iwp, wp
160
161       USE pegrid
162
163       IMPLICIT NONE
164
165       INTEGER(iwp) ::  i    !< running index x direction
166       INTEGER(iwp) ::  j    !< running index y direction
167       INTEGER(iwp) ::  k    !< running index z direction
168
169       REAL(wp) ::  flag     !< flag to mask topography grid points
170
171
172       DO  k = nzb+1, nzt
173!
174!--       Predetermine flag to mask topography
175          flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
176
177          q_p(k,j,i)  = q_p(k,j,i)  - ql_c(k,j,i) * flag
178          pt_p(k,j,i) = pt_p(k,j,i) + l_d_cp * ql_c(k,j,i) * pt_d_t(k) * flag
179       ENDDO
180
181    END SUBROUTINE i_droplets_ptq_ij
182
183 END MODULE interaction_droplets_ptq_mod
Note: See TracBrowser for help on using the repository browser.