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

Last change on this file since 1320 was 1320, checked in by raasch, 10 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: 9.9 KB
Line 
1 MODULE subsidence_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: subsidence.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 3.7 2009-12-11 14:15:58Z heinze
38! Initial revision
39!
40! Description:
41! ------------
42! Impact of large-scale subsidence or ascent as tendency term for use
43! in the prognostic equation of potential temperature. This enables the
44! construction of a constant boundary layer height z_i with time.
45!-----------------------------------------------------------------------------!
46
47
48    IMPLICIT NONE
49
50    PRIVATE
51    PUBLIC  init_w_subsidence, subsidence
52
53    INTERFACE init_w_subsidence
54       MODULE PROCEDURE init_w_subsidence
55    END INTERFACE init_w_subsidence
56
57    INTERFACE subsidence
58       MODULE PROCEDURE subsidence
59       MODULE PROCEDURE subsidence_ij
60    END INTERFACE subsidence
61
62 CONTAINS
63
64    SUBROUTINE init_w_subsidence 
65
66       USE arrays_3d,                                                          &
67           ONLY:  dzu, w_subs, zu
68
69       USE control_parameters,                                                 &
70           ONLY:  message_string, ocean, subs_vertical_gradient,               &
71                  subs_vertical_gradient_level, subs_vertical_gradient_level_i
72
73       USE indices,                                                            &
74           ONLY:  nzb, nzt
75
76       USE kinds
77
78       IMPLICIT NONE
79
80       INTEGER(iwp) ::  i !:
81       INTEGER(iwp) ::  k !:
82
83       REAL(wp)     ::  gradient   !:
84       REAL(wp)     ::  ws_surface !:
85
86       IF ( .NOT. ALLOCATED( w_subs )) THEN
87          ALLOCATE( w_subs(nzb:nzt+1) )
88          w_subs = 0.0
89       ENDIF
90
91      IF ( ocean )  THEN
92          message_string = 'Applying large scale vertical motion is not ' // &
93                           'allowed for ocean runs'
94          CALL message( 'init_w_subsidence', 'PA0324', 2, 2, 0, 6, 0 )
95       ENDIF
96
97!
98!--   Compute the profile of the subsidence/ascent velocity
99!--   using the given gradients
100      i = 1
101      gradient = 0.0
102      ws_surface = 0.0
103     
104
105      subs_vertical_gradient_level_i(1) = 0
106      DO  k = 1, nzt+1
107         IF ( i < 11 ) THEN
108            IF ( subs_vertical_gradient_level(i) < zu(k)  .AND. &
109                 subs_vertical_gradient_level(i) >= 0.0 )  THEN
110               gradient = subs_vertical_gradient(i) / 100.0
111               subs_vertical_gradient_level_i(i) = k - 1
112               i = i + 1
113            ENDIF
114         ENDIF
115         IF ( gradient /= 0.0 )  THEN
116            IF ( k /= 1 )  THEN
117               w_subs(k) = w_subs(k-1) + dzu(k) * gradient
118            ELSE
119               w_subs(k) = ws_surface   + 0.5 * dzu(k) * gradient
120            ENDIF
121         ELSE
122            w_subs(k) = w_subs(k-1)
123         ENDIF
124      ENDDO
125
126!
127!--   In case of no given gradients for the subsidence/ascent velocity,
128!--   choose zero gradient
129      IF ( subs_vertical_gradient_level(1) == -9999999.9 )  THEN
130         subs_vertical_gradient_level(1) = 0.0
131      ENDIF
132
133    END SUBROUTINE init_w_subsidence
134
135
136    SUBROUTINE subsidence( tendency, var, var_init ) 
137
138       USE arrays_3d,                                                          &
139           ONLY:  ddzu, w_subs
140
141       USE control_parameters,                                                 &
142           ONLY:  dt_3d
143
144       USE indices,                                                            &
145           ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzb_s_inner,&
146                  nzt
147
148       USE kinds
149
150       IMPLICIT NONE
151 
152       INTEGER(iwp) ::  i !:
153       INTEGER(iwp) ::  j !:
154       INTEGER(iwp) ::  k !:
155
156       REAL(wp)     ::  tmp_grad !:
157   
158       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var      !:
159       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  tendency !:
160       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_init                     !:
161       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_mod                      !:
162
163       var_mod = var_init
164
165!
166!--    Influence of w_subsidence on the current tendency term
167       DO  i = nxl, nxr
168          DO  j = nys, nyn
169             DO  k = nzb_s_inner(j,i)+1, nzt 
170                IF ( w_subs(k) < 0.0 ) THEN    ! large-scale subsidence
171                   tendency(k,j,i) = tendency(k,j,i) - w_subs(k) *  &
172                                     ( var(k+1,j,i) - var(k,j,i) ) * ddzu(k+1)
173                ELSE                           ! large-scale ascent
174                   tendency(k,j,i) = tendency(k,j,i) - w_subs(k) *  &
175                                     ( var(k,j,i) - var(k-1,j,i) ) * ddzu(k)
176                ENDIF
177             ENDDO
178          ENDDO
179       ENDDO
180
181!
182!--    Shifting of the initial profile is especially necessary with Rayleigh
183!--    damping switched on
184
185       DO  k = nzb, nzt
186          IF ( w_subs(k) < 0.0 ) THEN      ! large-scale subsidence
187             var_mod(k) = var_init(k) - dt_3d * w_subs(k) *  &
188                               ( var_init(k+1) - var_init(k) ) * ddzu(k+1)
189          ENDIF
190       ENDDO
191!
192!--   At the upper boundary, the initial profile is shifted with aid of
193!--   the gradient tmp_grad. (This is ok if the gradients are linear.)
194      IF ( w_subs(nzt) < 0.0 ) THEN
195         tmp_grad = ( var_init(nzt+1) - var_init(nzt) ) * ddzu(nzt+1)
196         var_mod(nzt+1) = var_init(nzt+1) -  &
197                              dt_3d * w_subs(nzt+1) * tmp_grad
198      ENDIF
199       
200
201      DO  k = nzt+1, nzb+1, -1
202         IF ( w_subs(k) >= 0.0 ) THEN  ! large-scale ascent
203            var_mod(k) = var_init(k) - dt_3d * w_subs(k) *  &
204                               ( var_init(k) - var_init(k-1) ) * ddzu(k) 
205         ENDIF
206      ENDDO
207!
208!--   At the lower boundary shifting is not necessary because the
209!--   subsidence velocity w_subs(nzb) vanishes.
210
211
212      IF ( w_subs(nzb+1) >= 0.0 ) THEN
213         var_mod(nzb) = var_init(nzb)
214      ENDIF
215
216      var_init = var_mod
217
218
219 END SUBROUTINE subsidence
220
221 SUBROUTINE subsidence_ij( i, j, tendency, var, var_init ) 
222
223       USE arrays_3d,                                                          &
224           ONLY:  ddzu, w_subs
225
226       USE control_parameters,                                                 &
227           ONLY:  dt_3d
228
229       USE indices,                                                            &
230           ONLY:  nxl, nxlg, nxrg, nyng, nys, nysg, nzb_s_inner, nzb, nzt
231
232       USE kinds
233
234       IMPLICIT NONE
235 
236       INTEGER(iwp) ::  i !:
237       INTEGER(iwp) ::  j !:
238       INTEGER(iwp) ::  k !:
239
240       REAL(wp)     ::  tmp_grad !:
241   
242       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var      !:
243       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  tendency !:
244       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_init                     !:
245       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_mod                      !:
246
247       var_mod = var_init
248
249!
250!--    Influence of w_subsidence on the current tendency term
251       DO  k = nzb_s_inner(j,i)+1, nzt 
252          IF ( w_subs(k) < 0.0 ) THEN      ! large-scale subsidence
253             tendency(k,j,i) = tendency(k,j,i) - w_subs(k) *  &
254                               ( var(k+1,j,i) - var(k,j,i) ) * ddzu(k+1)
255          ELSE                             ! large-scale ascent
256             tendency(k,j,i) = tendency(k,j,i) - w_subs(k) *  &
257                               ( var(k,j,i) - var(k-1,j,i) ) * ddzu(k)
258          ENDIF
259       ENDDO
260
261
262!
263!--    Shifting of the initial profile is especially necessary with Rayleigh
264!--    damping switched on
265       IF ( i == nxl .AND. j == nys ) THEN ! shifting only once per PE
266
267          DO  k = nzb, nzt
268             IF ( w_subs(k) < 0.0 ) THEN      ! large-scale subsidence
269                var_mod(k) = var_init(k) - dt_3d * w_subs(k) *  &
270                                  ( var_init(k+1) - var_init(k) ) * ddzu(k+1)
271             ENDIF
272          ENDDO
273!
274!--       At the upper boundary, the initial profile is shifted with aid of
275!--       the gradient tmp_grad. (This is ok if the gradients are linear.)
276          IF ( w_subs(nzt) < 0.0 ) THEN
277             tmp_grad = ( var_init(nzt+1) - var_init(nzt) ) * ddzu(nzt+1)
278             var_mod(nzt+1) = var_init(nzt+1) -  &
279                                  dt_3d * w_subs(nzt+1) * tmp_grad
280          ENDIF
281       
282
283          DO  k = nzt+1, nzb+1, -1
284             IF ( w_subs(k) >= 0.0 ) THEN  ! large-scale ascent
285                var_mod(k) = var_init(k) - dt_3d * w_subs(k) *  &
286                                   ( var_init(k) - var_init(k-1) ) * ddzu(k)
287             ENDIF
288          ENDDO
289!
290!--       At the lower boundary shifting is not necessary because the
291!--       subsidence velocity w_subs(nzb) vanishes.
292
293
294          IF ( w_subs(nzb+1) >= 0.0 ) THEN
295             var_mod(nzb) = var_init(nzb)
296          ENDIF
297
298          var_init = var_mod 
299
300       ENDIF
301
302 END SUBROUTINE subsidence_ij
303
304
305 END MODULE subsidence_mod
Note: See TracBrowser for help on using the repository browser.