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

Last change on this file since 1960 was 1960, checked in by suehring, 8 years ago

Separate balance equations for humidity and passive_scalar

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