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.
lbc_lnk_neicoll_generic.h90 in NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/LBC – NEMO

source: NEMO/branches/2021/dev_r14312_MPI_Interface/src/OCE/LBC/lbc_lnk_neicoll_generic.h90 @ 14349

Last change on this file since 14349 was 14349, checked in by smasson, 3 years ago

dev_r14312_MPI_Interface: further simplifications of lbclk and lbcnfd, #2598

File size: 12.9 KB
Line 
1
2   SUBROUTINE lbc_lnk_neicoll_/**/PRECISION( cdname, ptab, cd_nat, psgn, kfld, kfillmode, pfillval, lsend, lrecv, ncsten )
3      CHARACTER(len=*)              , INTENT(in   ) ::   cdname      ! name of the calling subroutine
4      TYPE(PTR_4d_/**/PRECISION),  DIMENSION(:), INTENT(inout) ::   ptab        ! pointer of arrays on which apply the b.c.
5      CHARACTER(len=1), DIMENSION(:), INTENT(in   ) ::   cd_nat      ! nature of array grid-points
6      REAL(PRECISION),  DIMENSION(:), INTENT(in   ) ::   psgn        ! sign used across the north fold boundary
7      INTEGER                       , INTENT(in   ) ::   kfld        ! number of pt3d arrays
8      INTEGER ,             OPTIONAL, INTENT(in   ) ::   kfillmode   ! filling method for halo over land (default = constant)
9      REAL(PRECISION),      OPTIONAL, INTENT(in   ) ::   pfillval    ! background value (used at closed boundaries)
10      LOGICAL, DIMENSION(4),OPTIONAL, INTENT(in   ) ::   lsend, lrecv  ! communication with other 4 proc
11      LOGICAL,              OPTIONAL, INTENT(in   ) ::   ncsten      ! 5-point or 9-point stencil
12      !
13      INTEGER  ::   ji, jj, jk, jl, jf, jn      ! dummy loop indices
14      INTEGER  ::   ipk, ipl, ipf                                     ! dimension of the input array
15      INTEGER  ::   ip0i, ip1i, im0i, im1i
16      INTEGER  ::   ip0j, ip1j, im0j, im1j
17      INTEGER  ::   ishti, ishtj, ishti2, ishtj2
18      INTEGER  ::   iszs, iszr
19      INTEGER  ::   ierr
20      INTEGER  ::   idx
21      INTEGER  ::   impi_nc
22      INTEGER  ::   ifill_nfd
23      INTEGER, DIMENSION(4)  ::   iwewe, issnn
24      INTEGER, DIMENSION(8)  ::   isizei, ishtsi, ishtri, ishtpi
25      INTEGER, DIMENSION(8)  ::   isizej, ishtsj, ishtrj, ishtpj
26      INTEGER, DIMENSION(8)  ::   ifill, iszall
27      INTEGER, DIMENSION(:), ALLOCATABLE  ::   icounts, icountr    ! number of elements to be sent/received
28      INTEGER, DIMENSION(:), ALLOCATABLE  ::   idispls, idisplr    ! displacement in halos arrays
29      LOGICAL, DIMENSION(8)  ::   llsend, llrecv
30      REAL(PRECISION) ::   zland
31      REAL(PRECISION), DIMENSION(:), ALLOCATABLE  ::   zsnd, zrcv          ! halos arrays
32      LOGICAL  ::   llncall                                          ! default: 9-point stencil
33      LOGICAL  ::   ll_IdoNFold
34      !!----------------------------------------------------------------------
35      !
36      ! ----------------------------------------- !
37      !     1. local variables initialization     !
38      ! ----------------------------------------- !
39      !
40      ipk = SIZE(ptab(1)%pt4d,3)
41      ipl = SIZE(ptab(1)%pt4d,4)
42      ipf = kfld
43      !
44      IF( narea == 1 .AND. numcom == -1 ) CALL mpp_report( cdname, ipk, ipl, ipf, ld_lbc = .TRUE. )
45      !
46      ! take care of optional parameters
47      !
48      llncall = .TRUE.
49      IF( PRESENT(ncsten) ) llncall = ncsten
50      !
51      impi_nc = mpi_nc_com4
52      IF(llncall)   impi_nc = mpi_nc_com8
53      !
54      zland = 0._wp                                     ! land filling value: zero by default
55      IF( PRESENT( pfillval ) )   zland = pfillval      ! set land value
56      !
57      ! define llsend and llrecv: logicals which say if mpi-neibourgs for send or receive exist or not.
58      IF     ( PRESENT(lsend) .AND. PRESENT(lrecv) ) THEN   ! localy defined neighbourgs
59         CALL ctl_stop( 'STOP', 'mpp_nc_generic+BDY not yet implemented')
60!!$         ---> llsend(:) = lsend(:)   ;   llrecv(:) = lrecv(:) ???
61      ELSE IF( PRESENT(lsend) .OR.  PRESENT(lrecv) ) THEN
62         WRITE(ctmp1,*) ' Routine ', cdname, '  is calling lbc_lnk with only one of the two arguments lsend or lrecv'
63         CALL ctl_stop( 'STOP', ctmp1 )
64      ELSE                                                  ! default neighbours
65         llsend(:) = mpinei(:) >= 0
66         IF( .NOT. llncall )   llsend(5:8) = .FALSE.        ! exclude corners
67         llrecv(:) = llsend(:)
68      END IF
69      !
70      ! define ifill: which method should be used to fill each parts (sides+corners) of the halos
71      ! default definition
72      DO jn = 1, 8
73         IF(             llrecv(jn) ) THEN   ;   ifill(jn) = jpfillmpi    ! with an mpi communication
74         ELSEIF(    l_SelfPerio(jn) ) THEN   ;   ifill(jn) = jpfillperio  ! with self-periodicity
75         ELSEIF( PRESENT(kfillmode) ) THEN   ;   ifill(jn) = kfillmode    ! localy defined
76         ELSE                                ;   ifill(jn) = jpfillcst    ! constant value (zland)
77         END IF
78      END DO
79      ! take care of "indirect self-periodicity" for the corners
80      DO jn = 5, 8
81         IF(.NOT.l_SelfPerio(jn) .AND. l_SelfPerio(jpwe))   ifill(jn) = jpfillnothing   ! no bi-perio but ew-perio: do corners later
82         IF(.NOT.l_SelfPerio(jn) .AND. l_SelfPerio(jpso))   ifill(jn) = jpfillnothing   ! no bi-perio but ns-perio: do corners later
83      END DO
84      ! north fold treatment
85      ll_IdoNFold = l_IdoNFold .AND. ifill(jpno) /= jpfillnothing
86      IF( ll_IdoNFold ) THEN
87         ifill_nfd = ifill(jpno)             ! if we are here, this means llrecv(jpno) = .false. and l_SelfPerio(jpno) = .false.
88         ifill( (/jpno/) ) = jpfillnothing   ! we do north fold -> do nothing for northern halo
89      ENDIF
90     
91      ! We first define the localization and size of the parts of the array that will be sent (s), received (r)
92      ! or used for periodocity (p). The localization is defined as "the bottom left corner - 1" in i and j directions.
93      ! This is a shift that will be applied later in the do loops to pick-up the appropriate part of the array
94      !                    !                       ________________________
95      ip0i =          0    !          im0j = inner |__|________________|__|
96      ip1i =      nn_hls   !   im1j = inner - halo |  |__|__________|__|  |
97      im1i = Nie0-nn_hls   !                       |  |  |          |  |  |
98      im0i = Nie0          !                       |  |  |          |  |  |
99      ip0j =          0    !                       |  |  |          |  |  |
100      ip1j =      nn_hls   !                       |  |__|__________|__|  |
101      im1j = Nje0-nn_hls   !           ip1j = halo |__|__|__________|__|__|
102      im0j = Nje0          !              ip0j = 0 |__|________________|__|
103      !                    !                    ip0i ip1i        im1i im0i
104      !
105      iwewe(:) = (/ jpwe,jpea,jpwe,jpea /)   ;   issnn(:) = (/ jpso,jpso,jpno,jpno /)
106      !     sides:       west    east   south   north      ;       corners: so-we, so-ea, no-we, no-ea
107      isizei(1:4) = (/ nn_hls, nn_hls,   Ni_0,   Ni_0 /)   ;   isizei(5:8) = nn_hls            ! i- count
108      isizej(1:4) = (/   Nj_0,   Nj_0, nn_hls, nn_hls /)   ;   isizej(5:8) = nn_hls            ! j- count
109      ishtsi(1:4) = (/   ip1i,   im1i,   ip1i,   ip1i /)   ;   ishtsi(5:8) = ishtsi( iwewe )   ! i- shift send data
110      ishtsj(1:4) = (/   ip1j,   ip1j,   ip1j,   im1j /)   ;   ishtsj(5:8) = ishtsj( issnn )   ! j- shift send data
111      ishtri(1:4) = (/   ip0i,   im0i,   ip1i,   ip1i /)   ;   ishtri(5:8) = ishtri( iwewe )   ! i- shift received data location
112      ishtrj(1:4) = (/   ip1j,   ip1j,   ip0j,   im0j /)   ;   ishtrj(5:8) = ishtrj( issnn )   ! j- shift received data location
113      ishtpi(1:4) = (/   im1i,   ip1i,   ip1i,   ip1i /)   ;   ishtpi(5:8) = ishtpi( iwewe )   ! i- shift data used for periodicity
114      ishtpj(1:4) = (/   ip1j,   ip1j,   im1j,   ip1j /)   ;   ishtpj(5:8) = ishtpj( issnn )   ! j- shift data used for periodicity
115      !
116      ! -------------------------------- !
117      !     2. Prepare MPI exchanges     !
118      ! -------------------------------- !
119      !
120      ! Allocate local temporary arrays to be sent/received.
121      iszs = COUNT( llsend )
122      iszr = COUNT( llrecv )
123      ALLOCATE( icounts(iszs), icountr(iszr), idispls(iszs), idisplr(iszr) )   ! ok if iszs = 0 or iszr = 0
124      iszall(:) = isizei(:) * isizej(:) * ipk * ipl * ipf
125      icounts(:) = PACK( iszall, mask = llsend )                                       ! ok if mask = .false.
126      icountr(:) = PACK( iszall, mask = llrecv )
127      idispls(1) = 0
128      DO jn = 2,iszs
129         idispls(jn) = idispls(jn-1) + icounts(jn-1)   ! with _alltoallv: in units of sendtype
130      END DO
131      idisplr(1) = 0
132      DO jn = 2,iszr
133         idisplr(jn) = idisplr(jn-1) + icountr(jn-1)   ! with _alltoallv: in units of sendtype
134      END DO
135     
136      ALLOCATE( zsnd(SUM(icounts)), zrcv(SUM(icountr)) )
137
138      ! fill sending buffer with ptab(jf)%pt4d
139      idx = 1
140      DO jn = 1, 8
141         IF( llsend(jn) ) THEN
142            ishti = ishtsi(jn)
143            ishtj = ishtsj(jn)
144            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn)
145               zsnd(idx) = ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl)
146               idx = idx + 1
147            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO
148         END IF
149      END DO
150      !
151      ! ------------------------------------------------ !
152      !     3. Do all MPI exchanges in 1 unique call     !
153      ! ------------------------------------------------ !
154      !
155      IF( ln_timing ) CALL tic_tac(.TRUE.)
156      CALL mpi_neighbor_alltoallv (zsnd, icounts, idispls, MPI_TYPE, zrcv, icountr, idisplr, MPI_TYPE, impi_nc, ierr)
157      IF( ln_timing ) CALL tic_tac(.FALSE.)
158      !
159      ! ------------------------- !
160      !     4. Fill all halos     !
161      ! ------------------------- !
162      !
163      idx = 1
164      DO jn = 1, 8
165         ishti = ishtri(jn)
166         ishtj = ishtrj(jn)
167         SELECT CASE ( ifill(jn) )
168         CASE ( jpfillnothing )               ! no filling
169         CASE ( jpfillmpi   )                 ! fill with data received by MPI
170            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn)
171               ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = zrcv(idx)
172               idx = idx + 1
173            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO
174         CASE ( jpfillperio )                 ! use periodicity
175            ishti2 = ishtpi(jn)
176            ishtj2 = ishtpj(jn)
177            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn)
178               ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = ptab(jf)%pt4d(ishti2+ji,ishtj2+jj,jk,jl)
179            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO
180         CASE ( jpfillcopy  )                 ! filling with inner domain values
181            ishti2 = ishtsi(jn)
182            ishtj2 = ishtsj(jn)
183            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn)
184               ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = ptab(jf)%pt4d(ishti2+ji,ishtj2+jj,jk,jl)
185            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO
186         CASE ( jpfillcst   )                 ! filling with constant value
187            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn)
188               ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = zland
189            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO
190         END SELECT
191      END DO
192
193      DEALLOCATE( icounts, icountr, idispls, idisplr, zsnd, zrcv )
194
195      ! potential "indirect self-periodicity" for the corners
196      DO jn = 5, 8
197         IF( .NOT. l_SelfPerio(jn) .AND. l_SelfPerio(jpwe)  ) THEN   ! no bi-perio but ew-perio: corners indirect definition
198            ishti  = ishtri(jn)
199            ishtj  = ishtrj(jn)
200            ishti2 = ishtpi(jn)   ! use i- shift periodicity
201            ishtj2 = ishtrj(jn)   ! use j- shift recv location: use ew-perio -> ok as filling of the south and north halos now done
202            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn)
203               ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = ptab(jf)%pt4d(ishti2+ji,ishtj2+jj,jk,jl)
204            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO
205         ENDIF
206         IF( .NOT. l_SelfPerio(jn) .AND. l_SelfPerio(jpso)  ) THEN   ! no bi-perio but ns-perio: corners indirect definition
207            ishti  = ishtri(jn)
208            ishtj  = ishtrj(jn)
209            ishti2 = ishtri(jn)   ! use i- shift recv location: use ns-perio -> ok as filling of the west and east halos now done
210            ishtj2 = ishtpj(jn)   ! use j- shift periodicity
211            DO jf = 1, ipf  ;  DO jl = 1, ipl  ;  DO jk = 1, ipk  ;  DO jj = 1,isizej(jn)  ;  DO ji = 1,isizei(jn)
212               ptab(jf)%pt4d(ishti+ji,ishtj+jj,jk,jl) = ptab(jf)%pt4d(ishti2+ji,ishtj2+jj,jk,jl)
213            END DO   ;   END DO   ;   END DO   ;   END DO   ;   END DO
214         ENDIF
215      END DO
216      !
217      ! ------------------------------- !
218      !     5. north fold treatment     !
219      ! ------------------------------- !
220      !
221      IF( ll_IdoNFold ) THEN
222         IF( jpni == 1 )  THEN   ;   CALL lbc_nfd( ptab, cd_nat, psgn                  , ipf )   ! self NFold
223         ELSE                    ;   CALL mpp_nfd( ptab, cd_nat, psgn, ifill_nfd, zland, ipf )   ! mpi  NFold
224         ENDIF
225      ENDIF
226      !
227   END SUBROUTINE lbc_lnk_neicoll_/**/PRECISION
228
Note: See TracBrowser for help on using the repository browser.