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

Last change on this file since 1365 was 1365, checked in by boeske, 10 years ago

large scale forcing enabled

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