Ignore:
Timestamp:
Oct 23, 2019 3:18:57 PM (5 years ago)
Author:
schwenkel
Message:

further modularization of boundary conditions: moving boundary conditions to their modules

File:
1 edited

Legend:

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

    r4196 r4272  
    2525! -----------------
    2626! $Id$
     27! Further modularization of boundary conditions: moved boundary conditions to
     28! respective modules
     29!
     30! 4196 2019-08-29 11:02:06Z gronemeier
    2731! Consider rotation of model domain for calculating the Stokes drift
    2832!
     
    8185        ONLY:  sums_wssas_ws_l
    8286
     87    USE indices,                                                               &
     88        ONLY:  advc_flags_s, nxl, nxr, nyn, nys, nzb, nzt, wall_flags_0
     89
     90    USE surface_mod,                                                           &
     91        ONLY:  bc_h, surf_def_v, surf_def_h, surf_lsm_h, surf_lsm_v,           &
     92               surf_usm_h, surf_usm_v
    8393
    8494    IMPLICIT NONE
     
    192202    END INTERFACE ocean_prognostic_equations
    193203
     204    INTERFACE ocean_boundary_conditions
     205       MODULE PROCEDURE ocean_boundary_conditions
     206    END INTERFACE ocean_boundary_conditions
     207
    194208    INTERFACE ocean_swap_timelevel
    195209       MODULE PROCEDURE ocean_swap_timelevel
     
    236250           ocean_swap_timelevel, ocean_rrd_global, ocean_rrd_local,            &
    237251           ocean_wrd_global, ocean_wrd_local, ocean_3d_data_averaging,         &
    238            stokes_drift_terms, wave_breaking_term
     252           ocean_boundary_conditions, stokes_drift_terms, wave_breaking_term
    239253
    240254
     
    257271    USE indices,                                                               &
    258272        ONLY:  nxl, nxr, nyn, nys, nzb, nzt
    259 
    260     USE surface_mod,                                                           &
    261         ONLY :  bc_h
    262273
    263274    IMPLICIT NONE
     
    370381    USE indices,                                                               &
    371382        ONLY:  nzb, nzt
    372 
    373     USE surface_mod,                                                           &
    374        ONLY :  bc_h
    375383
    376384    IMPLICIT NONE
     
    15851593    USE diffusion_s_mod,                                                       &
    15861594        ONLY:  diffusion_s
    1587 
    1588     USE indices,                                                               &
    1589         ONLY:  advc_flags_s, nxl, nxr, nyn, nys, nzb, nzt, wall_flags_0
    1590 
    1591     USE surface_mod,                                                           &
    1592         ONLY:  surf_def_v, surf_def_h, surf_lsm_h, surf_lsm_v, surf_usm_h,     &
    1593                surf_usm_v
    15941595
    15951596    IMPLICIT NONE
     
    17571758    USE diffusion_s_mod,                                                       &
    17581759        ONLY:  diffusion_s
    1759 
    1760     USE indices,                                                               &
    1761         ONLY:  advc_flags_s, nzb, nzt, wall_flags_0
    1762 
    1763     USE surface_mod,                                                           &
    1764         ONLY:  surf_def_v, surf_def_h, surf_lsm_h, surf_lsm_v, surf_usm_h,     &
    1765                surf_usm_v
    17661760
    17671761    IMPLICIT NONE
     
    18621856 END SUBROUTINE ocean_prognostic_equations_ij
    18631857
     1858!------------------------------------------------------------------------------!
     1859! Description:
     1860! ------------
     1861!> Boundary conditions for ocean model
     1862!------------------------------------------------------------------------------!
     1863 SUBROUTINE ocean_boundary_conditions
     1864
     1865    IMPLICIT NONE
     1866
     1867    INTEGER(iwp) ::  i                            !< grid index x direction.
     1868    INTEGER(iwp) ::  j                            !< grid index y direction.
     1869    INTEGER(iwp) ::  k                            !< grid index z direction.
     1870    INTEGER(iwp) ::  l                            !< running index boundary type, for up- and downward-facing walls.
     1871    INTEGER(iwp) ::  m                            !< running index surface elements.
     1872
     1873!
     1874!--    Boundary conditions for salinity
     1875!--    Bottom boundary: Neumann condition because salinity flux is always
     1876!--    given.
     1877       DO  l = 0, 1
     1878          !$OMP PARALLEL DO PRIVATE( i, j, k )
     1879          DO  m = 1, bc_h(l)%ns
     1880             i = bc_h(l)%i(m)
     1881             j = bc_h(l)%j(m)
     1882             k = bc_h(l)%k(m)
     1883             sa_p(k+bc_h(l)%koff,j,i) = sa_p(k,j,i)
     1884          ENDDO
     1885       ENDDO
     1886!
     1887!--    Top boundary: Dirichlet or Neumann
     1888       IF ( ibc_sa_t == 0 )  THEN
     1889           sa_p(nzt+1,:,:) = sa(nzt+1,:,:)
     1890       ELSEIF ( ibc_sa_t == 1 )  THEN
     1891           sa_p(nzt+1,:,:) = sa_p(nzt,:,:)
     1892       ENDIF
     1893
     1894 END SUBROUTINE ocean_boundary_conditions
    18641895
    18651896!------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.