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

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

last commit documented

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