Ignore:
Timestamp:
Feb 25, 2016 12:31:13 PM (8 years ago)
Author:
hellstea
Message:

Introduction of nested domain system

File:
1 edited

Legend:

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

    r1744 r1762  
    1919! Current revisions:
    2020! -----------------
    21 !
     21! Introduction of nested domain feature
    2222!
    2323! Former revisions:
     
    134134               ibc_pt_b, ibc_pt_t, ibc_q_b, ibc_q_t, ibc_sa_t, ibc_uv_b,       &
    135135               ibc_uv_t, icloud_scheme, inflow_l, inflow_n, inflow_r, inflow_s,&
    136                intermediate_timestep_count, large_scale_forcing, ocean,        &
     136               intermediate_timestep_count, large_scale_forcing, nest_domain,  &
     137               nest_bound_l, nest_bound_s, nudging, ocean,                     &
    137138               outflow_l, outflow_n, outflow_r, outflow_s, passive_scalar,     &
    138                precipitation, tsc, use_cmax, &
    139                nudging
     139               precipitation, tsc, use_cmax
    140140
    141141    USE grid_variables,                                                        &
     
    179179
    180180!
    181 !-- Top boundary
     181!-- Top boundary. A nested domain ( ibc_uv_t = 3 ) does not require settings.
    182182    IF ( ibc_uv_t == 0 )  THEN
    183183       !$acc kernels present( u_init, u_p, v_init, v_p )
     
    185185        v_p(nzt+1,:,:) = v_init(nzt+1)
    186186       !$acc end kernels
    187     ELSE
     187    ELSEIF ( ibc_uv_t == 1 )  THEN
    188188       !$acc kernels present( u_p, v_p )
    189189        u_p(nzt+1,:,:) = u_p(nzt,:,:)
     
    191191       !$acc end kernels
    192192    ENDIF
    193     !$acc kernels present( w_p )
    194     w_p(nzt:nzt+1,:,:) = 0.0_wp  ! nzt is not a prognostic level (but cf. pres)
    195     !$acc end kernels
     193
     194    IF ( .NOT. nest_domain )  THEN
     195       !$acc kernels present( w_p )
     196       w_p(nzt:nzt+1,:,:) = 0.0_wp  ! nzt is not a prognostic level (but cf. pres)
     197       !$acc end kernels
     198    ENDIF
    196199
    197200!
     
    255258          ENDDO
    256259       ENDDO
    257        e_p(nzt+1,:,:) = e_p(nzt,:,:)
     260       IF ( .NOT. nest_domain )  THEN
     261          e_p(nzt+1,:,:) = e_p(nzt,:,:)
     262       ENDIF
    258263       !$acc end kernels
    259264    ENDIF
     
    325330    ENDIF
    326331!
    327 !-- In case of inflow at the south boundary the boundary for v is at nys
    328 !-- and in case of inflow at the left boundary the boundary for u is at nxl.
    329 !-- Since in prognostic_equations (cache optimized version) these levels are
    330 !-- handled as a prognostic level, boundary values have to be restored here.
     332!-- In case of inflow or nest boundary at the south boundary the boundary for v
     333!-- is at nys and in case of inflow or nest boundary at the left boundary the
     334!-- boundary for u is at nxl. Since in prognostic_equations (cache optimized
     335!-- version) these levels are handled as a prognostic level, boundary values
     336!-- have to be restored here.
    331337!-- For the SGS-TKE, Neumann boundary conditions are used at the inflow.
    332338    IF ( inflow_s )  THEN
     
    340346    ELSEIF ( inflow_r )  THEN
    341347       IF ( .NOT. constant_diffusion ) e_p(:,:,nxr+1) = e_p(:,:,nxr)
     348    ENDIF
     349
     350!
     351!-- The same restoration for u at i=nxl and v at j=nys as above must be made
     352!-- in case of nest boundaries. Note however, that the above ELSEIF-structure is
     353!-- not appropriate here as there may be more than one nest boundary on a
     354!-- PE-domain. Furthermore Neumann conditions for SGS-TKE are not required here.
     355    IF ( nest_bound_s )  THEN
     356       v_p(:,nys,:) = v_p(:,nys-1,:)
     357    ENDIF
     358    IF ( nest_bound_l )  THEN
     359       u_p(:,:,nxl) = u_p(:,:,nxl-1)
    342360    ENDIF
    343361
Note: See TracChangeset for help on using the changeset viewer.