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

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

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