New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 15548 for NEMO/branches/2021/ticket2632_r14588_theta_sbcblk/src/OCE/BDY/bdydyn2d.F90 – NEMO

Ignore:
Timestamp:
2021-11-28T18:59:49+01:00 (3 years ago)
Author:
gsamson
Message:

update branch to the head of the trunk (r15547); ticket #2632

Location:
NEMO/branches/2021/ticket2632_r14588_theta_sbcblk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/ticket2632_r14588_theta_sbcblk

    • Property svn:externals
      •  

        old new  
        99 
        1010# SETTE 
        11 ^/utils/CI/sette@14244        sette 
         11^/utils/CI/sette@HEAD        sette 
         12 
  • NEMO/branches/2021/ticket2632_r14588_theta_sbcblk/src/OCE/BDY/bdydyn2d.F90

    r14433 r15548  
    1818   USE bdylib          ! BDY library routines 
    1919   USE phycst          ! physical constants 
    20    USE lib_mpp, ONLY: jpfillnothing 
     20   USE lib_mpp 
    2121   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2222   USE wet_dry         ! Use wet dry to get reference ssh level 
    2323   USE in_out_manager  ! 
    24    USE lib_mpp, ONLY: ctl_stop 
    2524 
    2625   IMPLICIT NONE 
     
    5049      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pssh 
    5150      !! 
    52       INTEGER  ::   ib_bdy, ir     ! BDY set index, rim index 
    53       LOGICAL  ::   llrim0         ! indicate if rim 0 is treated 
    54       LOGICAL, DIMENSION(4) :: llsend2, llrecv2, llsend3, llrecv3  ! indicate how communications are to be carried out 
     51      INTEGER               ::   ib_bdy, ir     ! BDY set index, rim index 
     52      INTEGER, DIMENSION(3) ::   idir3 
     53      INTEGER, DIMENSION(6) ::   idir6 
     54      LOGICAL               ::   llrim0         ! indicate if rim 0 is treated 
     55      LOGICAL, DIMENSION(8) ::   llsend2, llrecv2, llsend3, llrecv3  ! indicate how communications are to be carried out 
     56      !!---------------------------------------------------------------------- 
    5557       
    5658      llsend2(:) = .false.   ;   llrecv2(:) = .false. 
     
    8789            SELECT CASE( cn_dyn2d(ib_bdy) ) 
    8890            CASE('flather') 
    89                llsend2(1:2) = llsend2(1:2) .OR. lsend_bdyint(ib_bdy,2,1:2,ir)   ! west/east, U points 
    90                llsend2(1)   = llsend2(1)   .OR. lsend_bdyext(ib_bdy,2,1,ir)     ! neighbour might search point towards its east bdy 
    91                llrecv2(1:2) = llrecv2(1:2) .OR. lrecv_bdyint(ib_bdy,2,1:2,ir)   ! west/east, U points 
    92                llrecv2(2)   = llrecv2(2)   .OR. lrecv_bdyext(ib_bdy,2,2,ir)     ! might search point towards bdy on the east 
    93                llsend3(3:4) = llsend3(3:4) .OR. lsend_bdyint(ib_bdy,3,3:4,ir)   ! north/south, V points 
    94                llsend3(3)   = llsend3(3)   .OR. lsend_bdyext(ib_bdy,3,3,ir)     ! neighbour might search point towards its north bdy  
    95                llrecv3(3:4) = llrecv3(3:4) .OR. lrecv_bdyint(ib_bdy,3,3:4,ir)   ! north/south, V points 
    96                llrecv3(4)   = llrecv3(4)   .OR. lrecv_bdyext(ib_bdy,3,4,ir)     ! might search point towards bdy on the north 
     91               idir6 = (/ jpwe, jpea, jpsw, jpse, jpnw, jpne /) 
     92               llsend2(idir6) = llsend2(idir6) .OR. lsend_bdyint(ib_bdy,2,idir6,ir)   ! west/east, U points 
     93               idir3 = (/ jpwe, jpsw, jpnw /) 
     94               llsend2(idir3) = llsend2(idir3) .OR. lsend_bdyext(ib_bdy,2,idir3,ir)   ! nei might search point towards its east bdy 
     95               llrecv2(idir6) = llrecv2(idir6) .OR. lrecv_bdyint(ib_bdy,2,idir6,ir)   ! west/east, U points 
     96               idir3 = (/ jpea, jpse, jpne /) 
     97               llrecv2(idir3) = llrecv2(idir3) .OR. lrecv_bdyext(ib_bdy,2,idir3,ir)   ! might search point towards bdy on the east 
     98               idir6 = (/ jpso, jpno, jpsw, jpse, jpnw, jpne /) 
     99               llsend3(idir6) = llsend3(idir6) .OR. lsend_bdyint(ib_bdy,3,idir6,ir)   ! north/south, V points 
     100               idir3 = (/ jpso, jpsw, jpse /) 
     101               llsend3(idir3) = llsend3(idir3) .OR. lsend_bdyext(ib_bdy,3,idir3,ir)   ! nei might search point towards its north bdy 
     102               llrecv3(idir6) = llrecv3(idir6) .OR. lrecv_bdyint(ib_bdy,3,idir6,ir)   ! north/south, V points 
     103               idir3 = (/ jpno, jpnw, jpne /) 
     104               llrecv3(idir3) = llrecv3(idir3) .OR. lrecv_bdyext(ib_bdy,3,idir3,ir)   ! might search point towards bdy on the north 
    97105            CASE('orlanski', 'orlanski_npo') 
    98                llsend2(:) = llsend2(:) .OR. lsend_bdy(ib_bdy,2,:,ir)   ! possibly every direction, U points 
    99                llrecv2(:) = llrecv2(:) .OR. lrecv_bdy(ib_bdy,2,:,ir)   ! possibly every direction, U points 
    100                llsend3(:) = llsend3(:) .OR. lsend_bdy(ib_bdy,3,:,ir)   ! possibly every direction, V points 
    101                llrecv3(:) = llrecv3(:) .OR. lrecv_bdy(ib_bdy,3,:,ir)   ! possibly every direction, V points 
     106               llsend2(:) = llsend2(:) .OR. lsend_bdyolr(ib_bdy,2,:,ir)   ! possibly every direction, U points 
     107               llrecv2(:) = llrecv2(:) .OR. lrecv_bdyolr(ib_bdy,2,:,ir)   ! possibly every direction, U points 
     108               llsend3(:) = llsend3(:) .OR. lsend_bdyolr(ib_bdy,3,:,ir)   ! possibly every direction, V points 
     109               llrecv3(:) = llrecv3(:) .OR. lrecv_bdyolr(ib_bdy,3,:,ir)   ! possibly every direction, V points 
    102110            END SELECT 
    103111         END DO 
     
    310318      INTEGER ::   ibeg, iend      ! length of rim to be treated (rim 0 or rim 1) 
    311319      LOGICAL ::   llrim0          ! indicate if rim 0 is treated 
    312       LOGICAL, DIMENSION(4) :: llsend1, llrecv1  ! indicate how communications are to be carried out 
     320      LOGICAL, DIMENSION(8) :: llsend1, llrecv1  ! indicate how communications are to be carried out 
    313321      !!---------------------------------------------------------------------- 
    314322      llsend1(:) = .false.   ;   llrecv1(:) = .false. 
Note: See TracChangeset for help on using the changeset viewer.