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

Last change on this file since 1698 was 1683, checked in by knoop, 8 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 13.0 KB
Line 
1!> @file subsidence.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 terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2014 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! -----------------
21!
22!
23! Former revisions:
24! -----------------
25! $Id: subsidence.f90 1683 2015-10-07 23:57:51Z raasch $
26!
27! 1682 2015-10-07 23:56:08Z knoop
28! Code annotations made doxygen readable
29!
30! 1489 2014-10-30 08:09:12Z raasch
31! bugfix: sums_ls_l can only be used if large_scale_forcing is switched on
32!
33! 1382 2014-04-30 12:15:41Z boeske
34! Changed the weighting factor that is used in the summation of subsidence
35! tendencies for profile data output from weight_pres to weight_substep
36! added Neumann boundary conditions for profile data output of subsidence terms
37! at nzt+1
38!
39! 1380 2014-04-28 12:40:45Z heinze
40! Shifting only necessary in case of scalar Rayleigh damping
41!
42! 1365 2014-04-22 15:03:56Z boeske
43! Summation of subsidence tendencies for data output added
44! +ls_index, sums_ls_l, tmp_tend
45!
46! 1353 2014-04-08 15:21:23Z heinze
47! REAL constants provided with KIND-attribute
48!
49! 1320 2014-03-20 08:40:49Z raasch
50! ONLY-attribute added to USE-statements,
51! kind-parameters added to all INTEGER and REAL declaration statements,
52! kinds are defined in new module kinds,
53! old module precision_kind is removed,
54! revision history before 2012 removed,
55! comment fields (!:) to be used for variable explanations added to
56! all variable declaration statements
57!
58! 1036 2012-10-22 13:43:42Z raasch
59! code put under GPL (PALM 3.9)
60!
61! Revision 3.7 2009-12-11 14:15:58Z heinze
62! Initial revision
63!
64! Description:
65! ------------
66!> Impact of large-scale subsidence or ascent as tendency term for use
67!> in the prognostic equation of potential temperature. This enables the
68!> construction of a constant boundary layer height z_i with time.
69!-----------------------------------------------------------------------------!
70 MODULE subsidence_mod
71 
72
73
74    IMPLICIT NONE
75
76    PRIVATE
77    PUBLIC  init_w_subsidence, subsidence
78
79    INTERFACE init_w_subsidence
80       MODULE PROCEDURE init_w_subsidence
81    END INTERFACE init_w_subsidence
82
83    INTERFACE subsidence
84       MODULE PROCEDURE subsidence
85       MODULE PROCEDURE subsidence_ij
86    END INTERFACE subsidence
87
88 CONTAINS
89
90!------------------------------------------------------------------------------!
91! Description:
92! ------------
93!> @todo Missing subroutine description.
94!------------------------------------------------------------------------------!
95    SUBROUTINE init_w_subsidence 
96
97       USE arrays_3d,                                                          &
98           ONLY:  dzu, w_subs, zu
99
100       USE control_parameters,                                                 &
101           ONLY:  message_string, ocean, subs_vertical_gradient,               &
102                  subs_vertical_gradient_level, subs_vertical_gradient_level_i
103
104       USE indices,                                                            &
105           ONLY:  nzb, nzt
106
107       USE kinds
108
109       IMPLICIT NONE
110
111       INTEGER(iwp) ::  i !<
112       INTEGER(iwp) ::  k !<
113
114       REAL(wp)     ::  gradient   !<
115       REAL(wp)     ::  ws_surface !<
116
117       IF ( .NOT. ALLOCATED( w_subs ))  THEN
118          ALLOCATE( w_subs(nzb:nzt+1) )
119          w_subs = 0.0_wp
120       ENDIF
121
122       IF ( ocean )  THEN
123          message_string = 'Applying large scale vertical motion is not ' // &
124                           'allowed for ocean runs'
125          CALL message( 'init_w_subsidence', 'PA0324', 2, 2, 0, 6, 0 )
126       ENDIF
127
128!
129!--   Compute the profile of the subsidence/ascent velocity
130!--   using the given gradients
131      i = 1
132      gradient = 0.0_wp
133      ws_surface = 0.0_wp
134     
135
136      subs_vertical_gradient_level_i(1) = 0
137      DO  k = 1, nzt+1
138         IF ( i < 11 )  THEN
139            IF ( subs_vertical_gradient_level(i) < zu(k)  .AND. &
140                 subs_vertical_gradient_level(i) >= 0.0_wp )  THEN
141               gradient = subs_vertical_gradient(i) / 100.0_wp
142               subs_vertical_gradient_level_i(i) = k - 1
143               i = i + 1
144            ENDIF
145         ENDIF
146         IF ( gradient /= 0.0_wp )  THEN
147            IF ( k /= 1 )  THEN
148               w_subs(k) = w_subs(k-1) + dzu(k) * gradient
149            ELSE
150               w_subs(k) = ws_surface   + 0.5_wp * dzu(k) * gradient
151            ENDIF
152         ELSE
153            w_subs(k) = w_subs(k-1)
154         ENDIF
155      ENDDO
156
157!
158!--   In case of no given gradients for the subsidence/ascent velocity,
159!--   choose zero gradient
160      IF ( subs_vertical_gradient_level(1) == -9999999.9_wp )  THEN
161         subs_vertical_gradient_level(1) = 0.0_wp
162      ENDIF
163
164    END SUBROUTINE init_w_subsidence
165
166
167!------------------------------------------------------------------------------!
168! Description:
169! ------------
170!> @todo Missing subroutine description.
171!------------------------------------------------------------------------------!
172    SUBROUTINE subsidence( tendency, var, var_init, ls_index ) 
173
174       USE arrays_3d,                                                          &
175           ONLY:  ddzu, w_subs
176
177       USE control_parameters,                                                 &
178           ONLY:  dt_3d, intermediate_timestep_count, large_scale_forcing,     &
179                  scalar_rayleigh_damping
180
181       USE indices,                                                            &
182           ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzb_s_inner,&
183                  nzt
184
185       USE kinds
186
187       USE statistics,                                                         &
188           ONLY:  sums_ls_l, weight_substep
189
190       IMPLICIT NONE
191 
192       INTEGER(iwp) ::  i !<
193       INTEGER(iwp) ::  j !<
194       INTEGER(iwp) ::  k !<
195       INTEGER(iwp) ::  ls_index !<
196
197       REAL(wp)     ::  tmp_tend !<
198       REAL(wp)     ::  tmp_grad !<
199   
200       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var      !<
201       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  tendency !<
202       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_init                     !<
203       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_mod                      !<
204
205       var_mod = var_init
206
207!
208!--    Influence of w_subsidence on the current tendency term
209       DO  i = nxl, nxr
210          DO  j = nys, nyn
211
212             DO  k = nzb_s_inner(j,i)+1, nzt 
213                IF ( w_subs(k) < 0.0_wp )  THEN    ! large-scale subsidence
214                   tmp_tend = - w_subs(k) *                                    &
215                              ( var(k+1,j,i) - var(k,j,i) ) * ddzu(k+1)
216                ELSE                               ! large-scale ascent
217                   tmp_tend = - w_subs(k) *                                    &
218                              ( var(k,j,i) - var(k-1,j,i) ) * ddzu(k)
219                ENDIF
220
221                tendency(k,j,i) = tendency(k,j,i) + tmp_tend
222
223                IF ( large_scale_forcing )  THEN
224                   sums_ls_l(k,ls_index) = sums_ls_l(k,ls_index) + tmp_tend    &
225                                   * weight_substep(intermediate_timestep_count)
226                ENDIF
227             ENDDO
228
229             sums_ls_l(nzt+1,ls_index) = sums_ls_l(nzt,ls_index)
230
231          ENDDO
232       ENDDO
233
234!
235!--    Shifting of the initial profile is especially necessary with Rayleigh
236!--    damping switched on
237       IF ( scalar_rayleigh_damping ) THEN
238          DO  k = nzb, nzt
239             IF ( w_subs(k) < 0.0_wp )  THEN      ! large-scale subsidence
240                var_mod(k) = var_init(k) - dt_3d * w_subs(k) *  &
241                                  ( var_init(k+1) - var_init(k) ) * ddzu(k+1)
242             ENDIF
243          ENDDO
244!
245!--      At the upper boundary, the initial profile is shifted with aid of
246!--      the gradient tmp_grad. (This is ok if the gradients are linear.)
247         IF ( w_subs(nzt) < 0.0_wp )  THEN
248            tmp_grad = ( var_init(nzt+1) - var_init(nzt) ) * ddzu(nzt+1)
249            var_mod(nzt+1) = var_init(nzt+1) -  &
250                                 dt_3d * w_subs(nzt+1) * tmp_grad
251         ENDIF
252       
253
254         DO  k = nzt+1, nzb+1, -1
255            IF ( w_subs(k) >= 0.0_wp )  THEN  ! large-scale ascent
256               var_mod(k) = var_init(k) - dt_3d * w_subs(k) *  &
257                                  ( var_init(k) - var_init(k-1) ) * ddzu(k) 
258            ENDIF
259         ENDDO
260!
261!--      At the lower boundary shifting is not necessary because the
262!--      subsidence velocity w_subs(nzb) vanishes.
263         IF ( w_subs(nzb+1) >= 0.0_wp )  THEN
264            var_mod(nzb) = var_init(nzb)
265         ENDIF
266
267         var_init = var_mod
268      ENDIF
269
270
271 END SUBROUTINE subsidence
272
273!------------------------------------------------------------------------------!
274! Description:
275! ------------
276!> @todo Missing subroutine description.
277!------------------------------------------------------------------------------!
278 SUBROUTINE subsidence_ij( i, j, tendency, var, var_init, ls_index ) 
279
280       USE arrays_3d,                                                          &
281           ONLY:  ddzu, w_subs
282
283       USE control_parameters,                                                 &
284           ONLY:  dt_3d, intermediate_timestep_count, large_scale_forcing,     &
285                  scalar_rayleigh_damping
286
287       USE indices,                                                            &
288           ONLY:  nxl, nxlg, nxrg, nyng, nys, nysg, nzb_s_inner, nzb, nzt
289
290       USE kinds
291
292       USE statistics,                                                         &
293           ONLY:  sums_ls_l, weight_substep
294
295       IMPLICIT NONE
296 
297       INTEGER(iwp) ::  i !<
298       INTEGER(iwp) ::  j !<
299       INTEGER(iwp) ::  k !<
300       INTEGER(iwp) ::  ls_index !<
301
302       REAL(wp)     ::  tmp_tend !<
303       REAL(wp)     ::  tmp_grad !<
304   
305       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var      !<
306       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  tendency !<
307       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_init                     !<
308       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_mod                      !<
309
310       var_mod = var_init
311
312!
313!--    Influence of w_subsidence on the current tendency term
314       DO  k = nzb_s_inner(j,i)+1, nzt 
315          IF ( w_subs(k) < 0.0_wp )  THEN      ! large-scale subsidence
316             tmp_tend = - w_subs(k) * ( var(k+1,j,i) - var(k,j,i) ) * ddzu(k+1)
317          ELSE                                 ! large-scale ascent
318             tmp_tend = - w_subs(k) * ( var(k,j,i) - var(k-1,j,i) ) * ddzu(k)
319          ENDIF
320
321          tendency(k,j,i) = tendency(k,j,i) + tmp_tend
322
323          IF ( large_scale_forcing )  THEN
324             sums_ls_l(k,ls_index) = sums_ls_l(k,ls_index) + tmp_tend          &
325                                   * weight_substep(intermediate_timestep_count)
326          ENDIF
327       ENDDO
328
329       IF ( large_scale_forcing )  THEN
330          sums_ls_l(nzt+1,ls_index) = sums_ls_l(nzt,ls_index)
331       ENDIF
332
333!
334!--    Shifting of the initial profile is especially necessary with Rayleigh
335!--    damping switched on
336       IF ( scalar_rayleigh_damping ) THEN
337          IF ( i == nxl .AND. j == nys )  THEN ! shifting only once per PE
338
339             DO  k = nzb, nzt
340                IF ( w_subs(k) < 0.0_wp )  THEN      ! large-scale subsidence
341                   var_mod(k) = var_init(k) - dt_3d * w_subs(k) *  &
342                                     ( var_init(k+1) - var_init(k) ) * ddzu(k+1)
343                ENDIF
344             ENDDO
345!
346!--          At the upper boundary, the initial profile is shifted with aid of
347!--          the gradient tmp_grad. (This is ok if the gradients are linear.)
348             IF ( w_subs(nzt) < 0.0_wp )  THEN
349                tmp_grad = ( var_init(nzt+1) - var_init(nzt) ) * ddzu(nzt+1)
350                var_mod(nzt+1) = var_init(nzt+1) -  &
351                                     dt_3d * w_subs(nzt+1) * tmp_grad
352             ENDIF
353       
354
355             DO  k = nzt+1, nzb+1, -1
356                IF ( w_subs(k) >= 0.0_wp )  THEN  ! large-scale ascent
357                   var_mod(k) = var_init(k) - dt_3d * w_subs(k) *  &
358                                      ( var_init(k) - var_init(k-1) ) * ddzu(k)
359                ENDIF
360             ENDDO
361!
362!--          At the lower boundary shifting is not necessary because the
363!--          subsidence velocity w_subs(nzb) vanishes.
364             IF ( w_subs(nzb+1) >= 0.0_wp )  THEN
365                var_mod(nzb) = var_init(nzb)
366             ENDIF
367
368             var_init = var_mod 
369
370          ENDIF
371       ENDIF
372
373 END SUBROUTINE subsidence_ij
374
375
376 END MODULE subsidence_mod
Note: See TracBrowser for help on using the repository browser.