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

Last change on this file since 1329 was 1321, checked in by raasch, 10 years ago

last commit documented

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