Changeset 4268 for palm


Ignore:
Timestamp:
Oct 17, 2019 11:29:38 AM (4 years ago)
Author:
schwenkel
Message:

Introducing module interface for boundary conditions and move module specific boundary conditions into their modules

Location:
palm/trunk/SOURCE
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/boundary_conds.f90

    r4182 r4268  
    2525! -----------------
    2626! $Id$
     27! Removing bulk cloud variables to respective module
     28!
     29! 4182 2019-08-22 15:20:23Z scharf
    2730! Corrected "Former revisions" section
    2831!
     
    6467    USE arrays_3d,                                                             &
    6568        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,  &
    66                dzu, nc_p, nr_p, pt, pt_init, pt_p, q,                          &
    67                q_p, qc_p, qr_p, s, s_p, sa, sa_p, u, u_init, u_m_l, u_m_n,     &
     69               dzu, pt, pt_init, pt_p, q,                                      &
     70               q_p, s, s_p, sa, sa_p, u, u_init, u_m_l, u_m_n,                 &
    6871               u_m_r, u_m_s, u_p, v, v_init, v_m_l, v_m_n, v_m_r, v_m_s, v_p,  &
    6972               w, w_p, w_m_l, w_m_n, w_m_r, w_m_s
    70 
    71     USE bulk_cloud_model_mod,                                                  &
    72         ONLY: bulk_cloud_model, microphysics_morrison, microphysics_seifert
    7373
    7474    USE chemistry_model_mod,                                                   &
     
    102102 
    103103    USE salsa_mod,                                                             &
    104         ONLY:  salsa_boundary_conds       
     104        ONLY:  salsa_boundary_conds
    105105
    106106    USE surface_mod,                                                           &
     
    136136       !$ACC PRESENT(bc_h, w_p)
    137137       DO  m = 1, bc_h(l)%ns
    138           i = bc_h(l)%i(m)           
     138          i = bc_h(l)%i(m)
    139139          j = bc_h(l)%j(m)
    140140          k = bc_h(l)%k(m)
     
    174174             !$OMP PARALLEL DO PRIVATE( i, j, k )
    175175             DO  m = 1, bc_h(l)%ns
    176                 i = bc_h(l)%i(m)           
     176                i = bc_h(l)%i(m)
    177177                j = bc_h(l)%j(m)
    178178                k = bc_h(l)%k(m)
     
    223223          !$OMP PARALLEL DO PRIVATE( i, j, k )
    224224          DO  m = 1, bc_h(l)%ns
    225              i = bc_h(l)%i(m)           
     225             i = bc_h(l)%i(m)
    226226             j = bc_h(l)%j(m)
    227227             k = bc_h(l)%k(m)
     
    253253             !$OMP PARALLEL DO PRIVATE( i, j, k )
    254254             DO  m = 1, bc_h(l)%ns
    255                 i = bc_h(l)%i(m)           
     255                i = bc_h(l)%i(m)
    256256                j = bc_h(l)%j(m)
    257257                k = bc_h(l)%k(m)
     
    259259             ENDDO
    260260          ENDDO
    261          
     261
    262262       ELSE
    263          
     263
    264264          DO  l = 0, 1
    265265             !$OMP PARALLEL DO PRIVATE( i, j, k )
    266266             DO  m = 1, bc_h(l)%ns
    267                 i = bc_h(l)%i(m)           
     267                i = bc_h(l)%i(m)
    268268                j = bc_h(l)%j(m)
    269269                k = bc_h(l)%k(m)
     
    279279          q_p(nzt+1,:,:) = q_p(nzt,:,:) + bc_q_t_val * dzu(nzt+1)
    280280       ENDIF
    281 
    282        IF ( bulk_cloud_model  .AND.  microphysics_morrison )  THEN
    283 !             
    284 !--       Surface conditions cloud water (Dirichlet)
    285 !--       Run loop over all non-natural and natural walls. Note, in wall-datatype
    286 !--       the k coordinate belongs to the atmospheric grid point, therefore, set
    287 !--       qr_p and nr_p at upward (k-1) and downward-facing (k+1) walls
    288           DO  l = 0, 1
    289           !$OMP PARALLEL DO PRIVATE( i, j, k )
    290              DO  m = 1, bc_h(l)%ns
    291                 i = bc_h(l)%i(m)           
    292                 j = bc_h(l)%j(m)
    293                 k = bc_h(l)%k(m)
    294                 qc_p(k+bc_h(l)%koff,j,i) = 0.0_wp
    295                 nc_p(k+bc_h(l)%koff,j,i) = 0.0_wp
    296              ENDDO
    297           ENDDO
    298 !
    299 !--       Top boundary condition for cloud water (Dirichlet)
    300           qc_p(nzt+1,:,:) = 0.0_wp
    301           nc_p(nzt+1,:,:) = 0.0_wp
    302            
    303        ENDIF
    304 
    305        IF ( bulk_cloud_model  .AND.  microphysics_seifert )  THEN
    306 !             
    307 !--       Surface conditions rain water (Dirichlet)
    308 !--       Run loop over all non-natural and natural walls. Note, in wall-datatype
    309 !--       the k coordinate belongs to the atmospheric grid point, therefore, set
    310 !--       qr_p and nr_p at upward (k-1) and downward-facing (k+1) walls
    311           DO  l = 0, 1
    312           !$OMP PARALLEL DO PRIVATE( i, j, k )
    313              DO  m = 1, bc_h(l)%ns
    314                 i = bc_h(l)%i(m)           
    315                 j = bc_h(l)%j(m)
    316                 k = bc_h(l)%k(m)
    317                 qr_p(k+bc_h(l)%koff,j,i) = 0.0_wp
    318                 nr_p(k+bc_h(l)%koff,j,i) = 0.0_wp
    319              ENDDO
    320           ENDDO
    321 !
    322 !--       Top boundary condition for rain water (Dirichlet)
    323           qr_p(nzt+1,:,:) = 0.0_wp
    324           nr_p(nzt+1,:,:) = 0.0_wp
    325            
    326        ENDIF
    327281    ENDIF
    328282!
     
    336290!--    s_p at k-1
    337291       IF ( ibc_s_b == 0 ) THEN
    338          
     292
    339293          DO  l = 0, 1
    340294             !$OMP PARALLEL DO PRIVATE( i, j, k )
    341295             DO  m = 1, bc_h(l)%ns
    342                 i = bc_h(l)%i(m)           
     296                i = bc_h(l)%i(m)
    343297                j = bc_h(l)%j(m)
    344298                k = bc_h(l)%k(m)
     
    346300             ENDDO
    347301          ENDDO
    348          
     302
    349303       ELSE
    350          
     304
    351305          DO  l = 0, 1
    352306             !$OMP PARALLEL DO PRIVATE( i, j, k )
    353307             DO  m = 1, bc_h(l)%ns
    354                 i = bc_h(l)%i(m)           
     308                i = bc_h(l)%i(m)
    355309                j = bc_h(l)%j(m)
    356310                k = bc_h(l)%k(m)
     
    411365       IF ( humidity )  THEN
    412366          q_p(:,nys-1,:) = q_p(:,nys,:)
    413           IF ( bulk_cloud_model  .AND.  microphysics_morrison )  THEN
    414              qc_p(:,nys-1,:) = qc_p(:,nys,:)
    415              nc_p(:,nys-1,:) = nc_p(:,nys,:)
    416           ENDIF
    417           IF ( bulk_cloud_model  .AND.  microphysics_seifert )  THEN
    418              qr_p(:,nys-1,:) = qr_p(:,nys,:)
    419              nr_p(:,nys-1,:) = nr_p(:,nys,:)
    420           ENDIF
    421367       ENDIF
    422368       IF ( passive_scalar )  s_p(:,nys-1,:) = s_p(:,nys,:)
     
    425371       IF ( humidity )  THEN
    426372          q_p(:,nyn+1,:) = q_p(:,nyn,:)
    427           IF ( bulk_cloud_model  .AND.  microphysics_morrison )  THEN
    428              qc_p(:,nyn+1,:) = qc_p(:,nyn,:)
    429              nc_p(:,nyn+1,:) = nc_p(:,nyn,:)
    430           ENDIF
    431           IF ( bulk_cloud_model  .AND.  microphysics_seifert )  THEN
    432              qr_p(:,nyn+1,:) = qr_p(:,nyn,:)
    433              nr_p(:,nyn+1,:) = nr_p(:,nyn,:)
    434           ENDIF
    435373       ENDIF
    436374       IF ( passive_scalar )  s_p(:,nyn+1,:) = s_p(:,nyn,:)
     
    439377       IF ( humidity )  THEN
    440378          q_p(:,:,nxl-1) = q_p(:,:,nxl)
    441           IF ( bulk_cloud_model  .AND.  microphysics_morrison )  THEN
    442              qc_p(:,:,nxl-1) = qc_p(:,:,nxl)
    443              nc_p(:,:,nxl-1) = nc_p(:,:,nxl)
    444           ENDIF
    445           IF ( bulk_cloud_model  .AND.  microphysics_seifert )  THEN
    446              qr_p(:,:,nxl-1) = qr_p(:,:,nxl)
    447              nr_p(:,:,nxl-1) = nr_p(:,:,nxl)
    448           ENDIF
    449379       ENDIF
    450380       IF ( passive_scalar )  s_p(:,:,nxl-1) = s_p(:,:,nxl)
     
    453383       IF ( humidity )  THEN
    454384          q_p(:,:,nxr+1) = q_p(:,:,nxr)
    455           IF ( bulk_cloud_model  .AND.  microphysics_morrison )  THEN
    456              qc_p(:,:,nxr+1) = qc_p(:,:,nxr)
    457              nc_p(:,:,nxr+1) = nc_p(:,:,nxr)
    458           ENDIF
    459           IF ( bulk_cloud_model  .AND.  microphysics_seifert )  THEN
    460              qr_p(:,:,nxr+1) = qr_p(:,:,nxr)
    461              nr_p(:,:,nxr+1) = nr_p(:,:,nxr)
    462           ENDIF
    463385       ENDIF
    464386       IF ( passive_scalar )  s_p(:,:,nxr+1) = s_p(:,:,nxr)
     
    479401          u_p(:,-1,:) = u(:,0,:)
    480402          v_p(:,0,:)  = v(:,1,:)
    481           w_p(:,-1,:) = w(:,0,:)         
     403          w_p(:,-1,:) = w(:,0,:)
    482404       ELSEIF ( .NOT. use_cmax )  THEN
    483405
     
    528450                IF ( denom /= 0.0_wp )  THEN
    529451                   c_w(k,i) = -c_max * ( w(k,0,i) - w_m_s(k,0,i) ) / ( denom * tsc(2) )
     452                   IF ( c_w(k,i) < 0.0_wp )  THEN
     453                      c_w(k,i) = 0.0_wp
     454                   ELSEIF ( c_w(k,i) > c_max )  THEN
     455                      c_w(k,i) = c_max
     456                   ENDIF
     457                ELSE
     458                   c_w(k,i) = c_max
     459                ENDIF
     460
     461                c_u_m_l(k) = c_u_m_l(k) + c_u(k,i)
     462                c_v_m_l(k) = c_v_m_l(k) + c_v(k,i)
     463                c_w_m_l(k) = c_w_m_l(k) + c_w(k,i)
     464
     465             ENDDO
     466          ENDDO
     467
     468#if defined( __parallel )
     469          IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
     470          CALL MPI_ALLREDUCE( c_u_m_l(nzb+1), c_u_m(nzb+1), nzt-nzb, MPI_REAL, &
     471                              MPI_SUM, comm1dx, ierr )   
     472          IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
     473          CALL MPI_ALLREDUCE( c_v_m_l(nzb+1), c_v_m(nzb+1), nzt-nzb, MPI_REAL, &
     474                              MPI_SUM, comm1dx, ierr ) 
     475          IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
     476          CALL MPI_ALLREDUCE( c_w_m_l(nzb+1), c_w_m(nzb+1), nzt-nzb, MPI_REAL, &
     477                              MPI_SUM, comm1dx, ierr ) 
     478#else
     479          c_u_m = c_u_m_l
     480          c_v_m = c_v_m_l
     481          c_w_m = c_w_m_l
     482#endif
     483
     484          c_u_m = c_u_m / (nx+1)
     485          c_v_m = c_v_m / (nx+1)
     486          c_w_m = c_w_m / (nx+1)
     487
     488!
     489!--       Save old timelevels for the next timestep
     490          IF ( intermediate_timestep_count == 1 )  THEN
     491             u_m_s(:,:,:) = u(:,0:1,:)
     492             v_m_s(:,:,:) = v(:,1:2,:)
     493             w_m_s(:,:,:) = w(:,0:1,:)
     494          ENDIF
     495
     496!
     497!--       Calculate the new velocities
     498          DO  k = nzb+1, nzt+1
     499             DO  i = nxlg, nxrg
     500                u_p(k,-1,i) = u(k,-1,i) - dt_3d * tsc(2) * c_u_m(k) *          &
     501                                       ( u(k,-1,i) - u(k,0,i) ) * ddy
     502
     503                v_p(k,0,i)  = v(k,0,i)  - dt_3d * tsc(2) * c_v_m(k) *          &
     504                                       ( v(k,0,i) - v(k,1,i) ) * ddy
     505
     506                w_p(k,-1,i) = w(k,-1,i) - dt_3d * tsc(2) * c_w_m(k) *          &
     507                                       ( w(k,-1,i) - w(k,0,i) ) * ddy
     508             ENDDO
     509          ENDDO
     510
     511!
     512!--       Bottom boundary at the outflow
     513          IF ( ibc_uv_b == 0 )  THEN
     514             u_p(nzb,-1,:) = 0.0_wp
     515             v_p(nzb,0,:)  = 0.0_wp 
     516          ELSE
     517             u_p(nzb,-1,:) =  u_p(nzb+1,-1,:)
     518             v_p(nzb,0,:)  =  v_p(nzb+1,0,:)
     519          ENDIF
     520          w_p(nzb,-1,:) = 0.0_wp
     521
     522!
     523!--       Top boundary at the outflow
     524          IF ( ibc_uv_t == 0 )  THEN
     525             u_p(nzt+1,-1,:) = u_init(nzt+1)
     526             v_p(nzt+1,0,:)  = v_init(nzt+1)
     527          ELSE
     528             u_p(nzt+1,-1,:) = u_p(nzt,-1,:)
     529             v_p(nzt+1,0,:)  = v_p(nzt,0,:)
     530          ENDIF
     531          w_p(nzt:nzt+1,-1,:) = 0.0_wp
     532
     533       ENDIF
     534
     535    ENDIF
     536
     537    IF ( bc_radiation_n )  THEN
     538
     539       IF ( use_cmax )  THEN
     540          u_p(:,ny+1,:) = u(:,ny,:)
     541          v_p(:,ny+1,:) = v(:,ny,:)
     542          w_p(:,ny+1,:) = w(:,ny,:)
     543       ELSEIF ( .NOT. use_cmax )  THEN
     544
     545          c_max = dy / dt_3d
     546
     547          c_u_m_l = 0.0_wp
     548          c_v_m_l = 0.0_wp
     549          c_w_m_l = 0.0_wp
     550
     551          c_u_m = 0.0_wp
     552          c_v_m = 0.0_wp
     553          c_w_m = 0.0_wp
     554
     555!
     556!--       Calculate the phase speeds for u, v, and w, first local and then
     557!--       average along the outflow boundary.
     558          DO  k = nzb+1, nzt+1
     559             DO  i = nxl, nxr
     560
     561                denom = u_m_n(k,ny,i) - u_m_n(k,ny-1,i)
     562
     563                IF ( denom /= 0.0_wp )  THEN
     564                   c_u(k,i) = -c_max * ( u(k,ny,i) - u_m_n(k,ny,i) ) / ( denom * tsc(2) )
     565                   IF ( c_u(k,i) < 0.0_wp )  THEN
     566                      c_u(k,i) = 0.0_wp
     567                   ELSEIF ( c_u(k,i) > c_max )  THEN
     568                      c_u(k,i) = c_max
     569                   ENDIF
     570                ELSE
     571                   c_u(k,i) = c_max
     572                ENDIF
     573
     574                denom = v_m_n(k,ny,i) - v_m_n(k,ny-1,i)
     575
     576                IF ( denom /= 0.0_wp )  THEN
     577                   c_v(k,i) = -c_max * ( v(k,ny,i) - v_m_n(k,ny,i) ) / ( denom * tsc(2) )
     578                   IF ( c_v(k,i) < 0.0_wp )  THEN
     579                      c_v(k,i) = 0.0_wp
     580                   ELSEIF ( c_v(k,i) > c_max )  THEN
     581                      c_v(k,i) = c_max
     582                   ENDIF
     583                ELSE
     584                   c_v(k,i) = c_max
     585                ENDIF
     586
     587                denom = w_m_n(k,ny,i) - w_m_n(k,ny-1,i)
     588
     589                IF ( denom /= 0.0_wp )  THEN
     590                   c_w(k,i) = -c_max * ( w(k,ny,i) - w_m_n(k,ny,i) ) / ( denom * tsc(2) )
    530591                   IF ( c_w(k,i) < 0.0_wp )  THEN
    531592                      c_w(k,i) = 0.0_wp
     
    567628!--       Save old timelevels for the next timestep
    568629          IF ( intermediate_timestep_count == 1 )  THEN
    569              u_m_s(:,:,:) = u(:,0:1,:)
    570              v_m_s(:,:,:) = v(:,1:2,:)
    571              w_m_s(:,:,:) = w(:,0:1,:)
    572           ENDIF
    573 
    574 !
    575 !--       Calculate the new velocities
    576           DO  k = nzb+1, nzt+1
    577              DO  i = nxlg, nxrg
    578                 u_p(k,-1,i) = u(k,-1,i) - dt_3d * tsc(2) * c_u_m(k) *          &
    579                                        ( u(k,-1,i) - u(k,0,i) ) * ddy
    580 
    581                 v_p(k,0,i)  = v(k,0,i)  - dt_3d * tsc(2) * c_v_m(k) *          &
    582                                        ( v(k,0,i) - v(k,1,i) ) * ddy
    583 
    584                 w_p(k,-1,i) = w(k,-1,i) - dt_3d * tsc(2) * c_w_m(k) *          &
    585                                        ( w(k,-1,i) - w(k,0,i) ) * ddy
    586              ENDDO
    587           ENDDO
    588 
    589 !
    590 !--       Bottom boundary at the outflow
    591           IF ( ibc_uv_b == 0 )  THEN
    592              u_p(nzb,-1,:) = 0.0_wp
    593              v_p(nzb,0,:)  = 0.0_wp 
    594           ELSE                   
    595              u_p(nzb,-1,:) =  u_p(nzb+1,-1,:)
    596              v_p(nzb,0,:)  =  v_p(nzb+1,0,:)
    597           ENDIF
    598           w_p(nzb,-1,:) = 0.0_wp
    599 
    600 !
    601 !--       Top boundary at the outflow
    602           IF ( ibc_uv_t == 0 )  THEN
    603              u_p(nzt+1,-1,:) = u_init(nzt+1)
    604              v_p(nzt+1,0,:)  = v_init(nzt+1)
    605           ELSE
    606              u_p(nzt+1,-1,:) = u_p(nzt,-1,:)
    607              v_p(nzt+1,0,:)  = v_p(nzt,0,:)
    608           ENDIF
    609           w_p(nzt:nzt+1,-1,:) = 0.0_wp
    610 
    611        ENDIF
    612 
    613     ENDIF
    614 
    615     IF ( bc_radiation_n )  THEN
    616 
    617        IF ( use_cmax )  THEN
    618           u_p(:,ny+1,:) = u(:,ny,:)
    619           v_p(:,ny+1,:) = v(:,ny,:)
    620           w_p(:,ny+1,:) = w(:,ny,:)         
    621        ELSEIF ( .NOT. use_cmax )  THEN
    622 
    623           c_max = dy / dt_3d
    624 
    625           c_u_m_l = 0.0_wp
    626           c_v_m_l = 0.0_wp
    627           c_w_m_l = 0.0_wp
    628 
    629           c_u_m = 0.0_wp
    630           c_v_m = 0.0_wp
    631           c_w_m = 0.0_wp
    632 
    633 !
    634 !--       Calculate the phase speeds for u, v, and w, first local and then
    635 !--       average along the outflow boundary.
    636           DO  k = nzb+1, nzt+1
    637              DO  i = nxl, nxr
    638 
    639                 denom = u_m_n(k,ny,i) - u_m_n(k,ny-1,i)
    640 
    641                 IF ( denom /= 0.0_wp )  THEN
    642                    c_u(k,i) = -c_max * ( u(k,ny,i) - u_m_n(k,ny,i) ) / ( denom * tsc(2) )
    643                    IF ( c_u(k,i) < 0.0_wp )  THEN
    644                       c_u(k,i) = 0.0_wp
    645                    ELSEIF ( c_u(k,i) > c_max )  THEN
    646                       c_u(k,i) = c_max
    647                    ENDIF
    648                 ELSE
    649                    c_u(k,i) = c_max
    650                 ENDIF
    651 
    652                 denom = v_m_n(k,ny,i) - v_m_n(k,ny-1,i)
    653 
    654                 IF ( denom /= 0.0_wp )  THEN
    655                    c_v(k,i) = -c_max * ( v(k,ny,i) - v_m_n(k,ny,i) ) / ( denom * tsc(2) )
    656                    IF ( c_v(k,i) < 0.0_wp )  THEN
    657                       c_v(k,i) = 0.0_wp
    658                    ELSEIF ( c_v(k,i) > c_max )  THEN
    659                       c_v(k,i) = c_max
    660                    ENDIF
    661                 ELSE
    662                    c_v(k,i) = c_max
    663                 ENDIF
    664 
    665                 denom = w_m_n(k,ny,i) - w_m_n(k,ny-1,i)
    666 
    667                 IF ( denom /= 0.0_wp )  THEN
    668                    c_w(k,i) = -c_max * ( w(k,ny,i) - w_m_n(k,ny,i) ) / ( denom * tsc(2) )
    669                    IF ( c_w(k,i) < 0.0_wp )  THEN
    670                       c_w(k,i) = 0.0_wp
    671                    ELSEIF ( c_w(k,i) > c_max )  THEN
    672                       c_w(k,i) = c_max
    673                    ENDIF
    674                 ELSE
    675                    c_w(k,i) = c_max
    676                 ENDIF
    677 
    678                 c_u_m_l(k) = c_u_m_l(k) + c_u(k,i)
    679                 c_v_m_l(k) = c_v_m_l(k) + c_v(k,i)
    680                 c_w_m_l(k) = c_w_m_l(k) + c_w(k,i)
    681 
    682              ENDDO
    683           ENDDO
    684 
    685 #if defined( __parallel )   
    686           IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
    687           CALL MPI_ALLREDUCE( c_u_m_l(nzb+1), c_u_m(nzb+1), nzt-nzb, MPI_REAL, &
    688                               MPI_SUM, comm1dx, ierr )   
    689           IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
    690           CALL MPI_ALLREDUCE( c_v_m_l(nzb+1), c_v_m(nzb+1), nzt-nzb, MPI_REAL, &
    691                               MPI_SUM, comm1dx, ierr ) 
    692           IF ( collective_wait )  CALL MPI_BARRIER( comm1dx, ierr )
    693           CALL MPI_ALLREDUCE( c_w_m_l(nzb+1), c_w_m(nzb+1), nzt-nzb, MPI_REAL, &
    694                               MPI_SUM, comm1dx, ierr ) 
    695 #else
    696           c_u_m = c_u_m_l
    697           c_v_m = c_v_m_l
    698           c_w_m = c_w_m_l
    699 #endif
    700 
    701           c_u_m = c_u_m / (nx+1)
    702           c_v_m = c_v_m / (nx+1)
    703           c_w_m = c_w_m / (nx+1)
    704 
    705 !
    706 !--       Save old timelevels for the next timestep
    707           IF ( intermediate_timestep_count == 1 )  THEN
    708630                u_m_n(:,:,:) = u(:,ny-1:ny,:)
    709631                v_m_n(:,:,:) = v(:,ny-1:ny,:)
     
    731653             u_p(nzb,ny+1,:) = 0.0_wp
    732654             v_p(nzb,ny+1,:) = 0.0_wp   
    733           ELSE                   
     655          ELSE
    734656             u_p(nzb,ny+1,:) =  u_p(nzb+1,ny+1,:)
    735657             v_p(nzb,ny+1,:) =  v_p(nzb+1,ny+1,:)
     
    757679          u_p(:,:,0)  = u(:,:,1)
    758680          v_p(:,:,-1) = v(:,:,0)
    759           w_p(:,:,-1) = w(:,:,0)         
     681          w_p(:,:,-1) = w(:,:,0)
    760682       ELSEIF ( .NOT. use_cmax )  THEN
    761683
     
    870792             u_p(nzb,:,0)  = 0.0_wp
    871793             v_p(nzb,:,-1) = 0.0_wp
    872           ELSE                   
     794          ELSE
    873795             u_p(nzb,:,0)  =  u_p(nzb+1,:,0)
    874796             v_p(nzb,:,-1) =  v_p(nzb+1,:,-1)
     
    896818          u_p(:,:,nx+1) = u(:,:,nx)
    897819          v_p(:,:,nx+1) = v(:,:,nx)
    898           w_p(:,:,nx+1) = w(:,:,nx)         
     820          w_p(:,:,nx+1) = w(:,:,nx)
    899821       ELSEIF ( .NOT. use_cmax )  THEN
    900822
     
    1009931             u_p(nzb,:,nx+1) = 0.0_wp
    1010932             v_p(nzb,:,nx+1) = 0.0_wp
    1011           ELSE                   
     933          ELSE
    1012934             u_p(nzb,:,nx+1) =  u_p(nzb+1,:,nx+1)
    1013935             v_p(nzb,:,nx+1) =  v_p(nzb+1,:,nx+1)
  • palm/trunk/SOURCE/bulk_cloud_model_mod.f90

    r4182 r4268  
    2525! -----------------
    2626! $Id$
     27! Introducing bcm_boundary_conditions
     28!
     29! 4182 2019-08-22 15:20:23Z scharf
    2730! Corrected "Former revisions" section
    2831!
     
    114117               bc_radiation_n,                                                 &
    115118               bc_radiation_r,                                                 &
    116                bc_radiation_s,                                                 &                                                               
     119               bc_radiation_s,                                                 &
    117120               debug_output,                                                   &
    118121               dt_3d, dt_do2d_xy, intermediate_timestep_count,                 &
     
    247250           bcm_exchange_horiz, &
    248251           bcm_prognostic_equations, &
     252           bcm_boundary_conditions, &
    249253           bcm_3d_data_averaging, &
    250254           bcm_data_output_2d, &
     
    313317    INTERFACE bcm_exchange_horiz
    314318       MODULE PROCEDURE bcm_exchange_horiz
    315     END INTERFACE bcm_exchange_horiz   
     319    END INTERFACE bcm_exchange_horiz
    316320
    317321    INTERFACE bcm_prognostic_equations
     
    319323       MODULE PROCEDURE bcm_prognostic_equations_ij
    320324    END INTERFACE bcm_prognostic_equations
     325
     326    INTERFACE bcm_boundary_conditions
     327       MODULE PROCEDURE bcm_boundary_conditions
     328    END INTERFACE bcm_boundary_conditions
    321329
    322330    INTERFACE bcm_swap_timelevel
     
    20142022
    20152023!------------------------------------------------------------------------------!
     2024! Description: Boundary conditions of the bulk cloud module variables
     2025!------------------------------------------------------------------------------!
     2026    SUBROUTINE bcm_boundary_conditions
     2027
     2028       IMPLICIT NONE
     2029
     2030       INTEGER(iwp) ::  i !<
     2031       INTEGER(iwp) ::  j !<
     2032       INTEGER(iwp) ::  k !<
     2033       INTEGER(iwp) ::  m !<
     2034       INTEGER(iwp) ::  l !<
     2035
     2036       IF ( microphysics_morrison )  THEN
     2037!
     2038!--       Surface conditions cloud water (Dirichlet)
     2039!--       Run loop over all non-natural and natural walls. Note, in wall-datatype
     2040!--       the k coordinate belongs to the atmospheric grid point, therefore, set
     2041!--       qr_p and nr_p at upward (k-1) and downward-facing (k+1) walls
     2042          DO  l = 0, 1
     2043          !$OMP PARALLEL DO PRIVATE( i, j, k )
     2044             DO  m = 1, bc_h(l)%ns
     2045                i = bc_h(l)%i(m)
     2046                j = bc_h(l)%j(m)
     2047                k = bc_h(l)%k(m)
     2048                qc_p(k+bc_h(l)%koff,j,i) = 0.0_wp
     2049                nc_p(k+bc_h(l)%koff,j,i) = 0.0_wp
     2050             ENDDO
     2051          ENDDO
     2052!
     2053!--       Top boundary condition for cloud water (Dirichlet)
     2054          qc_p(nzt+1,:,:) = 0.0_wp
     2055          nc_p(nzt+1,:,:) = 0.0_wp
     2056
     2057       ENDIF
     2058
     2059       IF ( microphysics_seifert )  THEN
     2060!
     2061!--       Surface conditions rain water (Dirichlet)
     2062!--       Run loop over all non-natural and natural walls. Note, in wall-datatype
     2063!--       the k coordinate belongs to the atmospheric grid point, therefore, set
     2064!--       qr_p and nr_p at upward (k-1) and downward-facing (k+1) walls
     2065          DO  l = 0, 1
     2066          !$OMP PARALLEL DO PRIVATE( i, j, k )
     2067             DO  m = 1, bc_h(l)%ns
     2068                i = bc_h(l)%i(m)
     2069                j = bc_h(l)%j(m)
     2070                k = bc_h(l)%k(m)
     2071                qr_p(k+bc_h(l)%koff,j,i) = 0.0_wp
     2072                nr_p(k+bc_h(l)%koff,j,i) = 0.0_wp
     2073             ENDDO
     2074          ENDDO
     2075!
     2076!--       Top boundary condition for rain water (Dirichlet)
     2077          qr_p(nzt+1,:,:) = 0.0_wp
     2078          nr_p(nzt+1,:,:) = 0.0_wp
     2079
     2080       ENDIF
     2081
     2082!
     2083!--    Lateral boundary conditions for scalar quantities at the outflow.
     2084!--    Lateral oundary conditions for TKE and dissipation are set
     2085!--    in tcm_boundary_conds.
     2086       IF ( bc_radiation_s )  THEN
     2087          IF ( microphysics_morrison )  THEN
     2088             qc_p(:,nys-1,:) = qc_p(:,nys,:)
     2089             nc_p(:,nys-1,:) = nc_p(:,nys,:)
     2090          ENDIF
     2091          IF ( microphysics_seifert )  THEN
     2092             qr_p(:,nys-1,:) = qr_p(:,nys,:)
     2093             nr_p(:,nys-1,:) = nr_p(:,nys,:)
     2094          ENDIF
     2095       ELSEIF ( bc_radiation_n )  THEN
     2096          IF ( microphysics_morrison )  THEN
     2097             qc_p(:,nyn+1,:) = qc_p(:,nyn,:)
     2098             nc_p(:,nyn+1,:) = nc_p(:,nyn,:)
     2099          ENDIF
     2100          IF ( microphysics_seifert )  THEN
     2101             qr_p(:,nyn+1,:) = qr_p(:,nyn,:)
     2102             nr_p(:,nyn+1,:) = nr_p(:,nyn,:)
     2103          ENDIF
     2104       ELSEIF ( bc_radiation_l )  THEN
     2105          IF ( microphysics_morrison )  THEN
     2106             qc_p(:,:,nxl-1) = qc_p(:,:,nxl)
     2107             nc_p(:,:,nxl-1) = nc_p(:,:,nxl)
     2108          ENDIF
     2109          IF ( microphysics_seifert )  THEN
     2110             qr_p(:,:,nxl-1) = qr_p(:,:,nxl)
     2111             nr_p(:,:,nxl-1) = nr_p(:,:,nxl)
     2112          ENDIF
     2113       ELSEIF ( bc_radiation_r )  THEN
     2114          IF ( microphysics_morrison )  THEN
     2115             qc_p(:,:,nxr+1) = qc_p(:,:,nxr)
     2116             nc_p(:,:,nxr+1) = nc_p(:,:,nxr)
     2117          ENDIF
     2118          IF ( microphysics_seifert )  THEN
     2119             qr_p(:,:,nxr+1) = qr_p(:,:,nxr)
     2120             nr_p(:,:,nxr+1) = nr_p(:,:,nxr)
     2121          ENDIF
     2122       ENDIF
     2123
     2124    END SUBROUTINE bcm_boundary_conditions
     2125
     2126!------------------------------------------------------------------------------!
    20162127!
    20172128! Description:
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r4230 r4268  
    2727! -----------------
    2828! $Id$
     29! Moving module specific boundary conditions from time_integration to module
     30!
     31! 4230 2019-09-11 13:58:14Z suehring
    2932! Bugfix, initialize mean profiles also in restart runs. Also initialize
    3033! array used for Runge-Kutta tendecies in restart runs. 
     
    380383    END INTERFACE chem_boundary_conds
    381384
     385    INTERFACE chem_boundary_conditions
     386       MODULE PROCEDURE chem_boundary_conditions
     387    END INTERFACE chem_boundary_conditions
     388
    382389    INTERFACE chem_check_data_output
    383390       MODULE PROCEDURE chem_check_data_output
     
    537544
    538545
    539     PUBLIC chem_3d_data_averaging, chem_boundary_conds,                       &
     546    PUBLIC chem_3d_data_averaging, chem_boundary_conds, chem_boundary_conditions, &
    540547            chem_boundary_conds_decycle, chem_check_data_output,              &
    541548         chem_check_data_output_pr, chem_check_parameters,                    &
     
    799806 END SUBROUTINE chem_boundary_conds
    800807
     808!------------------------------------------------------------------------------!
     809! Description:
     810! ------------
     811!> Subroutine for boundary conditions
     812!------------------------------------------------------------------------------!
     813 SUBROUTINE chem_boundary_conditions
     814
     815    IMPLICIT NONE
     816
     817    INTEGER(iwp) ::  lsp             !<
     818    INTEGER(iwp) ::  lsp_usr         !<
     819
     820!
     821!--       Boundary conditions for prognostic quantitites of other modules:
     822!--       Here, only decycling is carried out
     823
     824          DO  lsp = 1, nvar
     825             lsp_usr = 1
     826             DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
     827                IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) )  THEN
     828                   CALL chem_boundary_conds( chem_species(lsp)%conc_p,                          &
     829                                             chem_species(lsp)%conc_pr_init )
     830                ENDIF
     831                lsp_usr = lsp_usr + 1
     832             ENDDO
     833          ENDDO
     834
     835
     836 END SUBROUTINE chem_boundary_conditions
    801837
    802838!------------------------------------------------------------------------------!
  • palm/trunk/SOURCE/module_interface.f90

    r4182 r4268  
    2525! -----------------
    2626! $Id$
     27! Introduction of module_interface_boundary_conditions
     28!
     29! 4182 2019-08-22 15:20:23Z scharf
    2730! Corrected "Former revisions" section
    2831!
     
    245248               bcm_exchange_horiz,                                             &
    246249               bcm_prognostic_equations,                                       &
     250               bcm_boundary_conditions,                                        &
    247251               bcm_swap_timelevel,                                             &
    248252               bcm_3d_data_averaging,                                          &
     
    266270              chem_non_advective_processes,                                    &
    267271              chem_prognostic_equations,                                       &
     272              chem_boundary_conditions,                                        &
    268273              chem_swap_timelevel,                                             &
    269274              chem_3d_data_averaging,                                          &
     
    418423               salsa_exchange_horiz_bounds,                                    &
    419424               salsa_prognostic_equations,                                     &
     425               salsa_boundary_conditions,                                      &
    420426               salsa_swap_timelevel,                                           &
    421427               salsa_3d_data_averaging,                                        &
     
    520526       module_interface_exchange_horiz,                                        &
    521527       module_interface_prognostic_equations,                                  &
     528       module_interface_boundary_conditions,                                   &
    522529       module_interface_swap_timelevel,                                        &
    523530       module_interface_3d_data_averaging,                                     &
     
    598605       MODULE PROCEDURE module_interface_swap_timelevel
    599606    END INTERFACE module_interface_swap_timelevel
     607
     608    INTERFACE module_interface_boundary_conditions
     609       MODULE PROCEDURE module_interface_boundary_conditions
     610    END INTERFACE module_interface_boundary_conditions
    600611
    601612    INTERFACE module_interface_3d_data_averaging
     
    12731284 END SUBROUTINE module_interface_prognostic_equations_ij
    12741285
     1286!------------------------------------------------------------------------------!
     1287! Description:
     1288! ------------
     1289!> Compute module-specific boundary conditions
     1290!------------------------------------------------------------------------------!
     1291 SUBROUTINE module_interface_boundary_conditions
     1292
     1293
     1294    IF ( debug_output_timestep )  CALL debug_message( 'module-specific boundary_conditions', 'start' )
     1295
     1296    IF ( bulk_cloud_model    )  CALL bcm_boundary_conditions
     1297    IF ( air_chemistry       )  CALL chem_boundary_conditions
     1298    IF ( salsa               )  CALL salsa_boundary_conditions
     1299
     1300    IF ( debug_output_timestep )  CALL debug_message( 'module-specific boundary_conditions', 'end' )
     1301
     1302
     1303 END SUBROUTINE module_interface_boundary_conditions
    12751304
    12761305!------------------------------------------------------------------------------!
  • palm/trunk/SOURCE/salsa_mod.f90

    r4256 r4268  
    2626! -----------------
    2727! $Id$
     28! Moving module specific boundary conditions from time_integration to module
     29!
     30! 4256 2019-10-07 10:08:52Z monakurppa
    2831! Document previous changes: use global variables nx, ny and nz in salsa_header
    2932!
     
    773776    END INTERFACE salsa_boundary_conds
    774777
     778    INTERFACE salsa_boundary_conditions
     779       MODULE PROCEDURE salsa_boundary_conditions
     780    END INTERFACE salsa_boundary_conditions
     781
    775782    INTERFACE salsa_check_data_output
    776783       MODULE PROCEDURE salsa_check_data_output
     
    866873!
    867874!-- Public functions:
    868     PUBLIC salsa_boundary_conds, salsa_check_data_output, salsa_check_parameters,                 &
     875    PUBLIC salsa_boundary_conds, salsa_check_data_output, salsa_check_parameters, salsa_boundary_conditions, &
    869876           salsa_3d_data_averaging, salsa_data_output_2d, salsa_data_output_3d,                    &
    870877           salsa_data_output_mask, salsa_define_netcdf_grid, salsa_diagnostics, salsa_driver,      &
     
    79547961 END SUBROUTINE salsa_tendency
    79557962
     7963
     7964!------------------------------------------------------------------------------!
     7965! Description:
     7966! ------------
     7967!> Boundary conditions for prognostic variables in SALSA from module interface
     7968!------------------------------------------------------------------------------!
     7969 SUBROUTINE salsa_boundary_conditions
     7970
     7971    IMPLICIT NONE
     7972
     7973    INTEGER(iwp) ::  ib              !< index for aerosol size bins
     7974    INTEGER(iwp) ::  ic              !< index for aerosol mass bins
     7975    INTEGER(iwp) ::  icc             !< additional index for aerosol mass bins
     7976    INTEGER(iwp) ::  ig              !< index for salsa gases
     7977
     7978!
     7979!-- Boundary conditions for prognostic quantitites of other modules:
     7980!-- Here, only decycling is carried out
     7981    IF ( time_since_reference_point >= skip_time_do_salsa )  THEN
     7982
     7983       DO  ib = 1, nbins_aerosol
     7984          CALL salsa_boundary_conds( aerosol_number(ib)%conc_p, aerosol_number(ib)%init )
     7985          DO  ic = 1, ncomponents_mass
     7986             icc = ( ic - 1 ) * nbins_aerosol + ib
     7987             CALL salsa_boundary_conds( aerosol_mass(icc)%conc_p, aerosol_mass(icc)%init )
     7988          ENDDO
     7989       ENDDO
     7990       IF ( .NOT. salsa_gases_from_chem )  THEN
     7991          DO  ig = 1, ngases_salsa
     7992             CALL salsa_boundary_conds( salsa_gas(ig)%conc_p, salsa_gas(ig)%init )
     7993          ENDDO
     7994       ENDIF
     7995
     7996    ENDIF
     7997
     7998 END SUBROUTINE salsa_boundary_conditions
     7999
    79568000!------------------------------------------------------------------------------!
    79578001! Description:
  • palm/trunk/SOURCE/time_integration.f90

    r4227 r4268  
    2525! -----------------
    2626! $Id$
     27! Removing module specific boundary conditions an put them into their modules
     28!
     29! 4227 2019-09-10 18:04:34Z gronemeier
    2730! implement new palm_date_time_mod
    2831!
     
    254257
    255258    USE module_interface,                                                                          &
    256         ONLY:  module_interface_actions, module_interface_swap_timelevel
     259        ONLY:  module_interface_actions, module_interface_swap_timelevel,                          &
     260               module_interface_boundary_conditions
    257261
    258262    USE multi_agent_system_mod,                                                                    &
     
    583587!--    Execute all other module actions routunes
    584588       CALL module_interface_actions( 'before_timestep' )
    585        
     589
    586590!
    587591!--    Start of intermediate step loop
     
    750754!--       velocities at the outflow in case of a non-cyclic lateral wall)
    751755          CALL boundary_conds
    752 
    753 !
    754 !--       Boundary conditions for prognostic quantitites of other modules:
    755 !--       Here, only decycling is carried out
    756           IF ( air_chemistry )  THEN
    757 
    758              DO  lsp = 1, nvar
    759                 lsp_usr = 1
    760                 DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
    761                    IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) )  THEN
    762                       CALL chem_boundary_conds( chem_species(lsp)%conc_p,                          &
    763                                                 chem_species(lsp)%conc_pr_init )
    764                    ENDIF
    765                    lsp_usr = lsp_usr + 1
    766                 ENDDO
    767              ENDDO
    768 
    769           ENDIF
    770 
    771           IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
    772 
    773              DO  ib = 1, nbins_aerosol
    774                 CALL salsa_boundary_conds( aerosol_number(ib)%conc_p, aerosol_number(ib)%init )
    775                 DO  ic = 1, ncomponents_mass
    776                    icc = ( ic - 1 ) * nbins_aerosol + ib
    777                    CALL salsa_boundary_conds( aerosol_mass(icc)%conc_p, aerosol_mass(icc)%init )
    778                 ENDDO
    779              ENDDO
    780              IF ( .NOT. salsa_gases_from_chem )  THEN
    781                 DO  ig = 1, ngases_salsa
    782                    CALL salsa_boundary_conds( salsa_gas(ig)%conc_p, salsa_gas(ig)%init )
    783                 ENDDO
    784              ENDIF
    785 
    786           ENDIF
    787 
     756!
     757!--       Boundary conditions for module-specific variables
     758          CALL module_interface_boundary_conditions
    788759!
    789760!--       Incrementing timestep counter
     
    1009980
    1010981             ELSE
    1011 !               
     982!
    1012983!--             Mass (volume) flux correction to ensure global mass conservation for child domains.
    1013984                IF ( child_domain )  THEN
     
    1018989                   ENDIF
    1019990                ENDIF
    1020                
     991
    1021992                CALL pres
    1022993
     
    10841055                CALL lsm_energy_balance( .FALSE., 3 )
    10851056                CALL lsm_soil_model( .FALSE., 3, .TRUE. )
    1086                
     1057
    10871058!
    10881059!--             At the end, set boundary conditons for potential temperature
     
    10911062                CALL lsm_boundary_condition
    10921063
    1093                
     1064
    10941065                CALL cpu_log( log_point(54), 'land_surface', 'stop' )
    10951066             ENDIF
     
    10991070             IF (urban_surface) THEN
    11001071                CALL cpu_log( log_point(74), 'urban_surface', 'start' )
    1101                
     1072
    11021073                CALL usm_surface_energy_balance( .FALSE. )
    11031074                IF ( usm_material_model )  THEN
Note: See TracChangeset for help on using the changeset viewer.