Ignore:
Timestamp:
Dec 14, 2017 5:12:51 PM (7 years ago)
Author:
kanani
Message:

Merge of branch palm4u into trunk

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/boundary_conds.f90

    r2569 r2696  
    11!> @file boundary_conds.f90
    22!------------------------------------------------------------------------------!
    3 ! This file is part of PALM.
     3! This file is part of the PALM model system.
    44!
    55! PALM is free software: you can redistribute it and/or modify it under the
     
    2525! -----------------
    2626! $Id$
     27! Adjust boundary conditions for e and diss in case of TKE-e closure (TG)
     28! Implementation of chemistry module (FK)
     29!
     30! 2569 2017-10-20 11:54:42Z kanani
    2731! Removed redundant code for ibc_s_b=1 and ibc_q_b=1
    2832!
     
    166170    USE arrays_3d,                                                             &
    167171        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,  &
    168                dzu, e_p, nc_p, nr_p, pt, pt_p, q, q_p, qc_p, qr_p, s, s_p, sa, &
    169                sa_p, u, ug, u_init, u_m_l, u_m_n, u_m_r, u_m_s, u_p,           &
     172               diss_p, dzu, e_p, nc_p, nr_p, pt, pt_p, q, q_p, qc_p, qr_p, s, &
     173               s_p, sa, sa_p, u, ug, u_init, u_m_l, u_m_n, u_m_r, u_m_s, u_p,  &
    170174               v, vg, v_init, v_m_l, v_m_n, v_m_r, v_m_s, v_p,                 &
    171175               w, w_p, w_m_l, w_m_n, w_m_r, w_m_s, pt_init
    172                
     176
     177#if defined( __chem )
     178    USE chemistry_model_mod,                                                   &
     179        ONLY:  chem_boundary_conds
     180#endif
     181             
    173182    USE control_parameters,                                                    &
    174         ONLY:  bc_pt_t_val, bc_q_t_val, bc_s_t_val, constant_diffusion,        &
    175                cloud_physics, coupling_mode, dt_3d, humidity,                  &
     183        ONLY:  air_chemistry, bc_pt_t_val, bc_q_t_val, bc_s_t_val,             &
     184               constant_diffusion, cloud_physics, coupling_mode, dt_3d,        &
     185               force_bound_l, force_bound_s, forcing, humidity,                &
    176186               ibc_pt_b, ibc_pt_t, ibc_q_b, ibc_q_t, ibc_s_b, ibc_s_t,         &
    177187               ibc_sa_t, ibc_uv_b, ibc_uv_t, inflow_l, inflow_n, inflow_r,     &
     
    179189               microphysics_morrison, microphysics_seifert, nest_domain,       &
    180190               nest_bound_l, nest_bound_s, nudging, ocean, outflow_l,          &
    181                outflow_n, outflow_r, outflow_s, passive_scalar, tsc, use_cmax
     191               outflow_n, outflow_r, outflow_s, passive_scalar, rans_tke_e,    &
     192               tsc, use_cmax
    182193
    183194    USE grid_variables,                                                        &
     
    309320    IF ( .NOT. constant_diffusion )  THEN
    310321
    311        DO  l = 0, 1
    312 !
    313 !--       Set kb, for upward-facing surfaces value at topography top (k-1) is set,
    314 !--       for downward-facing surfaces at topography bottom (k+1).
    315           kb = MERGE( -1, 1, l == 0 )
    316           !$OMP PARALLEL DO PRIVATE( i, j, k )
    317           DO  m = 1, bc_h(l)%ns
    318              i = bc_h(l)%i(m)           
    319              j = bc_h(l)%j(m)
    320              k = bc_h(l)%k(m)
    321              e_p(k+kb,j,i) = e_p(k,j,i)
    322           ENDDO
    323        ENDDO
     322       IF ( .NOT. rans_tke_e )  THEN
     323          DO  l = 0, 1
     324!
     325!--         Set kb, for upward-facing surfaces value at topography top (k-1) is set,
     326!--         for downward-facing surfaces at topography bottom (k+1).
     327             kb = MERGE( -1, 1, l == 0 )
     328             !$OMP PARALLEL DO PRIVATE( i, j, k )
     329             DO  m = 1, bc_h(l)%ns
     330                i = bc_h(l)%i(m)           
     331                j = bc_h(l)%j(m)
     332                k = bc_h(l)%k(m)
     333                e_p(k+kb,j,i) = e_p(k,j,i)
     334             ENDDO
     335          ENDDO
     336       ENDIF
    324337
    325338       IF ( .NOT. nest_domain )  THEN
    326339          e_p(nzt+1,:,:) = e_p(nzt,:,:)
    327340       ENDIF
     341    ENDIF
     342
     343!
     344!-- Boundary conditions for TKE dissipation rate
     345    IF ( rans_tke_e .AND. .NOT. nest_domain )  THEN
     346       diss_p(nzt+1,:,:) = diss_p(nzt,:,:)
    328347    ENDIF
    329348
     
    500519
    501520    ENDIF   
     521!
     522!-- Top/bottom boundary conditions for chemical species
     523#if defined( __chem )
     524    IF ( air_chemistry )  CALL chem_boundary_conds( 'set_bc_bottomtop' )
     525#endif
    502526!
    503527!-- In case of inflow or nest boundary at the south boundary the boundary for v
     
    523547!-- in case of nest boundaries. This must not be done in case of vertical nesting
    524548!-- mode as in that case the lateral boundaries are actually cyclic.
    525     IF ( nesting_mode /= 'vertical' )  THEN
    526        IF ( nest_bound_s )  THEN
     549    IF ( nesting_mode /= 'vertical'  .OR.  forcing )  THEN
     550       IF ( nest_bound_s  .OR.  force_bound_s )  THEN
    527551          v_p(:,nys,:) = v_p(:,nys-1,:)
    528552       ENDIF
    529        IF ( nest_bound_l )  THEN
     553       IF ( nest_bound_l  .OR.  force_bound_l )  THEN
    530554          u_p(:,:,nxl) = u_p(:,:,nxl-1)
    531555       ENDIF
     
    537561       pt_p(:,nys-1,:)     = pt_p(:,nys,:)
    538562       IF ( .NOT. constant_diffusion )  e_p(:,nys-1,:) = e_p(:,nys,:)
     563       IF ( rans_tke_e )  diss_p(:,nys-1,:) = diss_p(:,nys,:)
    539564       IF ( humidity )  THEN
    540565          q_p(:,nys-1,:) = q_p(:,nys,:)
     
    551576    ELSEIF ( outflow_n )  THEN
    552577       pt_p(:,nyn+1,:)     = pt_p(:,nyn,:)
    553        IF ( .NOT. constant_diffusion     )  e_p(:,nyn+1,:) = e_p(:,nyn,:)
     578       IF ( .NOT. constant_diffusion )  e_p(:,nyn+1,:) = e_p(:,nyn,:)
     579       IF ( rans_tke_e )  diss_p(:,nyn+1,:) = diss_p(:,nyn,:)
    554580       IF ( humidity )  THEN
    555581          q_p(:,nyn+1,:) = q_p(:,nyn,:)
     
    566592    ELSEIF ( outflow_l )  THEN
    567593       pt_p(:,:,nxl-1)     = pt_p(:,:,nxl)
    568        IF ( .NOT. constant_diffusion     )  e_p(:,:,nxl-1) = e_p(:,:,nxl)
     594       IF ( .NOT. constant_diffusion )  e_p(:,:,nxl-1) = e_p(:,:,nxl)
     595       IF ( rans_tke_e )  diss_p(:,:,nxl-1) = diss_p(:,:,nxl)
    569596       IF ( humidity )  THEN
    570597          q_p(:,:,nxl-1) = q_p(:,:,nxl)
     
    581608    ELSEIF ( outflow_r )  THEN
    582609       pt_p(:,:,nxr+1)     = pt_p(:,:,nxr)
    583        IF ( .NOT. constant_diffusion     )  e_p(:,:,nxr+1) = e_p(:,:,nxr)
     610       IF ( .NOT. constant_diffusion )  e_p(:,:,nxr+1) = e_p(:,:,nxr)
     611       IF ( rans_tke_e )  diss_p(:,:,nxr+1) = diss_p(:,:,nxr)
    584612       IF ( humidity )  THEN
    585613          q_p(:,:,nxr+1) = q_p(:,:,nxr)
     
    595623       IF ( passive_scalar )  s_p(:,:,nxr+1) = s_p(:,:,nxr)
    596624    ENDIF
     625
     626!
     627!-- Lateral boundary conditions for chemical species
     628#if defined( __chem )
     629    IF ( air_chemistry )  CALL chem_boundary_conds( 'set_bc_lateral' )   
     630#endif
     631
    597632
    598633!
Note: See TracChangeset for help on using the changeset viewer.