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

Last change on this file since 1378 was 1366, checked in by boeske, 11 years ago

last commit documented

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