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

Last change on this file since 1462 was 1462, checked in by suehring, 10 years ago

Bugfix: set dirichlet boundary condition for passive_scalar at model domain top

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