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 15368 – NEMO

Changeset 15368


Ignore:
Timestamp:
2021-10-14T10:25:34+02:00 (3 years ago)
Author:
smasson
Message:

trunk: final version (hopefully) for ticket #2731

Location:
NEMO/trunk/src/OCE/BDY
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/BDY/bdydta.F90

    r15360 r15368  
    258258            END DO 
    259259         ENDIF   ! ltotvel 
    260          IF( bf_alias(jp_bdyv3d)%ltotvel ) THEN     ! if we read 3D total velocity (can be true only if u3d was read) 
     260         IF( bf_alias(jp_bdyv3d)%ltotvel ) THEN     ! if we read 3D total velocity (can be true only if v3d was read) 
    261261            igrd = 3                       ! meridional velocity 
    262262            DO ib = 1, idx_bdy(jbdy)%nblen(igrd) 
  • NEMO/trunk/src/OCE/BDY/bdydyn2d.F90

    r15363 r15368  
    5050      !! 
    5151      INTEGER               ::   ib_bdy, ir     ! BDY set index, rim index 
     52      INTEGER, DIMENSION(3) ::   idir3 
     53      INTEGER, DIMENSION(6) ::   idir6 
    5254      LOGICAL               ::   llrim0         ! indicate if rim 0 is treated 
    5355      LOGICAL, DIMENSION(8) ::   llsend2, llrecv2, llsend3, llrecv3  ! indicate how communications are to be carried out 
     
    8789            SELECT CASE( cn_dyn2d(ib_bdy) ) 
    8890            CASE('flather') 
    89                llsend2(:) = llsend2(:) .OR. lsend_bdyext(ib_bdy,2,:,ir) .OR. lsend_bdyint(ib_bdy,2,:,ir) 
    90                llrecv2(:) = llrecv2(:) .OR. lrecv_bdyext(ib_bdy,2,:,ir) .OR. lrecv_bdyint(ib_bdy,2,:,ir) 
    91                llsend3(:) = llsend3(:) .OR. lsend_bdyext(ib_bdy,3,:,ir) .OR. lsend_bdyint(ib_bdy,3,:,ir) 
    92                llrecv3(:) = llrecv3(:) .OR. lrecv_bdyext(ib_bdy,3,:,ir) .OR. lrecv_bdyint(ib_bdy,3,:,ir) 
     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 
    93105            CASE('orlanski', 'orlanski_npo') 
    94106               llsend2(:) = llsend2(:) .OR. lsend_bdyolr(ib_bdy,2,:,ir)   ! possibly every direction, U points 
  • NEMO/trunk/src/OCE/BDY/bdydyn3d.F90

    r15363 r15368  
    4545      ! 
    4646      INTEGER               ::   ib_bdy, ir     ! BDY set index, rim index 
     47      INTEGER, DIMENSION(6) ::   idir6 
    4748      LOGICAL               ::   llrim0         ! indicate if rim 0 is treated 
    4849      LOGICAL, DIMENSION(8) ::   llsend2, llrecv2, llsend3, llrecv3  ! indicate how communications are to be carried out 
     
    8586               llsend3(:) = llsend3(:) .OR. lsend_bdyolr(ib_bdy,3,:,ir)   ! possibly every direction, V points 
    8687               llrecv3(:) = llrecv3(:) .OR. lrecv_bdyolr(ib_bdy,3,:,ir)   ! possibly every direction, V points 
    87             CASE('zerograd', 'neumann') 
    88                llsend2(:) = llsend2(:) .OR. lsend_bdyint(ib_bdy,2,:,ir) 
    89                llrecv2(:) = llrecv2(:) .OR. lrecv_bdyint(ib_bdy,2,:,ir) 
    90                llsend3(:) = llsend3(:) .OR. lsend_bdyint(ib_bdy,3,:,ir) 
    91                llrecv3(:) = llrecv3(:) .OR. lrecv_bdyint(ib_bdy,3,:,ir) 
     88            CASE('zerograd') 
     89               idir6 = (/ jpso, jpno, jpsw, jpse, jpnw, jpne /) 
     90               llsend2(idir6) = llsend2(idir6) .OR. lsend_bdyint(ib_bdy,2,idir6,ir)   ! north/south, U points 
     91               llrecv2(idir6) = llrecv2(idir6) .OR. lrecv_bdyint(ib_bdy,2,idir6,ir)   ! north/south, U points 
     92               idir6 = (/ jpwe, jpea, jpsw, jpse, jpnw, jpne /) 
     93               llsend3(idir6) = llsend3(idir6) .OR. lsend_bdyint(ib_bdy,3,idir6,ir)   ! west/east, V points 
     94               llrecv3(idir6) = llrecv3(idir6) .OR. lrecv_bdyint(ib_bdy,3,idir6,ir)   ! west/east, V points 
     95            CASE('neumann') 
     96               llsend2(:) = llsend2(:) .OR. lsend_bdyint(ib_bdy,2,:,ir)   ! possibly every direction, U points 
     97               llrecv2(:) = llrecv2(:) .OR. lrecv_bdyint(ib_bdy,2,:,ir)   ! possibly every direction, U points 
     98               llsend3(:) = llsend3(:) .OR. lsend_bdyint(ib_bdy,3,:,ir)   ! possibly every direction, V points 
     99               llrecv3(:) = llrecv3(:) .OR. lrecv_bdyint(ib_bdy,3,:,ir)   ! possibly every direction, V points 
    92100            END SELECT 
    93101         END DO 
  • NEMO/trunk/src/OCE/BDY/bdyice.F90

    r15360 r15368  
    331331      INTEGER               ::   jbdy, ir          ! BDY set index, rim index 
    332332      INTEGER               ::   ibeg, iend        ! length of rim to be treated (rim 0 or rim 1) 
     333      INTEGER, DIMENSION(3) ::   idir3 
    333334      REAL(wp)              ::   zmsk1, zmsk2, zflag 
    334335      LOGICAL, DIMENSION(8) :: llsend2, llrecv2, llsend3, llrecv3  ! indicate how communications are to be carried out 
     
    430431            DO jbdy = 1, nb_bdy 
    431432               IF( cn_ice(jbdy) == 'frs' .AND. nn_ice_dta(jbdy) /= 0 ) THEN 
    432                   llsend2(:) = llsend2(:) .OR. lsend_bdyext(ib_bdy,2,:,ir) .OR. lsend_bdyint(ib_bdy,2,:,ir) 
    433                   llrecv2(:) = llrecv2(:) .OR. lrecv_bdyext(ib_bdy,2,:,ir) .OR. lrecv_bdyint(ib_bdy,2,:,ir) 
     433                  llsend2(  :  ) = llsend2(  :  ) .OR. lsend_bdyint(jbdy,2,  :  ,ir)   ! possibly every direction, U points 
     434                  idir3 = (/ jpwe, jpsw, jpnw /) 
     435                  llsend2(idir3) = llsend2(idir3) .OR. lsend_bdyext(jbdy,2,idir3,ir)   ! nei might search point towards its ea bdy 
     436                  llrecv2(  :  ) = llrecv2(  :  ) .OR. lrecv_bdyint(jbdy,2,  :  ,ir)   ! possibly every direction, U points 
     437                  idir3 = (/ jpea, jpse, jpne /) 
     438                  llrecv2(idir3) = llrecv2(idir3) .OR. lrecv_bdyext(jbdy,2,idir3,ir)   ! might search point towards east bdy 
    434439               END IF 
    435440            END DO 
     
    442447            DO jbdy = 1, nb_bdy 
    443448               IF( cn_ice(jbdy) == 'frs' .AND. nn_ice_dta(jbdy) /= 0 ) THEN 
    444                   llsend3(:) = llsend3(:) .OR. lsend_bdyext(ib_bdy,3,:,ir) .OR. lsend_bdyint(ib_bdy,3,:,ir) 
    445                   llrecv3(:) = llrecv3(:) .OR. lrecv_bdyext(ib_bdy,3,:,ir) .OR. lrecv_bdyint(ib_bdy,3,:,ir) 
     449                  llsend3(  :  ) = llsend3(  :  ) .OR. lsend_bdyint(jbdy,3,  :  ,ir)   ! possibly every direction, V points 
     450                  idir3 = (/ jpso, jpsw, jpse /) 
     451                  llsend3(idir3) = llsend3(idir3) .OR. lsend_bdyext(jbdy,3,idir3,ir)   ! nei might search point towards its no bdy 
     452                  llrecv3(  :  ) = llrecv3(  :  ) .OR. lrecv_bdyint(jbdy,3,  :  ,ir)   ! possibly every direction, V points 
     453                  idir3 = (/ jpno, jpnw, jpne /) 
     454                  llrecv3(idir3) = llrecv3(idir3) .OR. lrecv_bdyext(jbdy,3,idir3,ir)   ! might search point towards north bdy 
    446455               END IF 
    447456            END DO 
  • NEMO/trunk/src/OCE/BDY/bdyini.F90

    r15363 r15368  
    147147      INTEGER  ::   icount, icountr, icountr0, ibr_max     ! local integers 
    148148      INTEGER  ::   ilen1                           !   -       - 
    149       INTEGER  ::   iiRst, iiRnd, iiSst, iiSnd, iiRcorn, iiSdiag, iiSsono 
    150       INTEGER  ::   ijRst, ijRnd, ijSst, ijSnd, ijRcorn, ijSdiag, ijSsono 
     149      INTEGER  ::   iiRst, iiRnd, iiSst, iiSnd, iiSstdiag, iiSnddiag, iiSstsono, iiSndsono 
     150      INTEGER  ::   ijRst, ijRnd, ijSst, ijSnd, ijSstdiag, ijSnddiag, ijSstsono, ijSndsono 
    151151      INTEGER  ::   iiout, ijout, iioutdir, ijoutdir, icnt 
    152152      INTEGER  ::   iRnei, iRdiag, iRsono 
     
    807807                     !             outside of the MPI domain     ..o|__:__ 
    808808                     iRnei    = jpwe             ;   iSnei    = jpea 
    809                      iiRst    = 1                ;   ijRst    = 2               ! Rcv we-side starting point, excluding sw-corner 
    810                      iiRnd    = 1                ;   ijRnd    = jpj-1           ! Rcv we-side   ending point, excluding nw-corner 
    811                      iiSst    = jpi-2*nn_hls+1   ;   ijSst    = 2               ! Snd ea-side starting point, excluding se-corner 
    812                      iiSnd    = jpi-2*nn_hls+1   ;   ijSnd    = jpj-1           ! Snd ea-side   ending point, excluding ne-corner 
     809                     iiRst    = 1                ;   ijRst    = Njs0            ! Rcv we-side starting point, excluding sw-corner 
     810                     iiRnd    = nn_hls           ;   ijRnd    = Nje0            ! Rcv we-side   ending point, excluding nw-corner 
     811                     iiSst    = Nie0-nn_hls+1    ;   ijSst    = Njs0            ! Snd ea-side starting point, excluding se-corner 
     812                     iiSnd    = Nie0             ;   ijSnd    = Nje0            ! Snd ea-side   ending point, excluding ne-corner 
    813813                     iioutdir = -1               ;   ijoutdir = -999            ! outside MPI domain: westward 
    814814                     !                                           ______.... 
     
    817817                     !             outside of the MPI domain     ___:__|o.. 
    818818                     iRnei    = jpea             ;   iSnei    = jpwe 
    819                      iiRst    = jpi              ;   ijRst    = 2                ! Rcv ea-side starting point, excluding se-corner 
    820                      iiRnd    = jpi              ;   ijRnd    = jpj-1            ! Rcv ea-side   ending point, excluding ne-corner 
    821                      iiSst    = 2*nn_hls         ;   ijSst    = 2                ! Snd we-side starting point, excluding sw-corner 
    822                      iiSnd    = 2*nn_hls         ;   ijSnd    = jpj-1            ! Snd we-side   ending point, excluding nw-corner 
     819                     iiRst    = Nie0+1           ;   ijRst    =  Njs0            ! Rcv ea-side starting point, excluding se-corner 
     820                     iiRnd    = jpi              ;   ijRnd    =  Nje0            ! Rcv ea-side   ending point, excluding ne-corner 
     821                     iiSst    = Nis0             ;   ijSst    =  Njs0            ! Snd we-side starting point, excluding sw-corner 
     822                     iiSnd    = Nis0+nn_hls-1    ;   ijSnd    =  Nje0            ! Snd we-side   ending point, excluding nw-corner 
    823823                     iioutdir = 1                ;   ijoutdir = -999             ! outside MPI domain: eastward 
    824824                     ! 
     
    829829                     !                                           :       : 
    830830                     iRnei    = jpso             ;   iSnei    = jpno 
    831                      iiRst    = 2                ;   ijRst    = 1                ! Rcv so-side starting point, excluding sw-corner 
    832                      iiRnd    = jpi-1            ;   ijRnd    = 1                ! Rcv so-side   ending point, excluding se-corner 
    833                      iiSst    = 2                ;   ijSst    = jpj-2*nn_hls+1   ! Snd no-side starting point, excluding nw-corner 
    834                      iiSnd    = jpi-1            ;   ijSnd    = jpj-2*nn_hls+1   ! Snd no-side   ending point, excluding ne-corner 
     831                     iiRst    = Nis0             ;   ijRst    = 1                ! Rcv so-side starting point, excluding sw-corner 
     832                     iiRnd    = Nie0             ;   ijRnd    = nn_hls           ! Rcv so-side   ending point, excluding se-corner 
     833                     iiSst    = Nis0             ;   ijSst    = Nje0-nn_hls+1    ! Snd no-side starting point, excluding nw-corner 
     834                     iiSnd    = Nie0             ;   ijSnd    = Nje0             ! Snd no-side   ending point, excluding ne-corner 
    835835                     iioutdir = -999             ;   ijoutdir = -1               ! outside MPI domain: southward 
    836836                     !                                           :       : 
     
    840840                     !                                           |¨¨¨¨¨¨¨| 
    841841                     iRnei    = jpno             ;   iSnei    = jpso 
    842                      iiRst    = 2                ;   ijRst    = jpj              ! Rcv no-side starting point, excluding nw-corner 
    843                      iiRnd    = jpi-1            ;   ijRnd    = jpj              ! Rcv no-side   ending point, excluding ne-corner 
    844                      iiSst    = 2                ;   ijSst    =     2*nn_hls     ! Snd so-side starting point, excluding sw-corner 
    845                      iiSnd    = jpi-1            ;   ijSnd    =     2*nn_hls     ! Snd so-side   ending point, excluding se-corner 
     842                     iiRst    = Nis0             ;   ijRst    = Nje0+1           ! Rcv no-side starting point, excluding nw-corner 
     843                     iiRnd    = Nie0             ;   ijRnd    = jpj              ! Rcv no-side   ending point, excluding ne-corner 
     844                     iiSst    = Nis0             ;   ijSst    = Njs0             ! Snd so-side starting point, excluding sw-corner 
     845                     iiSnd    = Nie0             ;   ijSnd    = Njs0+nn_hls-1    ! Snd so-side   ending point, excluding se-corner 
    846846                     iioutdir = -999             ;   ijoutdir = 1                ! outside MPI domain: northward 
    847847                  END SELECT 
     
    884884                     !             outside of the MPI domain   o o o: 
    885885                     !                                              : 
    886                      iRdiag   = jpsw             ;   iRsono   = jpso             ! Recv: for sw or so 
    887                      iSdiag   = jpne             ;   iSsono   = jpno             ! Send: to ne or no 
    888                      iiRcorn  = 1                ;   ijRcorn  = 1                ! receiving sw-corner 
    889                      iiSdiag  = jpi-2*nn_hls+1   ;   ijSdiag  = jpj-2*nn_hls+1   ! send to sw-corner of ne neighbourg 
    890                      iiSsono  = 1                ;   ijSsono  = jpj-2*nn_hls+1   ! send to sw-corner of no neighbourg 
    891                      iioutdir = -1               ;   ijoutdir = -1               ! outside MPI domain: westward or southward 
     886                     iRdiag    = jpsw            ;   iRsono    = jpso            ! Recv: for sw or so 
     887                     iSdiag    = jpne            ;   iSsono    = jpno            ! Send: to ne or no 
     888                     iiRst     = 1               ;   ijRst     = 1               ! Rcv sw-corner starting point 
     889                     iiRnd     = nn_hls          ;   ijRnd     = nn_hls          ! Rcv sw-corner   ending point 
     890                     iiSstdiag = Nie0-nn_hls+1   ;   ijSstdiag = Nje0-nn_hls+1   ! send to sw-corner of ne neighbourg 
     891                     iiSnddiag = Nie0            ;   ijSnddiag = Nje0            ! send to sw-corner of ne neighbourg 
     892                     iiSstsono = 1               ;   ijSstsono = Nje0-nn_hls+1   ! send to sw-corner of no neighbourg 
     893                     iiSndsono = nn_hls          ;   ijSndsono = Nje0            ! send to sw-corner of no neighbourg 
     894                     iioutdir  = -1              ;   ijoutdir  = -1              ! outside MPI domain: westward or southward 
    892895                     !                                          ....|... 
    893896                  CASE( 2 )   ! x: rim on se-corner             :   |o 
     
    895898                     !             outside of the MPI domain    :o o o 
    896899                     !                                          :     
    897                      iRdiag   = jpse             ;   iRsono   = jpso             ! Recv: for se or so 
    898                      iSdiag   = jpnw             ;   iSsono   = jpno             ! Send: to nw or no 
    899                      iiRcorn  = jpi              ;   ijRcorn  = 1                ! receiving se-corner 
    900                      iiSdiag  =     2*nn_hls     ;   ijSdiag  = jpj-2*nn_hls+1   ! send to se-corner of nw neighbourg 
    901                      iiSsono  = jpi              ;   ijSsono  = jpj-2*nn_hls+1   ! send to se-corner of no neighbourg 
    902                      iioutdir = 1                ;   ijoutdir = -1               ! outside MPI domain: eastward or southward 
     900                     iRdiag    = jpse            ;   iRsono    = jpso            ! Recv: for se or so 
     901                     iSdiag    = jpnw            ;   iSsono    = jpno            ! Send: to nw or no 
     902                     iiRst     = Nie0+1          ;   ijRst     = 1               ! Rcv se-corner starting point 
     903                     iiRnd     = jpi             ;   ijRnd     = nn_hls          ! Rcv se-corner   ending point 
     904                     iiSstdiag = Nis0            ;   ijSstdiag = Nje0-nn_hls+1   ! send to se-corner of nw neighbourg 
     905                     iiSnddiag = Nis0+nn_hls-1   ;   ijSnddiag = Nje0            ! send to se-corner of nw neighbourg 
     906                     iiSstsono = Nie0+1          ;   ijSstsono = Nje0-nn_hls+1   ! send to se-corner of no neighbourg 
     907                     iiSndsono = jpi             ;   ijSndsono = Nje0            ! send to se-corner of no neighbourg 
     908                     iioutdir  = 1               ;   ijoutdir  = -1              ! outside MPI domain: eastward or southward 
    903909                     !                                              :        
    904910                     !                                         o o_o:___ 
     
    906912                     !          o: potential neighbour(s)    ..o|...: 
    907913                     !             outside of the MPI domain    | 
    908                      iRdiag   = jpnw             ;   iRsono   = jpno             ! Recv: for nw or no 
    909                      iSdiag   = jpse             ;   iSsono   = jpso             ! Send: to se or so 
    910                      iiRcorn  = 1                ;   ijRcorn  = jpj              ! receiving nw-corner 
    911                      iiSdiag  = jpi-2*nn_hls+1   ;   ijSdiag  =     2*nn_hls     ! send to nw-corner of se neighbourg 
    912                      iiSsono  = 1                ;   ijSsono  =     2*nn_hls     ! send to nw-corner of so neighbourg 
    913                      iioutdir = -1               ;   ijoutdir =  1               ! outside MPI domain: westward or northward 
     914                     iRdiag    = jpnw            ;   iRsono    = jpno            ! Recv: for nw or no 
     915                     iSdiag    = jpse            ;   iSsono    = jpso            ! Send: to se or so 
     916                     iiRst     = 1               ;   ijRst     = Nje0+1          ! Rcv nw-corner starting point 
     917                     iiRnd     = nn_hls          ;   ijRnd     = jpj             ! Rcv nw-corner   ending point 
     918                     iiSstdiag = Nie0-nn_hls+1   ;   ijSstdiag = Njs0            ! send to nw-corner of se neighbourg 
     919                     iiSnddiag = Nie0            ;   ijSnddiag = Njs0+nn_hls-1   ! send to nw-corner of se neighbourg 
     920                     iiSstsono = 1               ;   ijSstsono = Njs0            ! send to nw-corner of so neighbourg 
     921                     iiSndsono = nn_hls          ;   ijSndsono = Njs0+nn_hls-1   ! send to nw-corner of so neighbourg 
     922                     iioutdir  = -1              ;   ijoutdir  =  1              ! outside MPI domain: westward or northward 
    914923                     !                                          :        
    915924                     !                                       ___:o_o o 
     
    917926                     !          o: potential neighbour(s)       :...|o... 
    918927                     !             outside of the MPI domain        | 
    919                      iRdiag   = jpne             ;   iRsono   = jpno             ! Recv: for ne or no 
    920                      iSdiag   = jpsw             ;   iSsono   = jpso             ! Send: to sw or so 
    921                      iiRcorn  = jpi              ;   ijRcorn  = jpj              ! receiving ne-corner 
    922                      iiSdiag  =     2*nn_hls     ;   ijSdiag  =     2*nn_hls     ! send to ne-corner of sw neighbourg 
    923                      iiSsono  = jpi              ;   ijSsono  =     2*nn_hls     ! send to ne-corner of so neighbourg 
    924                      iioutdir = 1                ;   ijoutdir = 1                ! outside MPI domain: eastward or southward 
     928                     iRdiag    = jpne            ;   iRsono    = jpno            ! Recv: for ne or no 
     929                     iSdiag    = jpsw            ;   iSsono    = jpso            ! Send: to sw or so 
     930                     iiRst     = Nie0+1          ;   ijRst     = Nje0+1          ! Rcv ne-corner starting point 
     931                     iiRnd     = jpi             ;   ijRnd     = jpj             ! Rcv ne-corner   ending point 
     932                     iiSstdiag = Nis0            ;   ijSstdiag = Njs0            ! send to ne-corner of sw neighbourg 
     933                     iiSnddiag = Nis0+nn_hls-1   ;   ijSnddiag = Njs0+nn_hls-1   ! send to ne-corner of sw neighbourg 
     934                     iiSstsono = Nie0+1          ;   ijSstsono = Njs0            ! send to ne-corner of so neighbourg 
     935                     iiSndsono = jpi             ;   ijSndsono = Njs0+nn_hls-1   ! send to ne-corner of so neighbourg 
     936                     iioutdir  = 1               ;   ijoutdir  = 1               ! outside MPI domain: eastward or southward 
    925937                  END SELECT 
    926938                  ! 
    927939                  ! Check if we need to receive data for this rim point 
    928                   IF( ii == iiRcorn .AND. ij == ijRcorn ) THEN   ! the rim point is located on the corner for the MPI domain 
     940                  IF( ii >= iiRst .AND. ii <= iiRnd .AND. ij >= ijRst .AND. ij <= ijRnd ) THEN   ! rim point on the corner 
    929941                     iiout = ii+iioutdir ; ijout = ij+ijoutdir        ! in which direction do we go outside of the MPI domain? 
    930942                     ! take care of neighbourg(s) in the interior of the computational domain 
     
    943955                  ! Check if this rim point corresponds to the corner of one neighbourg. if yes, do we need to send data? 
    944956                  ! Direct send to diag: Is this rim point the corner point of a diag neighbour with which we communicate? 
    945                   IF( ii == iiSdiag .AND. ij == ijSdiag .AND. mpiSnei(nn_hls,iSdiag) > -1 ) THEN 
     957                  IF( ii >= iiSstdiag .AND. ii <= iiSnddiag .AND. ij >= ijSstdiag .AND. ij <= ijSnddiag   & 
     958                     &                .AND. mpiSnei(nn_hls,iSdiag) > -1 ) THEN 
    946959                     iiout = ii+iioutdir ; ijout = ij+ijoutdir        ! in which direction do we go outside of the nei MPI domain? 
    947960                     ! take care of neighbourg(s) in the interior of the computational domain 
     
    954967                  ENDIF 
    955968                  ! Indirect send to diag (through so/no): rim point is the corner point of a so/no nei with which we communicate 
    956                   IF( ii == iiSsono .AND. ij == ijSsono .AND. mpiSnei(nn_hls,iSsono) > -1 .AND. nn_comm == 1 ) THEN 
     969                  IF( ii >= iiSstsono .AND. ii <= iiSndsono .AND. ij >= ijSstsono .AND. ij <= ijSndsono   & 
     970                     &                .AND. mpiSnei(nn_hls,iSsono) > -1 .AND. nn_comm == 1 ) THEN 
    957971                     iiout = ii+iioutdir ; ijout = ij+ijoutdir        ! in which direction do we go outside of the nei MPI domain? 
    958972                     ! take care of neighbourg(s) in the interior of the computational domain 
Note: See TracChangeset for help on using the changeset viewer.