source: palm/trunk/SOURCE/ls_forcing_mod.f90 @ 2037

Last change on this file since 2037 was 2037, checked in by knoop, 7 years ago

Anelastic approximation implemented

  • Property svn:keywords set to Id
File size: 22.1 KB
Line 
1!> @file ls_forcing_mod.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
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! 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-2016 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22! Anelastic approximation implemented
23!
24! Former revisions:
25! -----------------
26! $Id: ls_forcing_mod.f90 2037 2016-10-26 11:15:40Z knoop $
27!
28! 2000 2016-08-20 18:09:15Z knoop
29! Forced header and separation lines into 80 columns
30!
31! 1850 2016-04-08 13:29:27Z maronga
32! Module renamed
33!
34!
35! 1682 2015-10-07 23:56:08Z knoop
36! Code annotations made doxygen readable
37!
38! 1602 2015-06-22 07:50:56Z heinze
39! PA0370 changed to PA0363
40!
41! 1382 2014-04-30 12:15:41Z boeske
42! Renamed variables which store large scale forcing tendencies
43! pt_lsa -> td_lsa_lpt, pt_subs -> td_sub_lpt,
44! q_lsa  -> td_lsa_q,   q_subs  -> td_sub_q,
45! high|lowpt_lsa -> high|low_td_lsa_lpt, ...
46!
47! 1365 2014-04-22 15:03:56Z boeske
48! Usage of large scale forcing for pt and q enabled:
49! Added new subroutine ls_advec for horizontal large scale advection and large
50! scale subsidence,
51! error message in init_ls_forcing specified,
52! variable t renamed nt
53!
54! 1353 2014-04-08 15:21:23Z heinze
55! REAL constants provided with KIND-attribute
56!
57! 1320 2014-03-20 08:40:49Z raasch
58! ONLY-attribute added to USE-statements,
59! kind-parameters added to all INTEGER and REAL declaration statements,
60! kinds are defined in new module kinds,
61! comment fields (!:) to be used for variable explanations added to
62! all variable declaration statements
63!
64! 1318 2014-03-17 13:35:16Z raasch
65! module interfaces removed
66!
67! 1299 2014-03-06 13:15:21Z heinze
68! Ensure a zero large scale vertical velocity at the surface
69! Bugfix: typo in case of boundary condition in if-clause
70!
71! 1276 2014-01-15 13:40:41Z heinze
72! Use LSF_DATA also in case of Dirichlet bottom boundary condition for scalars
73!
74! 1249 2013-11-06 10:45:47Z heinze
75! remove call of user module
76! reformatting
77!
78! 1241 2013-10-30 11:36:58Z heinze
79! Initial revision
80!
81! Description:
82! ------------
83!> Calculates large scale forcings (geostrophic wind and subsidence velocity) as
84!> well as surfaces fluxes dependent on time given in an external file (LSF_DATA).
85!> Code is based in parts on DALES and UCLA-LES.
86!--------------------------------------------------------------------------------!
87 MODULE ls_forcing_mod
88 
89
90    PRIVATE
91    PUBLIC init_ls_forcing, ls_forcing_surf, ls_forcing_vert, ls_advec
92    SAVE
93
94    INTERFACE ls_advec
95       MODULE PROCEDURE ls_advec
96       MODULE PROCEDURE ls_advec_ij
97    END INTERFACE ls_advec
98
99 CONTAINS
100
101!------------------------------------------------------------------------------!
102! Description:
103! ------------
104!> @todo Missing subroutine description.
105!------------------------------------------------------------------------------!
106    SUBROUTINE init_ls_forcing
107
108       USE arrays_3d,                                                          &
109           ONLY:  p_surf, pt_surf, q_surf, qsws_surf, shf_surf, td_lsa_lpt,    &
110                  td_lsa_q, td_sub_lpt, td_sub_q, time_surf, time_vert,        &
111                  heatflux_input_conversion, waterflux_input_conversion,       &
112                  ug_vert, vg_vert, wsubs_vert, zu
113
114       USE control_parameters,                                                 &
115           ONLY:  end_time, lsf_surf, lsf_vert, message_string, nlsf
116
117       USE indices,                                                            &
118           ONLY:  ngp_sums_ls, nzb, nz, nzt
119
120       USE kinds
121
122       USE statistics,                                                         &
123           ONLY:  sums_ls_l
124
125
126       IMPLICIT NONE
127
128       CHARACTER(100) ::  chmess      !<
129       CHARACTER(1)   ::  hash        !<
130
131       INTEGER(iwp) ::  ierrn         !<
132       INTEGER(iwp) ::  finput = 90   !<
133       INTEGER(iwp) ::  k             !<
134       INTEGER(iwp) ::  nt             !<
135
136       REAL(wp) ::  fac               !<
137       REAL(wp) ::  highheight        !<
138       REAL(wp) ::  highug_vert       !<
139       REAL(wp) ::  highvg_vert       !<
140       REAL(wp) ::  highwsubs_vert    !<
141       REAL(wp) ::  lowheight         !<
142       REAL(wp) ::  lowug_vert        !<
143       REAL(wp) ::  lowvg_vert        !<
144       REAL(wp) ::  lowwsubs_vert     !<
145       REAL(wp) ::  high_td_lsa_lpt   !<
146       REAL(wp) ::  low_td_lsa_lpt    !<
147       REAL(wp) ::  high_td_lsa_q     !<
148       REAL(wp) ::  low_td_lsa_q      !<
149       REAL(wp) ::  high_td_sub_lpt   !<
150       REAL(wp) ::  low_td_sub_lpt    !<
151       REAL(wp) ::  high_td_sub_q     !<
152       REAL(wp) ::  low_td_sub_q      !<
153       REAL(wp) ::  r_dummy           !<
154
155       ALLOCATE( p_surf(0:nlsf), pt_surf(0:nlsf), q_surf(0:nlsf),              &
156                 qsws_surf(0:nlsf), shf_surf(0:nlsf),                          &
157                 td_lsa_lpt(nzb:nzt+1,0:nlsf), td_lsa_q(nzb:nzt+1,0:nlsf),     &
158                 td_sub_lpt(nzb:nzt+1,0:nlsf), td_sub_q(nzb:nzt+1,0:nlsf),     &
159                 time_vert(0:nlsf), time_surf(0:nlsf),                         &
160                 ug_vert(nzb:nzt+1,0:nlsf), vg_vert(nzb:nzt+1,0:nlsf),         &
161                 wsubs_vert(nzb:nzt+1,0:nlsf) )
162
163       p_surf = 0.0_wp; pt_surf = 0.0_wp; q_surf = 0.0_wp; qsws_surf = 0.0_wp
164       shf_surf = 0.0_wp; time_vert = 0.0_wp; td_lsa_lpt = 0.0_wp
165       td_lsa_q = 0.0_wp; td_sub_lpt = 0.0_wp; td_sub_q = 0.0_wp
166       time_surf = 0.0_wp; ug_vert = 0.0_wp; vg_vert = 0.0_wp
167       wsubs_vert = 0.0_wp
168
169!
170!--    Array for storing large scale forcing and nudging tendencies at each
171!--    timestep for data output
172       ALLOCATE( sums_ls_l(nzb:nzt+1,0:7) )
173       sums_ls_l = 0.0_wp
174
175       ngp_sums_ls = (nz+2)*6
176
177       OPEN ( finput, FILE='LSF_DATA', STATUS='OLD', &
178              FORM='FORMATTED', IOSTAT=ierrn )
179
180       IF ( ierrn /= 0 )  THEN
181          message_string = 'file LSF_DATA does not exist'
182          CALL message( 'ls_forcing', 'PA0368', 1, 2, 0, 6, 0 )
183       ENDIF
184
185       ierrn = 0
186!
187!--    First three lines of LSF_DATA contain header
188       READ ( finput, FMT='(a100)', IOSTAT=ierrn ) chmess
189       READ ( finput, FMT='(a100)', IOSTAT=ierrn ) chmess
190       READ ( finput, FMT='(a100)', IOSTAT=ierrn ) chmess
191
192       IF ( ierrn /= 0 )  THEN
193          message_string = 'errors in file LSF_DATA'
194          CALL message( 'ls_forcing', 'PA0369', 1, 2, 0, 6, 0 )
195       ENDIF
196
197!
198!--    Surface values are read in
199       nt     = 0
200       ierrn = 0
201
202       DO WHILE ( time_surf(nt) < end_time )
203          nt = nt + 1
204          READ ( finput, *, IOSTAT = ierrn ) time_surf(nt), shf_surf(nt),      &
205                                             qsws_surf(nt), pt_surf(nt),       &
206                                             q_surf(nt), p_surf(nt)
207
208          IF ( ierrn < 0 )  THEN
209            WRITE ( message_string, * ) 'No time dependent surface variables ',&
210                              'in&LSF_DATA for end of run found'
211
212             CALL message( 'ls_forcing', 'PA0363', 1, 2, 0, 6, 0 )
213          ENDIF
214       ENDDO
215
216       shf_surf  = shf_surf  * heatflux_input_conversion(nzb)
217       qsws_surf = qsws_surf * waterflux_input_conversion(nzb)
218
219       IF ( time_surf(1) > end_time )  THEN
220          WRITE ( message_string, * ) 'No time dependent surface variables in ',&
221                                     '&LSF_DATA for end of run found - ',      &
222                                     'lsf_surf is set to FALSE'
223          CALL message( 'ls_forcing', 'PA0371', 0, 0, 0, 6, 0 )
224          lsf_surf = .FALSE.
225       ENDIF
226
227!
228!--    Go to the end of the list with surface variables
229       DO WHILE ( ierrn == 0 )
230          READ ( finput, *, IOSTAT = ierrn ) r_dummy
231       ENDDO
232
233!
234!--    Profiles of ug, vg and w_subs are read in (large scale forcing)
235
236       nt = 0
237       DO WHILE ( time_vert(nt) < end_time )
238          nt = nt + 1
239          hash = "#"
240          ierrn = 1 ! not zero
241!
242!--       Search for the next line consisting of "# time",
243!--       from there onwards the profiles will be read
244          DO WHILE ( .NOT. ( hash == "#" .AND. ierrn == 0 ) ) 
245             READ ( finput, *, IOSTAT=ierrn ) hash, time_vert(nt)
246             IF ( ierrn < 0 )  THEN
247                WRITE( message_string, * ) 'No time dependent vertical profiles',&
248                                 ' in&LSF_DATA for end of run found'
249                CALL message( 'ls_forcing', 'PA0372', 1, 2, 0, 6, 0 )
250             ENDIF
251          ENDDO
252
253          IF ( nt == 1 .AND. time_vert(nt) > end_time ) EXIT
254
255          READ ( finput, *, IOSTAT=ierrn ) lowheight, lowug_vert, lowvg_vert,  &
256                                           lowwsubs_vert, low_td_lsa_lpt,      &
257                                           low_td_lsa_q, low_td_sub_lpt,       &
258                                           low_td_sub_q
259          IF ( ierrn /= 0 )  THEN
260             message_string = 'errors in file LSF_DATA'
261             CALL message( 'ls_forcing', 'PA0369', 1, 2, 0, 6, 0 )
262          ENDIF
263
264          READ ( finput, *, IOSTAT=ierrn ) highheight, highug_vert,            &
265                                           highvg_vert, highwsubs_vert,        &
266                                           high_td_lsa_lpt, high_td_lsa_q,     &
267                                           high_td_sub_lpt, high_td_sub_q
268     
269          IF ( ierrn /= 0 )  THEN
270             message_string = 'errors in file LSF_DATA'
271             CALL message( 'ls_forcing', 'PA0369', 1, 2, 0, 6, 0 )
272          ENDIF
273
274
275          DO  k = nzb, nzt+1
276             IF ( highheight < zu(k) )  THEN
277                lowheight      = highheight
278                lowug_vert     = highug_vert
279                lowvg_vert     = highvg_vert
280                lowwsubs_vert  = highwsubs_vert
281                low_td_lsa_lpt = high_td_lsa_lpt
282                low_td_lsa_q   = high_td_lsa_q
283                low_td_sub_lpt = high_td_sub_lpt
284                low_td_sub_q   = high_td_sub_q
285
286                ierrn = 0
287                READ ( finput, *, IOSTAT=ierrn ) highheight, highug_vert,      &
288                                                 highvg_vert, highwsubs_vert,  &
289                                                 high_td_lsa_lpt,              &
290                                                 high_td_lsa_q,                &
291                                                 high_td_sub_lpt, high_td_sub_q
292
293                IF ( ierrn /= 0 )  THEN
294                   WRITE( message_string, * ) 'zu(nzt+1) = ', zu(nzt+1), 'm ', &
295                        'is higher than the maximum height in LSF_DATA which ',&
296                        'is ', lowheight, 'm. Interpolation on PALM ',         &
297                        'grid is not possible.'
298                   CALL message( 'ls_forcing', 'PA0395', 1, 2, 0, 6, 0 )
299                ENDIF
300
301             ENDIF
302
303!
304!--          Interpolation of prescribed profiles in space
305             fac = (highheight-zu(k))/(highheight - lowheight)
306
307             ug_vert(k,nt)    = fac * lowug_vert                               &
308                                + ( 1.0_wp - fac ) * highug_vert
309             vg_vert(k,nt)    = fac * lowvg_vert                               &
310                                + ( 1.0_wp - fac ) * highvg_vert
311             wsubs_vert(k,nt) = fac * lowwsubs_vert                            &
312                                + ( 1.0_wp - fac ) * highwsubs_vert
313
314             td_lsa_lpt(k,nt) = fac * low_td_lsa_lpt                           &
315                                + ( 1.0_wp - fac ) * high_td_lsa_lpt
316             td_lsa_q(k,nt)   = fac * low_td_lsa_q                             &
317                                + ( 1.0_wp - fac ) * high_td_lsa_q
318             td_sub_lpt(k,nt) = fac * low_td_sub_lpt                           &
319                                + ( 1.0_wp - fac ) * high_td_sub_lpt
320             td_sub_q(k,nt)   = fac * low_td_sub_q                             &
321                                + ( 1.0_wp - fac ) * high_td_sub_q
322
323          ENDDO
324
325       ENDDO 
326
327!
328!--    Large scale vertical velocity has to be zero at the surface
329       wsubs_vert(nzb,:) = 0.0_wp
330 
331       IF ( time_vert(1) > end_time )  THEN
332          WRITE ( message_string, * ) 'Time dependent large scale profile ',   &
333                             'forcing from&LSF_DATA sets in after end of ' ,   &
334                             'simulation - lsf_vert is set to FALSE'
335          CALL message( 'ls_forcing', 'PA0373', 0, 0, 0, 6, 0 )
336          lsf_vert = .FALSE.
337       ENDIF
338
339       CLOSE( finput )
340
341
342    END SUBROUTINE init_ls_forcing 
343
344
345!------------------------------------------------------------------------------!
346! Description:
347! ------------
348!> @todo Missing subroutine description.
349!------------------------------------------------------------------------------!
350    SUBROUTINE ls_forcing_surf ( time )
351
352       USE arrays_3d,                                                          &
353           ONLY:  p_surf, pt_surf, q_surf, qsws, qsws_surf, shf, shf_surf,     &
354                  time_surf, time_vert, ug, ug_vert, vg, vg_vert
355
356       USE control_parameters,                                                 &
357           ONLY:  bc_q_b, ibc_pt_b, ibc_q_b, pt_surface, q_surface,            &
358                  surface_pressure
359
360       USE kinds
361
362       IMPLICIT NONE
363
364       INTEGER(iwp) ::  nt                     !<
365
366       REAL(wp)             :: fac            !<
367       REAL(wp), INTENT(in) :: time           !<
368
369!
370!--    Interpolation in time of LSF_DATA at the surface
371       nt = 1
372       DO WHILE ( time > time_surf(nt) )
373          nt = nt + 1
374       ENDDO
375       IF ( time /= time_surf(nt) )  THEN
376         nt = nt - 1
377       ENDIF
378
379       fac = ( time -time_surf(nt) ) / ( time_surf(nt+1) - time_surf(nt) )
380
381       IF ( ibc_pt_b == 0 )  THEN
382!
383!--       In case of Dirichlet boundary condition shf must not
384!--       be set - it is calculated via MOST in prandtl_fluxes
385          pt_surface = pt_surf(nt) + fac * ( pt_surf(nt+1) - pt_surf(nt) )
386
387       ELSEIF ( ibc_pt_b == 1 )  THEN
388!
389!--       In case of Neumann boundary condition pt_surface is needed for
390!--       calculation of reference density
391          shf        = shf_surf(nt) + fac * ( shf_surf(nt+1) - shf_surf(nt) )
392          pt_surface = pt_surf(nt) + fac * ( pt_surf(nt+1) - pt_surf(nt) )
393
394       ENDIF
395
396       IF ( ibc_q_b == 0 )  THEN
397!
398!--       In case of Dirichlet boundary condition qsws must not
399!--       be set - it is calculated via MOST in prandtl_fluxes
400          q_surface = q_surf(nt) + fac * ( q_surf(nt+1) - q_surf(nt) )
401
402       ELSEIF ( ibc_q_b == 1 )  THEN
403
404          qsws = qsws_surf(nt) + fac * ( qsws_surf(nt+1) - qsws_surf(nt) )
405
406       ENDIF
407
408       surface_pressure = p_surf(nt) + fac * ( p_surf(nt+1) - p_surf(nt) )
409
410    END SUBROUTINE ls_forcing_surf 
411
412
413!------------------------------------------------------------------------------!
414! Description:
415! ------------
416!> @todo Missing subroutine description.
417!------------------------------------------------------------------------------!
418    SUBROUTINE ls_forcing_vert ( time )
419
420       USE arrays_3d,                                                          &
421           ONLY:  time_vert, ug, ug_vert, vg, vg_vert, w_subs, wsubs_vert
422
423       USE control_parameters,                                                 &
424           ONLY:  large_scale_subsidence
425
426       USE kinds
427
428       IMPLICIT NONE
429
430       INTEGER(iwp) ::  nt                     !<
431
432       REAL(wp)             ::  fac           !<
433       REAL(wp), INTENT(in) ::  time          !<
434
435!
436!--    Interpolation in time of LSF_DATA for ug, vg and w_subs
437       nt = 1
438       DO WHILE ( time > time_vert(nt) )
439          nt = nt + 1
440       ENDDO
441       IF ( time /= time_vert(nt) )  THEN
442         nt = nt - 1
443       ENDIF
444
445       fac = ( time-time_vert(nt) ) / ( time_vert(nt+1)-time_vert(nt) )
446
447       ug     = ug_vert(:,nt) + fac * ( ug_vert(:,nt+1) - ug_vert(:,nt) )
448       vg     = vg_vert(:,nt) + fac * ( vg_vert(:,nt+1) - vg_vert(:,nt) )
449
450       IF ( large_scale_subsidence )  THEN
451          w_subs = wsubs_vert(:,nt)                                            &
452                   + fac * ( wsubs_vert(:,nt+1) - wsubs_vert(:,nt) )
453       ENDIF
454
455    END SUBROUTINE ls_forcing_vert
456
457
458!------------------------------------------------------------------------------!
459! Description:
460! ------------
461!> Call for all grid points
462!------------------------------------------------------------------------------!
463    SUBROUTINE ls_advec ( time, prog_var )
464
465       USE arrays_3d,                                                          &
466           ONLY:  td_lsa_lpt, td_lsa_q, td_sub_lpt, td_sub_q, tend, time_vert       
467       
468       USE control_parameters,                                                 &
469           ONLY:  large_scale_subsidence, use_subsidence_tendencies
470       
471       USE indices
472       
473       USE kinds
474
475       IMPLICIT NONE
476
477       CHARACTER (LEN=*) ::  prog_var   !<
478
479       REAL(wp), INTENT(in)  :: time    !<
480       REAL(wp) :: fac                  !< 
481
482       INTEGER(iwp) ::  i               !<
483       INTEGER(iwp) ::  j               !<
484       INTEGER(iwp) ::  k               !<
485       INTEGER(iwp) ::  nt               !<
486
487!
488!--    Interpolation in time of LSF_DATA
489       nt = 1
490       DO WHILE ( time > time_vert(nt) )
491          nt = nt + 1
492       ENDDO
493       IF ( time /= time_vert(nt) )  THEN
494         nt = nt - 1
495       ENDIF
496
497       fac = ( time-time_vert(nt) ) / ( time_vert(nt+1)-time_vert(nt) )
498
499!
500!--    Add horizontal large scale advection tendencies of pt and q
501       SELECT CASE ( prog_var )
502
503          CASE ( 'pt' )
504
505             DO  i = nxl, nxr
506                DO  j = nys, nyn
507                   DO  k = nzb_u_inner(j,i)+1, nzt
508                      tend(k,j,i) = tend(k,j,i) + td_lsa_lpt(k,nt) + fac *     &
509                                    ( td_lsa_lpt(k,nt+1) - td_lsa_lpt(k,nt) )
510                   ENDDO
511                ENDDO
512             ENDDO
513
514          CASE ( 'q' )
515
516             DO  i = nxl, nxr
517                DO  j = nys, nyn
518                   DO  k = nzb_u_inner(j,i)+1, nzt
519                      tend(k,j,i) = tend(k,j,i) + td_lsa_q(k,nt) + fac *       &
520                                    ( td_lsa_q(k,nt+1) - td_lsa_q(k,nt) )
521                   ENDDO
522                ENDDO
523             ENDDO
524
525       END SELECT
526
527!
528!--    Subsidence of pt and q with prescribed subsidence tendencies
529       IF ( large_scale_subsidence .AND. use_subsidence_tendencies )  THEN
530
531          SELECT CASE ( prog_var )
532
533             CASE ( 'pt' )
534
535                DO  i = nxl, nxr
536                   DO  j = nys, nyn
537                      DO  k = nzb_u_inner(j,i)+1, nzt
538                         tend(k,j,i) = tend(k,j,i) + td_sub_lpt(k,nt) + fac *  &
539                                       ( td_sub_lpt(k,nt+1) - td_sub_lpt(k,nt) )
540                      ENDDO
541                   ENDDO
542                ENDDO
543 
544             CASE ( 'q' )
545
546                DO  i = nxl, nxr
547                   DO  j = nys, nyn
548                      DO  k = nzb_u_inner(j,i)+1, nzt
549                         tend(k,j,i) = tend(k,j,i) + td_sub_q(k,nt) + fac *    &
550                                       ( td_sub_q(k,nt+1) - td_sub_q(k,nt) )
551                      ENDDO
552                   ENDDO
553                ENDDO
554
555          END SELECT
556
557       ENDIF
558
559    END SUBROUTINE ls_advec
560
561
562!------------------------------------------------------------------------------!
563! Description:
564! ------------
565!> Call for grid point i,j
566!------------------------------------------------------------------------------!
567    SUBROUTINE ls_advec_ij ( i, j, time, prog_var )
568
569       USE arrays_3d,                                                          &
570           ONLY:  td_lsa_lpt, td_lsa_q, td_sub_lpt, td_sub_q, tend, time_vert       
571       
572       USE control_parameters,                                                 &
573           ONLY:  large_scale_subsidence, use_subsidence_tendencies
574       
575       USE indices
576       
577       USE kinds
578
579       IMPLICIT NONE
580
581       CHARACTER (LEN=*) ::  prog_var   !<
582
583       REAL(wp), INTENT(in)  :: time    !<
584       REAL(wp) :: fac                  !<
585
586       INTEGER(iwp) ::  i               !<
587       INTEGER(iwp) ::  j               !<
588       INTEGER(iwp) ::  k               !<
589       INTEGER(iwp) ::  nt               !<
590
591!
592!--    Interpolation in time of LSF_DATA
593       nt = 1
594       DO WHILE ( time > time_vert(nt) )
595          nt = nt + 1
596       ENDDO
597       IF ( time /= time_vert(nt) )  THEN
598         nt = nt - 1
599       ENDIF
600
601       fac = ( time-time_vert(nt) ) / ( time_vert(nt+1)-time_vert(nt) )
602
603!
604!--    Add horizontal large scale advection tendencies of pt and q
605       SELECT CASE ( prog_var )
606
607          CASE ( 'pt' )
608
609             DO  k = nzb_u_inner(j,i)+1, nzt
610                tend(k,j,i) = tend(k,j,i) + td_lsa_lpt(k,nt)                   &
611                              + fac * ( td_lsa_lpt(k,nt+1) - td_lsa_lpt(k,nt) )
612             ENDDO
613
614          CASE ( 'q' )
615
616             DO  k = nzb_u_inner(j,i)+1, nzt
617                tend(k,j,i) = tend(k,j,i) + td_lsa_q(k,nt)                     &
618                              + fac * ( td_lsa_q(k,nt+1) - td_lsa_q(k,nt) )
619             ENDDO
620
621       END SELECT
622
623!
624!--    Subsidence of pt and q with prescribed profiles
625       IF ( large_scale_subsidence .AND. use_subsidence_tendencies )  THEN
626
627          SELECT CASE ( prog_var )
628
629             CASE ( 'pt' )
630
631                DO  k = nzb_u_inner(j,i)+1, nzt
632                   tend(k,j,i) = tend(k,j,i) + td_sub_lpt(k,nt) + fac *        &
633                                 ( td_sub_lpt(k,nt+1) - td_sub_lpt(k,nt) )
634                ENDDO
635 
636             CASE ( 'q' )
637
638                DO  k = nzb_u_inner(j,i)+1, nzt
639                   tend(k,j,i) = tend(k,j,i) + td_sub_q(k,nt) + fac *          &
640                                 ( td_sub_q(k,nt+1) - td_sub_q(k,nt) )
641                ENDDO
642
643          END SELECT
644
645       ENDIF
646
647    END SUBROUTINE ls_advec_ij
648
649
650 END MODULE ls_forcing_mod
Note: See TracBrowser for help on using the repository browser.