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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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:
Note: See TracChangeset for help on using the changeset viewer.