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 14367 for NEMO/branches/2021 – NEMO

Changeset 14367 for NEMO/branches/2021


Ignore:
Timestamp:
2021-02-02T08:51:42+01:00 (3 years ago)
Author:
smasson
Message:

dev_r14312_MPI_Interface: keep send/recv buffers in memory if smaller than jpi*jpj, #2598

Location:
NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/LBC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/LBC/lbc_lnk_neicoll_generic.h90

    r14366 r14367  
    1717      INTEGER  ::   ip0j, ip1j, im0j, im1j 
    1818      INTEGER  ::   ishti, ishtj, ishti2, ishtj2 
    19       INTEGER  ::   iszs, iszr 
     19      INTEGER  ::   iszS, iszR 
    2020      INTEGER  ::   ierr 
    2121      INTEGER  ::   ihls, idx 
     
    2626      INTEGER, DIMENSION(8)  ::   isizej, ishtSj, ishtRj, ishtPj 
    2727      INTEGER, DIMENSION(8)  ::   ifill, iszall 
    28       INTEGER, DIMENSION(:), ALLOCATABLE  ::   icounts, icountr    ! number of elements to be sent/received 
    29       INTEGER, DIMENSION(:), ALLOCATABLE  ::   idispls, idisplr    ! displacement in halos arrays 
     28      INTEGER, DIMENSION(:), ALLOCATABLE  ::   iScnt, iRcnt    ! number of elements to be sent/received 
     29      INTEGER, DIMENSION(:), ALLOCATABLE  ::   iSdpl, iRdpl    ! displacement in halos arrays 
    3030      LOGICAL, DIMENSION(8)  ::   llsend, llrecv 
    3131      REAL(PRECISION) ::   zland 
    32       REAL(PRECISION), DIMENSION(:), ALLOCATABLE  ::   zsnd, zrcv          ! halos arrays 
    33       LOGICAL  ::   ll4only                                        ! default: 8 neighbourgs 
     32      LOGICAL  ::   ll4only                                    ! default: 8 neighbourgs 
    3433      LOGICAL  ::   ll_IdoNFold 
    3534      !!---------------------------------------------------------------------- 
     
    140139      ! 
    141140      ! Allocate local temporary arrays to be sent/received. 
    142       iszs = COUNT( llsend ) 
    143       iszr = COUNT( llrecv ) 
    144       ALLOCATE( icounts(iszs), icountr(iszr), idispls(iszs), idisplr(iszr) )   ! ok if iszs = 0 or iszr = 0 
     141      iszS = COUNT( llsend ) 
     142      iszR = COUNT( llrecv ) 
     143      ALLOCATE( iScnt(iszS), iRcnt(iszR), iSdpl(iszS), iRdpl(iszR) )   ! ok if iszS = 0 or iszR = 0 
    145144      iszall(:) = isizei(:) * isizej(:) * ipk * ipl * ipf 
    146       icounts(:) = PACK( iszall, mask = llsend )                                       ! ok if mask = .false. 
    147       icountr(:) = PACK( iszall, mask = llrecv ) 
    148       idispls(1) = 0 
    149       DO jn = 2,iszs 
    150          idispls(jn) = idispls(jn-1) + icounts(jn-1)   ! with _alltoallv: in units of sendtype 
    151       END DO 
    152       idisplr(1) = 0 
    153       DO jn = 2,iszr 
    154          idisplr(jn) = idisplr(jn-1) + icountr(jn-1)   ! with _alltoallv: in units of sendtype 
     145      iScnt(:) = PACK( iszall, mask = llsend )                                       ! ok if mask = .false. 
     146      iRcnt(:) = PACK( iszall, mask = llrecv ) 
     147      iSdpl(1) = 0 
     148      DO jn = 2,iszS 
     149         iSdpl(jn) = iSdpl(jn-1) + iScnt(jn-1)   ! with _alltoallv: in units of sendtype 
     150      END DO 
     151      iRdpl(1) = 0 
     152      DO jn = 2,iszR 
     153         iRdpl(jn) = iRdpl(jn-1) + iRcnt(jn-1)   ! with _alltoallv: in units of sendtype 
    155154      END DO 
    156155       
    157       ALLOCATE( zsnd(SUM(icounts)), zrcv(SUM(icountr)) ) 
     156      ! Allocate buffer arrays to be sent/received if needed 
     157      iszS = SUM(iszall, mask = llsend)                             ! send buffer size 
     158      IF( ALLOCATED(BUFFSND) ) THEN 
     159         IF( SIZE(BUFFSND) < iszS )    DEALLOCATE(BUFFSND)          ! send buffer is too small 
     160      ENDIF 
     161      IF( .NOT. ALLOCATED(BUFFSND) )   ALLOCATE( BUFFSND(iszS) ) 
     162      iszR = SUM(iszall, mask = llrecv)                             ! recv buffer size 
     163      IF( ALLOCATED(BUFFRCV) ) THEN 
     164         IF( SIZE(BUFFRCV) < iszR )    DEALLOCATE(BUFFRCV)          ! recv buffer is too small 
     165      ENDIF 
     166      IF( .NOT. ALLOCATED(BUFFRCV) )   ALLOCATE( BUFFRCV(iszR) ) 
    158167 
    159168      ! fill sending buffer with ptab(jf)%pt4d 
     
    164173            ishtj = ishtSj(jn) 
    165174            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn) 
    166                zsnd(idx) = ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) 
     175               BUFFSND(idx) = ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) 
    167176               idx = idx + 1 
    168177            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     
    175184      ! 
    176185      IF( ln_timing ) CALL tic_tac(.TRUE.) 
    177       CALL mpi_neighbor_alltoallv (zsnd, icounts, idispls, MPI_TYPE, zrcv, icountr, idisplr, MPI_TYPE, impi_nc, ierr) 
     186      CALL mpi_neighbor_alltoallv (BUFFSND, iScnt, iSdpl, MPI_TYPE, BUFFRCV, iRcnt, iRdpl, MPI_TYPE, impi_nc, ierr) 
    178187      IF( ln_timing ) CALL tic_tac(.FALSE.) 
    179188      ! 
     
    190199         CASE ( jpfillmpi   )                 ! fill with data received by MPI 
    191200            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn) 
    192                ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = zrcv(idx) 
     201               ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = BUFFRCV(idx) 
    193202               idx = idx + 1 
    194203            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     
    212221      END DO 
    213222 
    214       DEALLOCATE( icounts, icountr, idispls, idisplr, zsnd, zrcv ) 
     223      DEALLOCATE( iScnt, iRcnt, iSdpl, iRdpl ) 
     224      IF( iszS > jpi*jpj )   DEALLOCATE(BUFFSND)                    ! blocking Send -> can directly deallocate 
     225      IF( iszR > jpi*jpj )   DEALLOCATE(BUFFRCV)                    ! blocking Recv -> can directly deallocate 
    215226 
    216227      ! potential "indirect self-periodicity" for the corners 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/LBC/lbc_lnk_pt2pt_generic.h90

    r14366 r14367  
    1  
     1   
    22   SUBROUTINE lbc_lnk_pt2pt_/**/PRECISION( cdname, ptab, cd_nat, psgn, kfld, kfillmode, pfillval, khls, lsend, lrecv, ld4only ) 
    33      CHARACTER(len=*)              , INTENT(in   ) ::   cdname      ! name of the calling subroutine 
     
    1818      INTEGER  ::   ishti, ishtj, ishti2, ishtj2 
    1919      INTEGER  ::   ifill_nfd, icomm, ierr 
    20       INTEGER  ::   ihls, idxs, idxr 
     20      INTEGER  ::   ihls, idxs, idxr, iszS, iszR 
    2121      INTEGER, DIMENSION(4)  ::   iwewe, issnn 
    2222      INTEGER, DIMENSION(8)  ::   isizei, ishtSi, ishtRi, ishtPi 
     
    2626      INTEGER, DIMENSION(8)  ::   iStag, iRtag     ! Send and Recv mpi_tag id 
    2727      REAL(PRECISION) ::   zland 
    28       REAL(PRECISION), DIMENSION(:), ALLOCATABLE  ::   zsnd, zrcv          ! halos arrays 
    2928      LOGICAL, DIMENSION(8)  ::   llsend, llrecv 
    3029      LOGICAL  ::   ll4only                                        ! default: 8 neighbourgs 
     
    137136      ! -------------------------------- ! 
    138137      ! 
    139       ireq(:) = MPI_REQUEST_NULL             ! default definition when no communication is done. understood by mpi_waitall 
    140138      iStag = (/ 1, 2, 3, 4, 5, 6, 7, 8 /)   ! any value but each one must be different 
    141139      ! define iRtag with the corresponding iStag, e.g. data received at west where sent at east. 
     
    153151      END DO 
    154152 
    155       ! Allocate local temporary arrays to be sent/received. 
    156       ALLOCATE( zsnd( SUM(iszall, mask = llsend) ), zrcv( SUM(iszall, mask = llrecv) ) ) 
     153      ! Allocate buffer arrays to be sent/received if needed 
     154      iszS = SUM(iszall, mask = llsend)                             ! send buffer size 
     155      IF( ALLOCATED(BUFFSND) ) THEN 
     156         CALL mpi_waitall(8, nreq_p2p, MPI_STATUSES_IGNORE, ierr)   ! wait for Isend from the PREVIOUS call 
     157         IF( SIZE(BUFFSND) < iszS )    DEALLOCATE(BUFFSND)          ! send buffer is too small 
     158      ENDIF 
     159      IF( .NOT. ALLOCATED(BUFFSND) )   ALLOCATE( BUFFSND(iszS) ) 
     160      iszR = SUM(iszall, mask = llrecv)                             ! recv buffer size 
     161      IF( ALLOCATED(BUFFRCV) ) THEN 
     162         IF( SIZE(BUFFRCV) < iszR )    DEALLOCATE(BUFFRCV)          ! recv buffer is too small 
     163      ENDIF 
     164      IF( .NOT. ALLOCATED(BUFFRCV) )   ALLOCATE( BUFFRCV(iszR) ) 
     165      ! 
     166      ! default definition when no communication is done. understood by mpi_waitall 
     167      nreq_p2p(:) = MPI_REQUEST_NULL   ! WARNING: Must be done after the call to mpi_waitall just above 
    157168      ! 
    158169      ! ----------------------------------------------- ! 
     
    165176            ishtj = ishtSj(jn) 
    166177            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn) 
    167                zsnd(idxs) = ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) 
     178               BUFFSND(idxs) = ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) 
    168179               idxs = idxs + 1 
    169180            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     
    171182            IF( ln_timing ) CALL tic_tac(.TRUE.) 
    172183            ! non-blocking send of the west/east side using local buffer 
    173             CALL MPI_ISEND( zsnd(ishtS(jn)+1), iszall(jn), MPI_TYPE, mpiSnei(ihls,jn), iStag(jn), icomm, ireq(jn), ierr ) 
     184            CALL MPI_ISEND( BUFFSND(ishtS(jn)+1), iszall(jn), MPI_TYPE, mpiSnei(ihls,jn), iStag(jn), icomm, nreq_p2p(jn), ierr ) 
    174185            IF( ln_timing ) CALL tic_tac(.FALSE.) 
    175186#endif 
     
    190201            IF( ln_timing ) CALL tic_tac(.TRUE.) 
    191202            !                                 ! blocking receive of the west/east halo in local temporary arrays 
    192             CALL MPI_RECV(  zrcv(ishtR(jn)+1), iszall(jn), MPI_TYPE, mpiRnei(ihls,jn), iRtag(jn), icomm, MPI_STATUS_IGNORE, ierr ) 
    193             IF( ln_timing ) CALL tic_tac(.FALSE.) 
    194 #endif 
    195             DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn) 
    196                ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = zrcv(idxr) 
     203            CALL MPI_RECV( BUFFRCV(ishtR(jn)+1), iszall(jn), MPI_TYPE, mpiRnei(ihls,jn), iRtag(jn), icomm, MPI_STATUS_IGNORE, ierr ) 
     204            IF( ln_timing ) CALL tic_tac(.FALSE.) 
     205#endif 
     206            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn) 
     207               ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = BUFFRCV(idxr) 
    197208               idxr = idxr + 1 
    198209            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     
    237248            ishtj = ishtSj(jn) 
    238249            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn) 
    239                zsnd(idxs) = ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) 
     250               BUFFSND(idxs) = ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) 
    240251               idxs = idxs + 1 
    241252            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     
    243254            IF( ln_timing ) CALL tic_tac(.TRUE.) 
    244255            ! non-blocking send of the south/north side using local buffer 
    245             CALL MPI_ISEND( zsnd(ishtS(jn)+1), iszall(jn), MPI_TYPE, mpiSnei(ihls,jn), iStag(jn), icomm, ireq(jn), ierr ) 
     256            CALL MPI_ISEND( BUFFSND(ishtS(jn)+1), iszall(jn), MPI_TYPE, mpiSnei(ihls,jn), iStag(jn), icomm, nreq_p2p(jn), ierr ) 
    246257            IF( ln_timing ) CALL tic_tac(.FALSE.) 
    247258#endif 
     
    262273            IF( ln_timing ) CALL tic_tac(.TRUE.) 
    263274            !                                 ! blocking receive of the south/north halo in local temporary arrays 
    264             CALL MPI_RECV(  zrcv(ishtR(jn)+1), iszall(jn), MPI_TYPE, mpiRnei(ihls,jn), iRtag(jn), icomm, MPI_STATUS_IGNORE, ierr ) 
    265             IF( ln_timing ) CALL tic_tac(.FALSE.) 
    266 #endif 
    267             DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn) 
    268                ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = zrcv(idxr) 
     275            CALL MPI_RECV( BUFFRCV(ishtR(jn)+1), iszall(jn), MPI_TYPE, mpiRnei(ihls,jn), iRtag(jn), icomm, MPI_STATUS_IGNORE, ierr ) 
     276            IF( ln_timing ) CALL tic_tac(.FALSE.) 
     277#endif 
     278            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn) 
     279               ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = BUFFRCV(idxr) 
    269280               idxr = idxr + 1 
    270281            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     
    298309            ishtj = ishtSj(jn) 
    299310            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn) 
    300                zsnd(idxs) = ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) 
     311               BUFFSND(idxs) = ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) 
    301312               idxs = idxs + 1 
    302313            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     
    304315            IF( ln_timing ) CALL tic_tac(.TRUE.) 
    305316            ! non-blocking send of the corners using local buffer 
    306             CALL MPI_ISEND( zsnd(ishtS(jn)+1), iszall(jn), MPI_TYPE, mpiSnei(ihls,jn), iStag(jn), icomm, ireq(jn), ierr ) 
     317            CALL MPI_ISEND( BUFFSND(ishtS(jn)+1), iszall(jn), MPI_TYPE, mpiSnei(ihls,jn), iStag(jn), icomm, nreq_p2p(jn), ierr ) 
    307318            IF( ln_timing ) CALL tic_tac(.FALSE.) 
    308319#endif 
     
    314325            IF( ln_timing ) CALL tic_tac(.TRUE.) 
    315326            ! blocking receive of the corner halo in local temporary arrays 
    316             CALL MPI_RECV(  zrcv(ishtR(jn)+1), iszall(jn), MPI_TYPE, mpiRnei(ihls,jn), iRtag(jn), icomm, MPI_STATUS_IGNORE, ierr ) 
     327            CALL MPI_RECV( BUFFRCV(ishtR(jn)+1), iszall(jn), MPI_TYPE, mpiRnei(ihls,jn), iRtag(jn), icomm, MPI_STATUS_IGNORE, ierr ) 
    317328            IF( ln_timing ) CALL tic_tac(.FALSE.) 
    318329#endif 
     
    320331            ishtj = ishtRj(jn) 
    321332            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn) 
    322                ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = zrcv(idxr) 
     333               ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = BUFFRCV(idxr) 
    323334               idxr = idxr + 1 
    324335            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO 
     
    328339      ! -------------------------------------------- ! 
    329340      !     9. deallocate local temporary arrays     ! 
     341      !        if they areg larger than jpi*jpj      !  <- arbitrary max size... 
    330342      ! -------------------------------------------- ! 
    331343      ! 
    332       CALL mpi_waitall(8, ireq, MPI_STATUSES_IGNORE, ierr) 
    333       DEALLOCATE( zsnd, zrcv ) 
     344      IF( iszR > jpi*jpj )   DEALLOCATE(BUFFRCV)                    ! blocking receive -> can directly deallocate 
     345      IF( iszS > jpi*jpj ) THEN 
     346         CALL mpi_waitall(8, nreq_p2p, MPI_STATUSES_IGNORE, ierr)   ! must wait before deallocate send buffer 
     347         DEALLOCATE(BUFFSND) 
     348      ENDIF 
    334349      ! 
    335350   END SUBROUTINE lbc_lnk_pt2pt_/**/PRECISION 
  • NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/LBC/lbclnk.F90

    r14366 r14367  
    5050   PUBLIC   lbc_lnk_icb        ! iceberg lateral boundary conditions 
    5151 
     52   REAL(dp), DIMENSION(:), ALLOCATABLE ::   buffsnd_dp, buffrcv_dp   ! MPI send/recv buffers 
     53   REAL(sp), DIMENSION(:), ALLOCATABLE ::   buffsnd_sp, buffrcv_sp   !  
     54   INTEGER,  DIMENSION(8)              ::   nreq_p2p                 ! request id for MPI_Isend in point-2-point communication 
     55    
    5256   !! * Substitutions 
    5357   !!#  include "do_loop_substitute.h90" 
     
    126130#define PRECISION sp 
    127131#  define MPI_TYPE MPI_REAL 
     132#  define BUFFSND buffsnd_sp 
     133#  define BUFFRCV buffrcv_sp 
    128134#  include "lbc_lnk_pt2pt_generic.h90" 
    129135#  include "lbc_lnk_neicoll_generic.h90" 
    130136#  undef MPI_TYPE 
     137#  undef BUFFSND 
     138#  undef BUFFRCV 
    131139#undef PRECISION 
    132140   !! 
     
    135143#define PRECISION dp 
    136144#  define MPI_TYPE MPI_DOUBLE_PRECISION 
     145#  define BUFFSND buffsnd_dp 
     146#  define BUFFRCV buffrcv_dp 
    137147#  include "lbc_lnk_pt2pt_generic.h90" 
    138148#  include "lbc_lnk_neicoll_generic.h90" 
    139149#  undef MPI_TYPE 
     150#  undef BUFFSND 
     151#  undef BUFFRCV 
    140152#undef PRECISION 
    141153 
Note: See TracChangeset for help on using the changeset viewer.