123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137 |
- MODULE lbclnk
- !!======================================================================
- !! *** MODULE lbclnk ***
- !! Ocean : lateral boundary conditions
- !!=====================================================================
- !! OPA 9.0 , LOCEAN-IPSL (2005)
- !! $Id: lbclnk.F90 1344 2009-03-27 14:02:19Z rblod $
- !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
- !!----------------------------------------------------------------------
- !!----------------------------------------------------------------------
- !! Default option shared memory computing
- !!----------------------------------------------------------------------
- !! lbc_lnk : generic interface for lbc_lnk_3d and lbc_lnk_2d
- !! lbc_lnk_3d : set the lateral boundary condition on a 3D variable
- !! on OPA ocean mesh
- !! lbc_lnk_2d : set the lateral boundary condition on a 2D variable
- !! on OPA ocean mesh
- !!----------------------------------------------------------------------
- !! * Modules used
- ! USE oce ! ocean dynamics and tracers
- USE dom_oce ! ocean space and time domain
- ! USE in_out_manager ! I/O manager
- USE lbcnfd ! north fold
- IMPLICIT NONE
- PRIVATE
- PUBLIC lbc_lnk ! ocean/ice lateral boundary conditions
- !!----------------------------------------------------------------------
- CONTAINS
- SUBROUTINE lbc_lnk( pt2d, cd_type, psgn, cd_mpp, pval )
- !!---------------------------------------------------------------------
- !! *** ROUTINE lbc_lnk_2d ***
- !!
- !! ** Purpose : set lateral boundary conditions (non mpp case)
- !!
- !! ** Method :
- !!
- !! History :
- !! ! 97-06 (G. Madec) Original code
- !! ! 01-05 (E. Durand) correction
- !! 8.5 ! 02-09 (G. Madec) F90: Free form and module
- !! ! 09-03 (R. Benshila) External north fold treatment
- !!----------------------------------------------------------------------
- !! * Arguments
- CHARACTER(len=1), INTENT( in ) :: &
- cd_type ! nature of pt2d grid-point
- ! ! = T , U , V , F or W gridpoints
- ! ! = I sea-ice U-V gridpoint (= F ocean grid point with indice shift)
- REAL(wp), INTENT( in ) :: &
- psgn ! control of the sign change
- ! ! =-1 , the sign is modified following the type of b.c. used
- ! ! = 1 , no sign change
- REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) :: &
- pt2d ! 2D array on which the boundary condition is applied
- CHARACTER(len=3), INTENT( in ), OPTIONAL :: &
- cd_mpp ! fill the overlap area only (here do nothing)
- REAL(wp) , INTENT(in ), OPTIONAL :: pval ! background value (used at closed boundaries)
- !! * Local declarations
- REAL(wp) :: zland
- IF( PRESENT( pval ) ) THEN ! set land value (zero by default)
- zland = pval
- ELSE
- zland = 0.e0
- ENDIF
- IF (PRESENT(cd_mpp)) THEN
- ! only fill the overlap area and extra allows
- ! this is in mpp case. In this module, just do nothing
- ELSE
- ! ! East-West boundaries
- ! ! ====================
- SELECT CASE ( nperio )
- !
- CASE ( 1 , 4 , 6 ) !** cyclic east-west
- pt2d( 1 ,:) = pt2d(jpim1,:) ! all points
- pt2d(jpi,:) = pt2d( 2 ,:)
- !
- CASE DEFAULT !** East closed -- West closed
- SELECT CASE ( cd_type )
- CASE ( 'T' , 'U' , 'V' , 'W' ) ! T-, U-, V-, W-points
- pt2d( 1 ,:) = zland
- pt2d(jpi,:) = zland
- CASE ( 'F' ) ! F-point
- pt2d(jpi,:) = zland
- END SELECT
- !
- END SELECT
-
- ! ! North-South boundaries
- ! ! ======================
- SELECT CASE ( nperio )
- !
- CASE ( 2 ) !** South symmetric -- North closed
- SELECT CASE ( cd_type )
- CASE ( 'T' , 'U' , 'W' ) ! T-, U-, W-points
- pt2d(:, 1 ) = pt2d(:,3)
- pt2d(:,jpj) = zland
- CASE ( 'V' , 'F' ) ! V-, F-points
- pt2d(:, 1 ) = psgn * pt2d(:,2)
- pt2d(:,jpj) = zland
- END SELECT
- !
- CASE ( 3 , 4 , 5 , 6 ) !** North fold T or F-point pivot -- South closed
- SELECT CASE ( cd_type ) ! South : closed
- CASE ( 'T' , 'U' , 'V' , 'W' , 'I' ) ! all points except F-point
- pt2d(:, 1 ) = zland
- END SELECT
- ! ! North fold
- pt2d( 1 ,1 ) = zland
- pt2d( 1 ,jpj) = zland
- pt2d(jpi,jpj) = zland
- CALL lbc_nfd( pt2d(:,:), cd_type, psgn )
- !
- CASE DEFAULT !** North closed -- South closed
- SELECT CASE ( cd_type )
- CASE ( 'T' , 'U' , 'V' , 'W' ) ! T-, U-, V-, W-points
- pt2d(:, 1 ) = zland
- pt2d(:,jpj) = zland
- CASE ( 'F' ) ! F-point
- pt2d(:,jpj) = zland
- END SELECT
- !
- END SELECT
- ENDIF
-
- END SUBROUTINE lbc_lnk
- !!======================================================================
- END MODULE lbclnk
|