source: palm/trunk/SOURCE/boundary_conds.f90 @ 2232

Last change on this file since 2232 was 2232, checked in by suehring, 7 years ago

Adjustments according new topography and surface-modelling concept implemented

  • Property svn:keywords set to Id
File size: 37.4 KB
RevLine 
[1682]1!> @file boundary_conds.f90
[2000]2!------------------------------------------------------------------------------!
[1036]3! This file is part of PALM.
4!
[2000]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.
[1036]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!
[2101]17! Copyright 1997-2017 Leibniz Universitaet Hannover
[2000]18!------------------------------------------------------------------------------!
[1036]19!
[484]20! Current revisions:
[1]21! -----------------
[2232]22! Set boundary conditions on topography top using flag method.
[1933]23!
[1321]24! Former revisions:
25! -----------------
26! $Id: boundary_conds.f90 2232 2017-05-30 17:47:52Z suehring $
27!
[2119]28! 2118 2017-01-17 16:38:49Z raasch
29! OpenACC directives removed
30!
[2001]31! 2000 2016-08-20 18:09:15Z knoop
32! Forced header and separation lines into 80 columns
33!
[1993]34! 1992 2016-08-12 15:14:59Z suehring
35! Adjustments for top boundary condition for passive scalar
36!
[1961]37! 1960 2016-07-12 16:34:24Z suehring
38! Treat humidity and passive scalar separately
39!
[1933]40! 1823 2016-04-07 08:57:52Z hoffmann
41! Initial version of purely vertical nesting introduced.
42!
[1823]43! 1822 2016-04-07 07:49:42Z hoffmann
44! icloud_scheme removed. microphyisics_seifert added.
45!
[1765]46! 1764 2016-02-28 12:45:19Z raasch
47! index bug for u_p at left outflow removed
48!
[1763]49! 1762 2016-02-25 12:31:13Z hellstea
50! Introduction of nested domain feature
51!
[1744]52! 1742 2016-01-13 09:50:06Z raasch
53! bugfix for outflow Neumann boundary conditions at bottom and top
54!
[1718]55! 1717 2015-11-11 15:09:47Z raasch
56! Bugfix: index error in outflow conditions for left boundary
57!
[1683]58! 1682 2015-10-07 23:56:08Z knoop
59! Code annotations made doxygen readable
60!
[1717]61! 1410 2014-05-23 12:16:18Z suehring
[1463]62! Bugfix: set dirichlet boundary condition for passive_scalar at model domain
63! top
64!
[1410]65! 1399 2014-05-07 11:16:25Z heinze
66! Bugfix: set inflow boundary conditions also if no humidity or passive_scalar
67! is used.
68!
[1399]69! 1398 2014-05-07 11:15:00Z heinze
70! Dirichlet-condition at the top for u and v changed to u_init and v_init also
71! for large_scale_forcing
72!
[1381]73! 1380 2014-04-28 12:40:45Z heinze
74! Adjust Dirichlet-condition at the top for pt in case of nudging
75!
[1362]76! 1361 2014-04-16 15:17:48Z hoffmann
77! Bottom and top boundary conditions of rain water content (qr) and
78! rain drop concentration (nr) changed to Dirichlet
79!
[1354]80! 1353 2014-04-08 15:21:23Z heinze
81! REAL constants provided with KIND-attribute
82
[1321]83! 1320 2014-03-20 08:40:49Z raasch
[1320]84! ONLY-attribute added to USE-statements,
85! kind-parameters added to all INTEGER and REAL declaration statements,
86! kinds are defined in new module kinds,
87! revision history before 2012 removed,
88! comment fields (!:) to be used for variable explanations added to
89! all variable declaration statements
[1160]90!
[1258]91! 1257 2013-11-08 15:18:40Z raasch
92! loop independent clauses added
93!
[1242]94! 1241 2013-10-30 11:36:58Z heinze
95! Adjust ug and vg at each timestep in case of large_scale_forcing
96!
[1160]97! 1159 2013-05-21 11:58:22Z fricke
[1159]98! Bugfix: Neumann boundary conditions for the velocity components at the
99! outflow are in fact radiation boundary conditions using the maximum phase
100! velocity that ensures numerical stability (CFL-condition).
101! Hence, logical operator use_cmax is now used instead of bc_lr_dirneu/_neudir.
102! Bugfix: In case of use_cmax at the outflow, u, v, w are replaced by
103! u_p, v_p, w_p 
[1116]104!
105! 1115 2013-03-26 18:16:16Z hoffmann
106! boundary conditions of two-moment cloud scheme are restricted to Neumann-
107! boundary-conditions
108!
[1114]109! 1113 2013-03-10 02:48:14Z raasch
110! GPU-porting
111! dummy argument "range" removed
112! Bugfix: wrong index in loops of radiation boundary condition
[1113]113!
[1054]114! 1053 2012-11-13 17:11:03Z hoffmann
115! boundary conditions for the two new prognostic equations (nr, qr) of the
116! two-moment cloud scheme
117!
[1037]118! 1036 2012-10-22 13:43:42Z raasch
119! code put under GPL (PALM 3.9)
120!
[997]121! 996 2012-09-07 10:41:47Z raasch
122! little reformatting
123!
[979]124! 978 2012-08-09 08:28:32Z fricke
125! Neumann boudnary conditions are added at the inflow boundary for the SGS-TKE.
126! Outflow boundary conditions for the velocity components can be set to Neumann
127! conditions or to radiation conditions with a horizontal averaged phase
128! velocity.
129!
[876]130! 875 2012-04-02 15:35:15Z gryschka
131! Bugfix in case of dirichlet inflow bc at the right or north boundary
132!
[1]133! Revision 1.1  1997/09/12 06:21:34  raasch
134! Initial revision
135!
136!
137! Description:
138! ------------
[1682]139!> Boundary conditions for the prognostic quantities.
140!> One additional bottom boundary condition is applied for the TKE (=(u*)**2)
141!> in prandtl_fluxes. The cyclic lateral boundary conditions are implicitly
142!> handled in routine exchange_horiz. Pressure boundary conditions are
143!> explicitly set in routines pres, poisfft, poismg and sor.
[1]144!------------------------------------------------------------------------------!
[1682]145 SUBROUTINE boundary_conds
146 
[1]147
[1320]148    USE arrays_3d,                                                             &
149        ONLY:  c_u, c_u_m, c_u_m_l, c_v, c_v_m, c_v_m_l, c_w, c_w_m, c_w_m_l,  &
[1960]150               dzu, e_p, nr_p, pt, pt_p, q, q_p, qr_p, s, s_p, sa, sa_p,       &
[1320]151               u, ug, u_init, u_m_l, u_m_n, u_m_r, u_m_s, u_p,                 &
152               v, vg, v_init, v_m_l, v_m_n, v_m_r, v_m_s, v_p,                 &
[1960]153               w, w_p, w_m_l, w_m_n, w_m_r, w_m_s, pt_init
[1320]154
155    USE control_parameters,                                                    &
[1960]156        ONLY:  bc_pt_t_val, bc_q_t_val, bc_s_t_val, constant_diffusion,        &
[1320]157               cloud_physics, dt_3d, humidity,                                 &
[1960]158               ibc_pt_b, ibc_pt_t, ibc_q_b, ibc_q_t, ibc_s_b, ibc_s_t,         &
159               ibc_sa_t, ibc_uv_b, ibc_uv_t, inflow_l, inflow_n, inflow_r,     &
160               inflow_s, intermediate_timestep_count, large_scale_forcing,     &
[1822]161               microphysics_seifert, nest_domain, nest_bound_l, nest_bound_s,  &
162               nudging, ocean, outflow_l, outflow_n, outflow_r, outflow_s,     &
163               passive_scalar, tsc, use_cmax
[1320]164
165    USE grid_variables,                                                        &
166        ONLY:  ddx, ddy, dx, dy
167
168    USE indices,                                                               &
169        ONLY:  nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg,             &
[2232]170               nzb, nzt, wall_flags_0
[1320]171
172    USE kinds
173
[1]174    USE pegrid
175
[1933]176    USE pmc_interface,                                                         &
177        ONLY : nesting_mode
[1320]178
[2232]179    USE surface_mod,                                                           &
180        ONLY :  bc_h
[1933]181
[1]182    IMPLICIT NONE
183
[2232]184    INTEGER(iwp) ::  i  !< grid index x direction
185    INTEGER(iwp) ::  j  !< grid index y direction
186    INTEGER(iwp) ::  k  !< grid index z direction
187    INTEGER(iwp) ::  kb !< variable to set respective boundary value, depends on facing.
188    INTEGER(iwp) ::  l  !< running index boundary type, for up- and downward-facing walls
189    INTEGER(iwp) ::  m  !< running index surface elements
[1]190
[1682]191    REAL(wp)    ::  c_max !<
192    REAL(wp)    ::  denom !<
[1]193
[73]194
[1]195!
[1113]196!-- Bottom boundary
197    IF ( ibc_uv_b == 1 )  THEN
198       u_p(nzb,:,:) = u_p(nzb+1,:,:)
199       v_p(nzb,:,:) = v_p(nzb+1,:,:)
200    ENDIF
[2232]201!
202!-- Set zero vertical velocity at topography top (l=0), or bottom (l=1) in case
203!-- of downward-facing surfaces.
204    DO  l = 0, 1
205!
206!--    Set kb, for upward-facing surfaces value at topography top (k-1) is set,
207!--    for downward-facing surfaces at topography bottom (k+1).
208       kb = MERGE( -1, 1, l == 0 )
209       !$OMP PARALLEL DO PRIVATE( i, j, k )
210       DO  m = 1, bc_h(l)%ns
211          i = bc_h(l)%i(m)           
212          j = bc_h(l)%j(m)
213          k = bc_h(l)%k(m)
214          w_p(k+kb,j,i) = 0.0_wp
[1113]215       ENDDO
216    ENDDO
217
218!
[1762]219!-- Top boundary. A nested domain ( ibc_uv_t = 3 ) does not require settings.
[1113]220    IF ( ibc_uv_t == 0 )  THEN
221        u_p(nzt+1,:,:) = u_init(nzt+1)
222        v_p(nzt+1,:,:) = v_init(nzt+1)
[1762]223    ELSEIF ( ibc_uv_t == 1 )  THEN
[1113]224        u_p(nzt+1,:,:) = u_p(nzt,:,:)
225        v_p(nzt+1,:,:) = v_p(nzt,:,:)
226    ENDIF
227
[1762]228    IF ( .NOT. nest_domain )  THEN
229       w_p(nzt:nzt+1,:,:) = 0.0_wp  ! nzt is not a prognostic level (but cf. pres)
230    ENDIF
231
[1113]232!
[2232]233!-- Temperature at bottom and top boundary.
[1113]234!-- In case of coupled runs (ibc_pt_b = 2) the temperature is given by
235!-- the sea surface temperature of the coupled ocean model.
[2232]236!-- Dirichlet
[1113]237    IF ( ibc_pt_b == 0 )  THEN
[2232]238       DO  l = 0, 1
239!
240!--       Set kb, for upward-facing surfaces value at topography top (k-1) is set,
241!--       for downward-facing surfaces at topography bottom (k+1).
242          kb = MERGE( -1, 1, l == 0 )
243          !$OMP PARALLEL DO PRIVATE( i, j, k )
244          DO  m = 1, bc_h(l)%ns
245             i = bc_h(l)%i(m)           
246             j = bc_h(l)%j(m)
247             k = bc_h(l)%k(m)
248             pt_p(k+kb,j,i) = pt(k+kb,j,i)
[1]249          ENDDO
250       ENDDO
[2232]251!
252!-- Neumann, zero-gradient
[1113]253    ELSEIF ( ibc_pt_b == 1 )  THEN
[2232]254       DO  l = 0, 1
255!
256!--       Set kb, for upward-facing surfaces value at topography top (k-1) is set,
257!--       for downward-facing surfaces at topography bottom (k+1).
258          kb = MERGE( -1, 1, l == 0 )
259          !$OMP PARALLEL DO PRIVATE( i, j, k )
260          DO  m = 1, bc_h(l)%ns
261             i = bc_h(l)%i(m)           
262             j = bc_h(l)%j(m)
263             k = bc_h(l)%k(m)
264             pt_p(k+kb,j,i) = pt_p(k,j,i)
[1113]265          ENDDO
266       ENDDO
267    ENDIF
[1]268
269!
[1113]270!-- Temperature at top boundary
271    IF ( ibc_pt_t == 0 )  THEN
272        pt_p(nzt+1,:,:) = pt(nzt+1,:,:)
[1380]273!
274!--     In case of nudging adjust top boundary to pt which is
275!--     read in from NUDGING-DATA
276        IF ( nudging )  THEN
277           pt_p(nzt+1,:,:) = pt_init(nzt+1)
278        ENDIF
[1113]279    ELSEIF ( ibc_pt_t == 1 )  THEN
280        pt_p(nzt+1,:,:) = pt_p(nzt,:,:)
281    ELSEIF ( ibc_pt_t == 2 )  THEN
[1992]282        pt_p(nzt+1,:,:) = pt_p(nzt,:,:) + bc_pt_t_val * dzu(nzt+1)
[1113]283    ENDIF
[1]284
285!
[1113]286!-- Boundary conditions for TKE
287!-- Generally Neumann conditions with de/dz=0 are assumed
288    IF ( .NOT. constant_diffusion )  THEN
[2232]289
290       DO  l = 0, 1
291!
292!--       Set kb, for upward-facing surfaces value at topography top (k-1) is set,
293!--       for downward-facing surfaces at topography bottom (k+1).
294          kb = MERGE( -1, 1, l == 0 )
295          !$OMP PARALLEL DO PRIVATE( i, j, k )
296          DO  m = 1, bc_h(l)%ns
297             i = bc_h(l)%i(m)           
298             j = bc_h(l)%j(m)
299             k = bc_h(l)%k(m)
300             e_p(k+kb,j,i) = e_p(k,j,i)
[73]301          ENDDO
[1113]302       ENDDO
[2232]303
[1762]304       IF ( .NOT. nest_domain )  THEN
305          e_p(nzt+1,:,:) = e_p(nzt,:,:)
306       ENDIF
[1113]307    ENDIF
308
309!
310!-- Boundary conditions for salinity
311    IF ( ocean )  THEN
312!
313!--    Bottom boundary: Neumann condition because salinity flux is always
[2232]314!--    given.
315       DO  l = 0, 1
316!
317!--       Set kb, for upward-facing surfaces value at topography top (k-1) is set,
318!--       for downward-facing surfaces at topography bottom (k+1).
319          kb = MERGE( -1, 1, l == 0 )
320          !$OMP PARALLEL DO PRIVATE( i, j, k )
321          DO  m = 1, bc_h(l)%ns
322             i = bc_h(l)%i(m)           
323             j = bc_h(l)%j(m)
324             k = bc_h(l)%k(m)
325             sa_p(k+kb,j,i) = sa_p(k,j,i)
[1]326          ENDDO
[1113]327       ENDDO
[1]328!
[1113]329!--    Top boundary: Dirichlet or Neumann
330       IF ( ibc_sa_t == 0 )  THEN
331           sa_p(nzt+1,:,:) = sa(nzt+1,:,:)
332       ELSEIF ( ibc_sa_t == 1 )  THEN
333           sa_p(nzt+1,:,:) = sa_p(nzt,:,:)
[1]334       ENDIF
335
[1113]336    ENDIF
337
[1]338!
[1960]339!-- Boundary conditions for total water content,
[1113]340!-- bottom and top boundary (see also temperature)
[1960]341    IF ( humidity )  THEN
[1113]342!
343!--    Surface conditions for constant_humidity_flux
[2232]344!--    Run loop over all non-natural and natural walls. Note, in wall-datatype
345!--    the k coordinate belongs to the atmospheric grid point, therefore, set
346!--    q_p at k-1
[1113]347       IF ( ibc_q_b == 0 ) THEN
[2232]348
349          DO  l = 0, 1
350!
351!--          Set kb, for upward-facing surfaces value at topography top (k-1) is set,
352!--          for downward-facing surfaces at topography bottom (k+1).
353             kb = MERGE( -1, 1, l == 0 )
354             !$OMP PARALLEL DO PRIVATE( i, j, k )
355             DO  m = 1, bc_h(l)%ns
356                i = bc_h(l)%i(m)           
357                j = bc_h(l)%j(m)
358                k = bc_h(l)%k(m)
359                q_p(k+kb,j,i) = q(k+kb,j,i)
[1]360             ENDDO
361          ENDDO
[2232]362         
[1113]363       ELSE
[2232]364          !$OMP PARALLEL DO PRIVATE( i, j, k )
365          DO  m = 1, bc_h(0)%ns
366             i = bc_h(0)%i(m)           
367             j = bc_h(0)%j(m)
368             k = bc_h(0)%k(m)
369             q_p(k-1,j,i) = q_p(k,j,i)
370          ENDDO
371         
372          DO  l = 0, 1
373!
374!--          Set kb, for upward-facing surfaces value at topography top (k-1) is set,
375!--          for downward-facing surfaces at topography bottom (k+1).
376             kb = MERGE( -1, 1, l == 0 )
377             !$OMP PARALLEL DO PRIVATE( i, j, k )
378             DO  m = 1, bc_h(l)%ns
379                i = bc_h(l)%i(m)           
380                j = bc_h(l)%j(m)
381                k = bc_h(l)%k(m)
382                q_p(k+kb,j,i) = q_p(k,j,i)
[95]383             ENDDO
384          ENDDO
[1113]385       ENDIF
[95]386!
[1113]387!--    Top boundary
[1462]388       IF ( ibc_q_t == 0 ) THEN
389          q_p(nzt+1,:,:) = q(nzt+1,:,:)
390       ELSEIF ( ibc_q_t == 1 ) THEN
[1992]391          q_p(nzt+1,:,:) = q_p(nzt,:,:) + bc_q_t_val * dzu(nzt+1)
[1462]392       ENDIF
[95]393
[1822]394       IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
[1113]395!             
[1361]396!--       Surface conditions rain water (Dirichlet)
[2232]397!--       Run loop over all non-natural and natural walls. Note, in wall-datatype
398!--       the k coordinate belongs to the atmospheric grid point, therefore, set
399!--       qr_p and nr_p at k-1
400          !$OMP PARALLEL DO PRIVATE( i, j, k )
401          DO  m = 1, bc_h(0)%ns
402             i = bc_h(0)%i(m)           
403             j = bc_h(0)%j(m)
404             k = bc_h(0)%k(m)
405             qr_p(k-1,j,i) = 0.0_wp
406             nr_p(k-1,j,i) = 0.0_wp
[1115]407          ENDDO
[1]408!
[1361]409!--       Top boundary condition for rain water (Dirichlet)
410          qr_p(nzt+1,:,:) = 0.0_wp
411          nr_p(nzt+1,:,:) = 0.0_wp
[1115]412           
[1]413       ENDIF
[1409]414    ENDIF
[1]415!
[1960]416!-- Boundary conditions for scalar,
417!-- bottom and top boundary (see also temperature)
418    IF ( passive_scalar )  THEN
419!
420!--    Surface conditions for constant_humidity_flux
[2232]421!--    Run loop over all non-natural and natural walls. Note, in wall-datatype
422!--    the k coordinate belongs to the atmospheric grid point, therefore, set
423!--    s_p at k-1
[1960]424       IF ( ibc_s_b == 0 ) THEN
[2232]425         
426          DO  l = 0, 1
427!
428!--          Set kb, for upward-facing surfaces value at topography top (k-1) is set,
429!--          for downward-facing surfaces at topography bottom (k+1).
430             kb = MERGE( -1, 1, l == 0 )
431             !$OMP PARALLEL DO PRIVATE( i, j, k )
432             DO  m = 1, bc_h(l)%ns
433                i = bc_h(l)%i(m)           
434                j = bc_h(l)%j(m)
435                k = bc_h(l)%k(m)
436                s_p(k+kb,j,i) = s(k+kb,j,i)
[1960]437             ENDDO
438          ENDDO
[2232]439         
[1960]440       ELSE
[2232]441          !$OMP PARALLEL DO PRIVATE( i, j, k )
442          DO  m = 1, bc_h(0)%ns
443             i = bc_h(0)%i(m)           
444             j = bc_h(0)%j(m)
445             k = bc_h(0)%k(m)
446             s_p(k-1,j,i) = s_p(k,j,i)
447          ENDDO
448         
449          DO  l = 0, 1
450!
451!--          Set kb, for upward-facing surfaces value at topography top (k-1) is set,
452!--          for downward-facing surfaces at topography bottom (k+1).
453             kb = MERGE( -1, 1, l == 0 )
454             !$OMP PARALLEL DO PRIVATE( i, j, k )
455             DO  m = 1, bc_h(l)%ns
456                i = bc_h(l)%i(m)           
457                j = bc_h(l)%j(m)
458                k = bc_h(l)%k(m)
459                s_p(k+kb,j,i) = s_p(k,j,i)
[1960]460             ENDDO
461          ENDDO
462       ENDIF
463!
[1992]464!--    Top boundary condition
465       IF ( ibc_s_t == 0 )  THEN
[1960]466          s_p(nzt+1,:,:) = s(nzt+1,:,:)
[1992]467       ELSEIF ( ibc_s_t == 1 )  THEN
468          s_p(nzt+1,:,:) = s_p(nzt,:,:)
469       ELSEIF ( ibc_s_t == 2 )  THEN
470          s_p(nzt+1,:,:) = s_p(nzt,:,:) + bc_s_t_val * dzu(nzt+1)
[1960]471       ENDIF
472
473    ENDIF   
474!
[1762]475!-- In case of inflow or nest boundary at the south boundary the boundary for v
476!-- is at nys and in case of inflow or nest boundary at the left boundary the
477!-- boundary for u is at nxl. Since in prognostic_equations (cache optimized
478!-- version) these levels are handled as a prognostic level, boundary values
479!-- have to be restored here.
[1409]480!-- For the SGS-TKE, Neumann boundary conditions are used at the inflow.
481    IF ( inflow_s )  THEN
482       v_p(:,nys,:) = v_p(:,nys-1,:)
483       IF ( .NOT. constant_diffusion ) e_p(:,nys-1,:) = e_p(:,nys,:)
484    ELSEIF ( inflow_n )  THEN
485       IF ( .NOT. constant_diffusion ) e_p(:,nyn+1,:) = e_p(:,nyn,:)
486    ELSEIF ( inflow_l ) THEN
487       u_p(:,:,nxl) = u_p(:,:,nxl-1)
488       IF ( .NOT. constant_diffusion ) e_p(:,:,nxl-1) = e_p(:,:,nxl)
489    ELSEIF ( inflow_r )  THEN
490       IF ( .NOT. constant_diffusion ) e_p(:,:,nxr+1) = e_p(:,:,nxr)
491    ENDIF
[1]492
493!
[1762]494!-- The same restoration for u at i=nxl and v at j=nys as above must be made
[1933]495!-- in case of nest boundaries. This must not be done in case of vertical nesting
496!-- mode as in that case the lateral boundaries are actually cyclic.
497    IF ( nesting_mode /= 'vertical' )  THEN
498       IF ( nest_bound_s )  THEN
499          v_p(:,nys,:) = v_p(:,nys-1,:)
500       ENDIF
501       IF ( nest_bound_l )  THEN
502          u_p(:,:,nxl) = u_p(:,:,nxl-1)
503       ENDIF
[1762]504    ENDIF
505
506!
[1409]507!-- Lateral boundary conditions for scalar quantities at the outflow
508    IF ( outflow_s )  THEN
509       pt_p(:,nys-1,:)     = pt_p(:,nys,:)
[2232]510       IF ( .NOT. constant_diffusion )  e_p(:,nys-1,:) = e_p(:,nys,:)
[1960]511       IF ( humidity )  THEN
[1409]512          q_p(:,nys-1,:) = q_p(:,nys,:)
[1822]513          IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
[1409]514             qr_p(:,nys-1,:) = qr_p(:,nys,:)
515             nr_p(:,nys-1,:) = nr_p(:,nys,:)
[1053]516          ENDIF
[1409]517       ENDIF
[1960]518       IF ( passive_scalar )  s_p(:,nys-1,:) = s_p(:,nys,:)
[1409]519    ELSEIF ( outflow_n )  THEN
520       pt_p(:,nyn+1,:)     = pt_p(:,nyn,:)
521       IF ( .NOT. constant_diffusion     )  e_p(:,nyn+1,:) = e_p(:,nyn,:)
[1960]522       IF ( humidity )  THEN
[1409]523          q_p(:,nyn+1,:) = q_p(:,nyn,:)
[1822]524          IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
[1409]525             qr_p(:,nyn+1,:) = qr_p(:,nyn,:)
526             nr_p(:,nyn+1,:) = nr_p(:,nyn,:)
[1053]527          ENDIF
[1409]528       ENDIF
[1960]529       IF ( passive_scalar )  s_p(:,nyn+1,:) = s_p(:,nyn,:)
[1409]530    ELSEIF ( outflow_l )  THEN
531       pt_p(:,:,nxl-1)     = pt_p(:,:,nxl)
532       IF ( .NOT. constant_diffusion     )  e_p(:,:,nxl-1) = e_p(:,:,nxl)
[1960]533       IF ( humidity )  THEN
[1409]534          q_p(:,:,nxl-1) = q_p(:,:,nxl)
[1822]535          IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
[1409]536             qr_p(:,:,nxl-1) = qr_p(:,:,nxl)
537             nr_p(:,:,nxl-1) = nr_p(:,:,nxl)
[1053]538          ENDIF
[1409]539       ENDIF
[1960]540       IF ( passive_scalar )  s_p(:,:,nxl-1) = s_p(:,:,nxl)
[1409]541    ELSEIF ( outflow_r )  THEN
542       pt_p(:,:,nxr+1)     = pt_p(:,:,nxr)
543       IF ( .NOT. constant_diffusion     )  e_p(:,:,nxr+1) = e_p(:,:,nxr)
[1960]544       IF ( humidity )  THEN
[1409]545          q_p(:,:,nxr+1) = q_p(:,:,nxr)
[1822]546          IF ( cloud_physics  .AND.  microphysics_seifert )  THEN
[1409]547             qr_p(:,:,nxr+1) = qr_p(:,:,nxr)
548             nr_p(:,:,nxr+1) = nr_p(:,:,nxr)
[1053]549          ENDIF
[1]550       ENDIF
[1960]551       IF ( passive_scalar )  s_p(:,:,nxr+1) = s_p(:,:,nxr)
[1]552    ENDIF
553
554!
[1159]555!-- Radiation boundary conditions for the velocities at the respective outflow.
556!-- The phase velocity is either assumed to the maximum phase velocity that
557!-- ensures numerical stability (CFL-condition) or calculated after
558!-- Orlanski(1976) and averaged along the outflow boundary.
[106]559    IF ( outflow_s )  THEN
[75]560
[1159]561       IF ( use_cmax )  THEN
562          u_p(:,-1,:) = u(:,0,:)
563          v_p(:,0,:)  = v(:,1,:)
564          w_p(:,-1,:) = w(:,0,:)         
565       ELSEIF ( .NOT. use_cmax )  THEN
[75]566
[978]567          c_max = dy / dt_3d
[75]568
[1353]569          c_u_m_l = 0.0_wp 
570          c_v_m_l = 0.0_wp
571          c_w_m_l = 0.0_wp
[978]572
[1353]573          c_u_m = 0.0_wp 
574          c_v_m = 0.0_wp
575          c_w_m = 0.0_wp
[978]576
[75]577!
[996]578!--       Calculate the phase speeds for u, v, and w, first local and then
579!--       average along the outflow boundary.
580          DO  k = nzb+1, nzt+1
581             DO  i = nxl, nxr
[75]582
[106]583                denom = u_m_s(k,0,i) - u_m_s(k,1,i)
584
[1353]585                IF ( denom /= 0.0_wp )  THEN
[996]586                   c_u(k,i) = -c_max * ( u(k,0,i) - u_m_s(k,0,i) ) / ( denom * tsc(2) )
[1353]587                   IF ( c_u(k,i) < 0.0_wp )  THEN
588                      c_u(k,i) = 0.0_wp
[106]589                   ELSEIF ( c_u(k,i) > c_max )  THEN
590                      c_u(k,i) = c_max
591                   ENDIF
592                ELSE
593                   c_u(k,i) = c_max
[75]594                ENDIF
595
[106]596                denom = v_m_s(k,1,i) - v_m_s(k,2,i)
597
[1353]598                IF ( denom /= 0.0_wp )  THEN
[996]599                   c_v(k,i) = -c_max * ( v(k,1,i) - v_m_s(k,1,i) ) / ( denom * tsc(2) )
[1353]600                   IF ( c_v(k,i) < 0.0_wp )  THEN
601                      c_v(k,i) = 0.0_wp
[106]602                   ELSEIF ( c_v(k,i) > c_max )  THEN
603                      c_v(k,i) = c_max
604                   ENDIF
605                ELSE
606                   c_v(k,i) = c_max
[75]607                ENDIF
608
[106]609                denom = w_m_s(k,0,i) - w_m_s(k,1,i)
[75]610
[1353]611                IF ( denom /= 0.0_wp )  THEN
[996]612                   c_w(k,i) = -c_max * ( w(k,0,i) - w_m_s(k,0,i) ) / ( denom * tsc(2) )
[1353]613                   IF ( c_w(k,i) < 0.0_wp )  THEN
614                      c_w(k,i) = 0.0_wp
[106]615                   ELSEIF ( c_w(k,i) > c_max )  THEN
616                      c_w(k,i) = c_max
617                   ENDIF
618                ELSE
619                   c_w(k,i) = c_max
[75]620                ENDIF
[106]621
[978]622                c_u_m_l(k) = c_u_m_l(k) + c_u(k,i)
623                c_v_m_l(k) = c_v_m_l(k) + c_v(k,i)
624                c_w_m_l(k) = c_w_m_l(k) + c_w(k,i)
[106]625
[978]626             ENDDO
627          ENDDO
[75]628
[978]629#if defined( __parallel )   
630          IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
631          CALL MPI_ALLREDUCE( c_u_m_l(nzb+1), c_u_m(nzb+1), nzt-nzb, MPI_REAL, &
632                              MPI_SUM, comm1dx, ierr )   
633          IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
634          CALL MPI_ALLREDUCE( c_v_m_l(nzb+1), c_v_m(nzb+1), nzt-nzb, MPI_REAL, &
635                              MPI_SUM, comm1dx, ierr ) 
636          IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
637          CALL MPI_ALLREDUCE( c_w_m_l(nzb+1), c_w_m(nzb+1), nzt-nzb, MPI_REAL, &
638                              MPI_SUM, comm1dx, ierr ) 
639#else
640          c_u_m = c_u_m_l
641          c_v_m = c_v_m_l
642          c_w_m = c_w_m_l
643#endif
644
645          c_u_m = c_u_m / (nx+1)
646          c_v_m = c_v_m / (nx+1)
647          c_w_m = c_w_m / (nx+1)
648
[75]649!
[978]650!--       Save old timelevels for the next timestep
651          IF ( intermediate_timestep_count == 1 )  THEN
652             u_m_s(:,:,:) = u(:,0:1,:)
653             v_m_s(:,:,:) = v(:,1:2,:)
654             w_m_s(:,:,:) = w(:,0:1,:)
655          ENDIF
656
657!
658!--       Calculate the new velocities
[996]659          DO  k = nzb+1, nzt+1
660             DO  i = nxlg, nxrg
[978]661                u_p(k,-1,i) = u(k,-1,i) - dt_3d * tsc(2) * c_u_m(k) *          &
[75]662                                       ( u(k,-1,i) - u(k,0,i) ) * ddy
663
[978]664                v_p(k,0,i)  = v(k,0,i)  - dt_3d * tsc(2) * c_v_m(k) *          &
[106]665                                       ( v(k,0,i) - v(k,1,i) ) * ddy
[75]666
[978]667                w_p(k,-1,i) = w(k,-1,i) - dt_3d * tsc(2) * c_w_m(k) *          &
[75]668                                       ( w(k,-1,i) - w(k,0,i) ) * ddy
[978]669             ENDDO
[75]670          ENDDO
671
672!
[978]673!--       Bottom boundary at the outflow
674          IF ( ibc_uv_b == 0 )  THEN
[1353]675             u_p(nzb,-1,:) = 0.0_wp 
676             v_p(nzb,0,:)  = 0.0_wp 
[978]677          ELSE                   
678             u_p(nzb,-1,:) =  u_p(nzb+1,-1,:)
679             v_p(nzb,0,:)  =  v_p(nzb+1,0,:)
680          ENDIF
[1353]681          w_p(nzb,-1,:) = 0.0_wp
[73]682
[75]683!
[978]684!--       Top boundary at the outflow
685          IF ( ibc_uv_t == 0 )  THEN
686             u_p(nzt+1,-1,:) = u_init(nzt+1)
687             v_p(nzt+1,0,:)  = v_init(nzt+1)
688          ELSE
[1742]689             u_p(nzt+1,-1,:) = u_p(nzt,-1,:)
690             v_p(nzt+1,0,:)  = v_p(nzt,0,:)
[978]691          ENDIF
[1353]692          w_p(nzt:nzt+1,-1,:) = 0.0_wp
[978]693
[75]694       ENDIF
[73]695
[75]696    ENDIF
[73]697
[106]698    IF ( outflow_n )  THEN
[73]699
[1159]700       IF ( use_cmax )  THEN
701          u_p(:,ny+1,:) = u(:,ny,:)
702          v_p(:,ny+1,:) = v(:,ny,:)
703          w_p(:,ny+1,:) = w(:,ny,:)         
704       ELSEIF ( .NOT. use_cmax )  THEN
[75]705
[978]706          c_max = dy / dt_3d
[75]707
[1353]708          c_u_m_l = 0.0_wp 
709          c_v_m_l = 0.0_wp
710          c_w_m_l = 0.0_wp
[978]711
[1353]712          c_u_m = 0.0_wp 
713          c_v_m = 0.0_wp
714          c_w_m = 0.0_wp
[978]715
[1]716!
[996]717!--       Calculate the phase speeds for u, v, and w, first local and then
718!--       average along the outflow boundary.
719          DO  k = nzb+1, nzt+1
720             DO  i = nxl, nxr
[73]721
[106]722                denom = u_m_n(k,ny,i) - u_m_n(k,ny-1,i)
723
[1353]724                IF ( denom /= 0.0_wp )  THEN
[996]725                   c_u(k,i) = -c_max * ( u(k,ny,i) - u_m_n(k,ny,i) ) / ( denom * tsc(2) )
[1353]726                   IF ( c_u(k,i) < 0.0_wp )  THEN
727                      c_u(k,i) = 0.0_wp
[106]728                   ELSEIF ( c_u(k,i) > c_max )  THEN
729                      c_u(k,i) = c_max
730                   ENDIF
731                ELSE
732                   c_u(k,i) = c_max
[73]733                ENDIF
734
[106]735                denom = v_m_n(k,ny,i) - v_m_n(k,ny-1,i)
[73]736
[1353]737                IF ( denom /= 0.0_wp )  THEN
[996]738                   c_v(k,i) = -c_max * ( v(k,ny,i) - v_m_n(k,ny,i) ) / ( denom * tsc(2) )
[1353]739                   IF ( c_v(k,i) < 0.0_wp )  THEN
740                      c_v(k,i) = 0.0_wp
[106]741                   ELSEIF ( c_v(k,i) > c_max )  THEN
742                      c_v(k,i) = c_max
743                   ENDIF
744                ELSE
745                   c_v(k,i) = c_max
[73]746                ENDIF
747
[106]748                denom = w_m_n(k,ny,i) - w_m_n(k,ny-1,i)
[73]749
[1353]750                IF ( denom /= 0.0_wp )  THEN
[996]751                   c_w(k,i) = -c_max * ( w(k,ny,i) - w_m_n(k,ny,i) ) / ( denom * tsc(2) )
[1353]752                   IF ( c_w(k,i) < 0.0_wp )  THEN
753                      c_w(k,i) = 0.0_wp
[106]754                   ELSEIF ( c_w(k,i) > c_max )  THEN
755                      c_w(k,i) = c_max
756                   ENDIF
757                ELSE
758                   c_w(k,i) = c_max
[73]759                ENDIF
[106]760
[978]761                c_u_m_l(k) = c_u_m_l(k) + c_u(k,i)
762                c_v_m_l(k) = c_v_m_l(k) + c_v(k,i)
763                c_w_m_l(k) = c_w_m_l(k) + c_w(k,i)
[106]764
[978]765             ENDDO
766          ENDDO
[73]767
[978]768#if defined( __parallel )   
769          IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
770          CALL MPI_ALLREDUCE( c_u_m_l(nzb+1), c_u_m(nzb+1), nzt-nzb, MPI_REAL, &
771                              MPI_SUM, comm1dx, ierr )   
772          IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
773          CALL MPI_ALLREDUCE( c_v_m_l(nzb+1), c_v_m(nzb+1), nzt-nzb, MPI_REAL, &
774                              MPI_SUM, comm1dx, ierr ) 
775          IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
776          CALL MPI_ALLREDUCE( c_w_m_l(nzb+1), c_w_m(nzb+1), nzt-nzb, MPI_REAL, &
777                              MPI_SUM, comm1dx, ierr ) 
778#else
779          c_u_m = c_u_m_l
780          c_v_m = c_v_m_l
781          c_w_m = c_w_m_l
782#endif
783
784          c_u_m = c_u_m / (nx+1)
785          c_v_m = c_v_m / (nx+1)
786          c_w_m = c_w_m / (nx+1)
787
[73]788!
[978]789!--       Save old timelevels for the next timestep
790          IF ( intermediate_timestep_count == 1 )  THEN
791                u_m_n(:,:,:) = u(:,ny-1:ny,:)
792                v_m_n(:,:,:) = v(:,ny-1:ny,:)
793                w_m_n(:,:,:) = w(:,ny-1:ny,:)
794          ENDIF
[73]795
[978]796!
797!--       Calculate the new velocities
[996]798          DO  k = nzb+1, nzt+1
799             DO  i = nxlg, nxrg
[978]800                u_p(k,ny+1,i) = u(k,ny+1,i) - dt_3d * tsc(2) * c_u_m(k) *      &
801                                       ( u(k,ny+1,i) - u(k,ny,i) ) * ddy
[73]802
[978]803                v_p(k,ny+1,i) = v(k,ny+1,i)  - dt_3d * tsc(2) * c_v_m(k) *     &
804                                       ( v(k,ny+1,i) - v(k,ny,i) ) * ddy
[73]805
[978]806                w_p(k,ny+1,i) = w(k,ny+1,i) - dt_3d * tsc(2) * c_w_m(k) *      &
807                                       ( w(k,ny+1,i) - w(k,ny,i) ) * ddy
808             ENDDO
[1]809          ENDDO
810
811!
[978]812!--       Bottom boundary at the outflow
813          IF ( ibc_uv_b == 0 )  THEN
[1353]814             u_p(nzb,ny+1,:) = 0.0_wp
815             v_p(nzb,ny+1,:) = 0.0_wp   
[978]816          ELSE                   
817             u_p(nzb,ny+1,:) =  u_p(nzb+1,ny+1,:)
818             v_p(nzb,ny+1,:) =  v_p(nzb+1,ny+1,:)
819          ENDIF
[1353]820          w_p(nzb,ny+1,:) = 0.0_wp
[73]821
822!
[978]823!--       Top boundary at the outflow
824          IF ( ibc_uv_t == 0 )  THEN
825             u_p(nzt+1,ny+1,:) = u_init(nzt+1)
826             v_p(nzt+1,ny+1,:) = v_init(nzt+1)
827          ELSE
828             u_p(nzt+1,ny+1,:) = u_p(nzt,nyn+1,:)
829             v_p(nzt+1,ny+1,:) = v_p(nzt,nyn+1,:)
830          ENDIF
[1353]831          w_p(nzt:nzt+1,ny+1,:) = 0.0_wp
[978]832
[1]833       ENDIF
834
[75]835    ENDIF
836
[106]837    IF ( outflow_l )  THEN
[75]838
[1159]839       IF ( use_cmax )  THEN
[1717]840          u_p(:,:,0)  = u(:,:,1)
841          v_p(:,:,-1) = v(:,:,0)
[1159]842          w_p(:,:,-1) = w(:,:,0)         
843       ELSEIF ( .NOT. use_cmax )  THEN
[75]844
[978]845          c_max = dx / dt_3d
[75]846
[1353]847          c_u_m_l = 0.0_wp 
848          c_v_m_l = 0.0_wp
849          c_w_m_l = 0.0_wp
[978]850
[1353]851          c_u_m = 0.0_wp 
852          c_v_m = 0.0_wp
853          c_w_m = 0.0_wp
[978]854
[1]855!
[996]856!--       Calculate the phase speeds for u, v, and w, first local and then
857!--       average along the outflow boundary.
858          DO  k = nzb+1, nzt+1
859             DO  j = nys, nyn
[75]860
[106]861                denom = u_m_l(k,j,1) - u_m_l(k,j,2)
862
[1353]863                IF ( denom /= 0.0_wp )  THEN
[996]864                   c_u(k,j) = -c_max * ( u(k,j,1) - u_m_l(k,j,1) ) / ( denom * tsc(2) )
[1353]865                   IF ( c_u(k,j) < 0.0_wp )  THEN
866                      c_u(k,j) = 0.0_wp
[107]867                   ELSEIF ( c_u(k,j) > c_max )  THEN
868                      c_u(k,j) = c_max
[106]869                   ENDIF
870                ELSE
[107]871                   c_u(k,j) = c_max
[75]872                ENDIF
873
[106]874                denom = v_m_l(k,j,0) - v_m_l(k,j,1)
[75]875
[1353]876                IF ( denom /= 0.0_wp )  THEN
[996]877                   c_v(k,j) = -c_max * ( v(k,j,0) - v_m_l(k,j,0) ) / ( denom * tsc(2) )
[1353]878                   IF ( c_v(k,j) < 0.0_wp )  THEN
879                      c_v(k,j) = 0.0_wp
[106]880                   ELSEIF ( c_v(k,j) > c_max )  THEN
881                      c_v(k,j) = c_max
882                   ENDIF
883                ELSE
884                   c_v(k,j) = c_max
[75]885                ENDIF
886
[106]887                denom = w_m_l(k,j,0) - w_m_l(k,j,1)
[75]888
[1353]889                IF ( denom /= 0.0_wp )  THEN
[996]890                   c_w(k,j) = -c_max * ( w(k,j,0) - w_m_l(k,j,0) ) / ( denom * tsc(2) )
[1353]891                   IF ( c_w(k,j) < 0.0_wp )  THEN
892                      c_w(k,j) = 0.0_wp
[106]893                   ELSEIF ( c_w(k,j) > c_max )  THEN
894                      c_w(k,j) = c_max
895                   ENDIF
896                ELSE
897                   c_w(k,j) = c_max
[75]898                ENDIF
[106]899
[978]900                c_u_m_l(k) = c_u_m_l(k) + c_u(k,j)
901                c_v_m_l(k) = c_v_m_l(k) + c_v(k,j)
902                c_w_m_l(k) = c_w_m_l(k) + c_w(k,j)
[106]903
[978]904             ENDDO
905          ENDDO
[75]906
[978]907#if defined( __parallel )   
908          IF ( collective_wait )  CALL MPI_BARRIER( comm1dy, ierr )
909          CALL MPI_ALLREDUCE( c_u_m_l(nzb+1), c_u_m(nzb+1), nzt-nzb, MPI_REAL, &
910                              MPI_SUM, comm1dy, ierr )   
911          IF ( collective_wait )  CALL MPI_BARRIER( comm1dy, ierr )
912          CALL MPI_ALLREDUCE( c_v_m_l(nzb+1), c_v_m(nzb+1), nzt-nzb, MPI_REAL, &
913                              MPI_SUM, comm1dy, ierr ) 
914          IF ( collective_wait )  CALL MPI_BARRIER( comm1dy, ierr )
915          CALL MPI_ALLREDUCE( c_w_m_l(nzb+1), c_w_m(nzb+1), nzt-nzb, MPI_REAL, &
916                              MPI_SUM, comm1dy, ierr ) 
917#else
918          c_u_m = c_u_m_l
919          c_v_m = c_v_m_l
920          c_w_m = c_w_m_l
921#endif
922
923          c_u_m = c_u_m / (ny+1)
924          c_v_m = c_v_m / (ny+1)
925          c_w_m = c_w_m / (ny+1)
926
[73]927!
[978]928!--       Save old timelevels for the next timestep
929          IF ( intermediate_timestep_count == 1 )  THEN
930                u_m_l(:,:,:) = u(:,:,1:2)
931                v_m_l(:,:,:) = v(:,:,0:1)
932                w_m_l(:,:,:) = w(:,:,0:1)
933          ENDIF
934
935!
936!--       Calculate the new velocities
[996]937          DO  k = nzb+1, nzt+1
[1113]938             DO  j = nysg, nyng
[978]939                u_p(k,j,0) = u(k,j,0) - dt_3d * tsc(2) * c_u_m(k) *            &
[106]940                                       ( u(k,j,0) - u(k,j,1) ) * ddx
[75]941
[978]942                v_p(k,j,-1) = v(k,j,-1) - dt_3d * tsc(2) * c_v_m(k) *          &
[75]943                                       ( v(k,j,-1) - v(k,j,0) ) * ddx
944
[978]945                w_p(k,j,-1) = w(k,j,-1) - dt_3d * tsc(2) * c_w_m(k) *          &
[75]946                                       ( w(k,j,-1) - w(k,j,0) ) * ddx
[978]947             ENDDO
[75]948          ENDDO
949
950!
[978]951!--       Bottom boundary at the outflow
952          IF ( ibc_uv_b == 0 )  THEN
[1353]953             u_p(nzb,:,0)  = 0.0_wp 
954             v_p(nzb,:,-1) = 0.0_wp
[978]955          ELSE                   
956             u_p(nzb,:,0)  =  u_p(nzb+1,:,0)
957             v_p(nzb,:,-1) =  v_p(nzb+1,:,-1)
958          ENDIF
[1353]959          w_p(nzb,:,-1) = 0.0_wp
[1]960
[75]961!
[978]962!--       Top boundary at the outflow
963          IF ( ibc_uv_t == 0 )  THEN
[1764]964             u_p(nzt+1,:,0)  = u_init(nzt+1)
[978]965             v_p(nzt+1,:,-1) = v_init(nzt+1)
966          ELSE
[1764]967             u_p(nzt+1,:,0)  = u_p(nzt,:,0)
[978]968             v_p(nzt+1,:,-1) = v_p(nzt,:,-1)
969          ENDIF
[1353]970          w_p(nzt:nzt+1,:,-1) = 0.0_wp
[978]971
[75]972       ENDIF
[73]973
[75]974    ENDIF
[73]975
[106]976    IF ( outflow_r )  THEN
[73]977
[1159]978       IF ( use_cmax )  THEN
979          u_p(:,:,nx+1) = u(:,:,nx)
980          v_p(:,:,nx+1) = v(:,:,nx)
981          w_p(:,:,nx+1) = w(:,:,nx)         
982       ELSEIF ( .NOT. use_cmax )  THEN
[75]983
[978]984          c_max = dx / dt_3d
[75]985
[1353]986          c_u_m_l = 0.0_wp 
987          c_v_m_l = 0.0_wp
988          c_w_m_l = 0.0_wp
[978]989
[1353]990          c_u_m = 0.0_wp 
991          c_v_m = 0.0_wp
992          c_w_m = 0.0_wp
[978]993
[1]994!
[996]995!--       Calculate the phase speeds for u, v, and w, first local and then
996!--       average along the outflow boundary.
997          DO  k = nzb+1, nzt+1
998             DO  j = nys, nyn
[73]999
[106]1000                denom = u_m_r(k,j,nx) - u_m_r(k,j,nx-1)
1001
[1353]1002                IF ( denom /= 0.0_wp )  THEN
[996]1003                   c_u(k,j) = -c_max * ( u(k,j,nx) - u_m_r(k,j,nx) ) / ( denom * tsc(2) )
[1353]1004                   IF ( c_u(k,j) < 0.0_wp )  THEN
1005                      c_u(k,j) = 0.0_wp
[106]1006                   ELSEIF ( c_u(k,j) > c_max )  THEN
1007                      c_u(k,j) = c_max
1008                   ENDIF
1009                ELSE
1010                   c_u(k,j) = c_max
[73]1011                ENDIF
1012
[106]1013                denom = v_m_r(k,j,nx) - v_m_r(k,j,nx-1)
[73]1014
[1353]1015                IF ( denom /= 0.0_wp )  THEN
[996]1016                   c_v(k,j) = -c_max * ( v(k,j,nx) - v_m_r(k,j,nx) ) / ( denom * tsc(2) )
[1353]1017                   IF ( c_v(k,j) < 0.0_wp )  THEN
1018                      c_v(k,j) = 0.0_wp
[106]1019                   ELSEIF ( c_v(k,j) > c_max )  THEN
1020                      c_v(k,j) = c_max
1021                   ENDIF
1022                ELSE
1023                   c_v(k,j) = c_max
[73]1024                ENDIF
1025
[106]1026                denom = w_m_r(k,j,nx) - w_m_r(k,j,nx-1)
[73]1027
[1353]1028                IF ( denom /= 0.0_wp )  THEN
[996]1029                   c_w(k,j) = -c_max * ( w(k,j,nx) - w_m_r(k,j,nx) ) / ( denom * tsc(2) )
[1353]1030                   IF ( c_w(k,j) < 0.0_wp )  THEN
1031                      c_w(k,j) = 0.0_wp
[106]1032                   ELSEIF ( c_w(k,j) > c_max )  THEN
1033                      c_w(k,j) = c_max
1034                   ENDIF
1035                ELSE
1036                   c_w(k,j) = c_max
[73]1037                ENDIF
[106]1038
[978]1039                c_u_m_l(k) = c_u_m_l(k) + c_u(k,j)
1040                c_v_m_l(k) = c_v_m_l(k) + c_v(k,j)
1041                c_w_m_l(k) = c_w_m_l(k) + c_w(k,j)
[106]1042
[978]1043             ENDDO
1044          ENDDO
[73]1045
[978]1046#if defined( __parallel )   
1047          IF ( collective_wait )  CALL MPI_BARRIER( comm1dy, ierr )
1048          CALL MPI_ALLREDUCE( c_u_m_l(nzb+1), c_u_m(nzb+1), nzt-nzb, MPI_REAL, &
1049                              MPI_SUM, comm1dy, ierr )   
1050          IF ( collective_wait )  CALL MPI_BARRIER( comm1dy, ierr )
1051          CALL MPI_ALLREDUCE( c_v_m_l(nzb+1), c_v_m(nzb+1), nzt-nzb, MPI_REAL, &
1052                              MPI_SUM, comm1dy, ierr ) 
1053          IF ( collective_wait )  CALL MPI_BARRIER( comm1dy, ierr )
1054          CALL MPI_ALLREDUCE( c_w_m_l(nzb+1), c_w_m(nzb+1), nzt-nzb, MPI_REAL, &
1055                              MPI_SUM, comm1dy, ierr ) 
1056#else
1057          c_u_m = c_u_m_l
1058          c_v_m = c_v_m_l
1059          c_w_m = c_w_m_l
1060#endif
1061
1062          c_u_m = c_u_m / (ny+1)
1063          c_v_m = c_v_m / (ny+1)
1064          c_w_m = c_w_m / (ny+1)
1065
[73]1066!
[978]1067!--       Save old timelevels for the next timestep
1068          IF ( intermediate_timestep_count == 1 )  THEN
1069                u_m_r(:,:,:) = u(:,:,nx-1:nx)
1070                v_m_r(:,:,:) = v(:,:,nx-1:nx)
1071                w_m_r(:,:,:) = w(:,:,nx-1:nx)
1072          ENDIF
[73]1073
[978]1074!
1075!--       Calculate the new velocities
[996]1076          DO  k = nzb+1, nzt+1
[1113]1077             DO  j = nysg, nyng
[978]1078                u_p(k,j,nx+1) = u(k,j,nx+1) - dt_3d * tsc(2) * c_u_m(k) *      &
1079                                       ( u(k,j,nx+1) - u(k,j,nx) ) * ddx
[73]1080
[978]1081                v_p(k,j,nx+1) = v(k,j,nx+1) - dt_3d * tsc(2) * c_v_m(k) *      &
1082                                       ( v(k,j,nx+1) - v(k,j,nx) ) * ddx
[73]1083
[978]1084                w_p(k,j,nx+1) = w(k,j,nx+1) - dt_3d * tsc(2) * c_w_m(k) *      &
1085                                       ( w(k,j,nx+1) - w(k,j,nx) ) * ddx
1086             ENDDO
[73]1087          ENDDO
1088
1089!
[978]1090!--       Bottom boundary at the outflow
1091          IF ( ibc_uv_b == 0 )  THEN
[1353]1092             u_p(nzb,:,nx+1) = 0.0_wp
1093             v_p(nzb,:,nx+1) = 0.0_wp 
[978]1094          ELSE                   
1095             u_p(nzb,:,nx+1) =  u_p(nzb+1,:,nx+1)
1096             v_p(nzb,:,nx+1) =  v_p(nzb+1,:,nx+1)
1097          ENDIF
[1353]1098          w_p(nzb,:,nx+1) = 0.0_wp
[73]1099
1100!
[978]1101!--       Top boundary at the outflow
1102          IF ( ibc_uv_t == 0 )  THEN
1103             u_p(nzt+1,:,nx+1) = u_init(nzt+1)
1104             v_p(nzt+1,:,nx+1) = v_init(nzt+1)
1105          ELSE
1106             u_p(nzt+1,:,nx+1) = u_p(nzt,:,nx+1)
1107             v_p(nzt+1,:,nx+1) = v_p(nzt,:,nx+1)
1108          ENDIF
[1742]1109          w_p(nzt:nzt+1,:,nx+1) = 0.0_wp
[978]1110
[1]1111       ENDIF
1112
1113    ENDIF
1114
1115 END SUBROUTINE boundary_conds
Note: See TracBrowser for help on using the repository browser.