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.
lib_mpp_tam.F90 in branches/2012/dev_r3604_LEGI8_TAM/NEMOGCM/NEMO/OPATAM_SRC/LBC – NEMO

source: branches/2012/dev_r3604_LEGI8_TAM/NEMOGCM/NEMO/OPATAM_SRC/LBC/lib_mpp_tam.F90 @ 3611

Last change on this file since 3611 was 3611, checked in by pabouttier, 11 years ago

Add TAM code and ORCA2_TAM configuration - see Ticket #1007

  • Property svn:executable set to *
File size: 68.0 KB
Line 
1MODULE lib_mpp_tam
2   !!======================================================================
3   !!                       ***  MODULE  lib_mpp_tam  ***
4   !! Ocean numerics:  massively parallel processing library
5   !!=====================================================================
6   !! History :  OPA  !  1994  (M. Guyon, J. Escobar, M. Imbard)  Original code
7   !!            7.0  !  1997  (A.M. Treguier)  SHMEM additions
8   !!            8.0  !  1998  (M. Imbard, J. Escobar, L. Colombet ) SHMEM and MPI
9   !!                 !  1998  (J.M. Molines) Open boundary conditions
10   !!   NEMO     1.0  !  2003  (J.-M. Molines, G. Madec)  F90, free form
11   !!                 !  2003  (J.M. Molines) add mpp_ini_north(_3d,_2d)
12   !!             -   !  2004  (R. Bourdalle Badie)  isend option in mpi
13   !!                 !  2004  (J.M. Molines) minloc, maxloc
14   !!             -   !  2005  (G. Madec, S. Masson)  npolj=5,6 F-point & ice cases
15   !!             -   !  2005  (R. Redler) Replacement of MPI_COMM_WORLD except for MPI_Abort
16   !!             -   !  2005  (R. Benshila, G. Madec)  add extra halo case
17   !!             -   !  2008  (R. Benshila) add mpp_ini_ice
18   !!            3.2  !  2009  (R. Benshila) SHMEM suppression, north fold in lbc_nfd
19   !!            3.2  !  2009  (O. Marti)    add mpp_ini_znl
20   !!            4.0  !  2011  (G. Madec)  move ctl_ routines from in_out_manager
21   !!   NEMOTAM  2.?  !  2007  (K. Mogensen) Original code (lib_mppadj)
22   !!            3.0  !  2009  (A. Vidard) nemo v3 update
23   !!            3.2  !  2010  (A. Vidard) 3.2 version, complete rewrite
24   !!            3.4  !  2012  (P.-A. Bouttier) v3.4 update
25   !!----------------------------------------------------------------------
26
27   !!----------------------------------------------------------------------
28   !!   ctl_stop   : update momentum and tracer Kz from a tke scheme
29   !!   ctl_warn   : initialization, namelist read, and parameters control
30   !!   ctl_opn    : Open file and check if required file is available.
31   !!   get_unit    : give the index of an unused logical unit
32   !!----------------------------------------------------------------------
33#if defined key_mpp_mpi
34   !!----------------------------------------------------------------------
35   !!   'key_mpp_mpi'             MPI massively parallel processing library
36   !!----------------------------------------------------------------------
37   !!   mpp_lnk_adj       : interface (defined in lbclnk) for message passing of 2d or 3d arrays (mpp_lnk_2d, mpp_lnk_3d)
38   !!   mpp_lnk_3d_gather_adj :  Message passing manadgement for two 3D arrays
39   !!   mpp_lnk_e_adj     : interface (defined in lbclnk) for message passing of 2d array with extra halo (mpp_lnk_2d_e)
40   !!   mpp_lbc_north_adj : north fold processors gathering
41   !!   mpp_lbc_north_e_adj : variant of mpp_lbc_north for extra outer halo
42   !!----------------------------------------------------------------------
43   USE dom_oce        ! ocean space and time domain
44   USE lbcnfd_tam     ! north fold treatment
45   USE lib_mpp
46   USE in_out_manager ! I/O manager
47
48   IMPLICIT NONE
49   PRIVATE
50
51   PUBLIC   mpp_lbc_north_adj, mpp_lbc_north_e_adj
52   PUBLIC   mpp_lnk_3d_adj, mpp_lnk_3d_gather_adj, mpp_lnk_2d_adj, mpp_lnk_2d_e_adj
53   PUBLIC   lib_mpp_alloc_adj
54   PUBLIC   mpp_sum_nfd
55   !! * Interfaces
56   !! define generic interface for these routine as they are called sometimes
57   !! with scalar arguments instead of array arguments, which causes problems
58   !! for the compilation on AIX system as well as NEC and SGI. Ok on COMPACQ
59   INTERFACE mpp_lbc_north_adj
60      MODULE PROCEDURE mpp_lbc_north_3d_adj, mpp_lbc_north_2d_adj
61   END INTERFACE
62
63   INTERFACE mpp_sum_nfd
64      MODULE PROCEDURE mpp_sum_nfd_3d,mpp_sum_nfd_4d
65   END INTERFACE
66   !! ========================= !!
67   !!  MPI  variable definition !!
68   !! ========================= !!
69!$AGRIF_DO_NOT_TREAT
70#if defined key_mpp_mpi
71#include "mpif.h"
72#endif
73!$AGRIF_END_DO_NOT_TREAT
74
75   ! message passing arrays
76   REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE, SAVE ::   t4ns_ad, t4sn_ad   ! 2 x 3d for north-south & south-north
77   REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE, SAVE ::   t4ew_ad, t4we_ad   ! 2 x 3d for east-west & west-east
78   REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE, SAVE ::   t4p1_ad, t4p2_ad   ! 2 x 3d for north fold
79   REAL(wp), DIMENSION(:,:,:,:)  , ALLOCATABLE, SAVE ::   t3ns_ad, t3sn_ad   ! 3d for north-south & south-north
80   REAL(wp), DIMENSION(:,:,:,:)  , ALLOCATABLE, SAVE ::   t3ew_ad, t3we_ad   ! 3d for east-west & west-east
81   REAL(wp), DIMENSION(:,:,:,:)  , ALLOCATABLE, SAVE ::   t3p1_ad, t3p2_ad   ! 3d for north fold
82   REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   t2ns_ad, t2sn_ad   ! 2d for north-south & south-north
83   REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   t2ew_ad, t2we_ad   ! 2d for east-west & west-east
84   REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   t2p1_ad, t2p2_ad   ! 2d for north fold
85   REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   tr2ns_ad, tr2sn_ad ! 2d for north-south & south-north + extra outer halo
86   REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   tr2ew_ad, tr2we_ad ! 2d for east-west   & west-east   + extra outer halo
87
88   ! Arrays used in mpp_lbc_north_3d()
89   REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE, SAVE   ::   ztabad, znorthlocad
90   REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, SAVE   ::   znorthgloioad
91   REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE, SAVE   ::   zfoldwkad      ! Workspace for message transfers avoiding mpi_allgather
92
93   ! Arrays used in mpp_lbc_north_2d()
94   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   ztabad_2d, znorthlocad_2d
95   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE    ::   znorthgloioad_2d
96   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   zfoldwkad_2d    ! Workspace for message transfers avoiding mpi_allgather
97
98   ! Arrays used in mpp_lbc_north_e()
99   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   ztabad_e, znorthlocad_e
100   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE    ::   znorthgloioad_e
101
102   !!----------------------------------------------------------------------
103   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
104   !! $Id$
105   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
106   !!----------------------------------------------------------------------
107CONTAINS
108
109INTEGER FUNCTION lib_mpp_alloc_adj( kumout )
110      !!----------------------------------------------------------------------
111      !!              ***  routine lib_mpp_alloc  ***
112      !!----------------------------------------------------------------------
113      INTEGER, INTENT(in) ::   kumout   ! ocean.output logical unit
114      !!----------------------------------------------------------------------
115      !
116      ALLOCATE( t4ns_ad(jpi,jprecj,jpk,2,2) , t4sn_ad(jpi,jprecj,jpk,2,2) ,                                            &
117         &      t4ew_ad(jpj,jpreci,jpk,2,2) , t4we_ad(jpj,jpreci,jpk,2,2) ,                                            &
118         &      t4p1_ad(jpi,jprecj,jpk,2,2) , t4p2_ad(jpi,jprecj,jpk,2,2) ,                                            &
119         &      t3ns_ad(jpi,jprecj,jpk,2)   , t3sn_ad(jpi,jprecj,jpk,2)   ,                                            &
120         &      t3ew_ad(jpj,jpreci,jpk,2)   , t3we_ad(jpj,jpreci,jpk,2)   ,                                            &
121         &      t3p1_Ad(jpi,jprecj,jpk,2)   , t3p2_ad(jpi,jprecj,jpk,2)   ,                                            &
122         &      t2ns_ad(jpi,jprecj    ,2)   , t2sn_ad(jpi,jprecj    ,2)   ,                                            &
123         &      t2ew_ad(jpj,jpreci    ,2)   , t2we_ad(jpj,jpreci    ,2)   ,                                            &
124         &      t2p1_ad(jpi,jprecj    ,2)   , t2p2_ad(jpi,jprecj    ,2)   ,                                            &
125         !
126         &      tr2ns_ad(1-jpr2di:jpi+jpr2di,jprecj+jpr2dj,2) ,                                                     &
127         &      tr2sn_ad(1-jpr2di:jpi+jpr2di,jprecj+jpr2dj,2) ,                                                     &
128         &      tr2ew_ad(1-jpr2dj:jpj+jpr2dj,jpreci+jpr2di,2) ,                                                     &
129         &      tr2we_ad(1-jpr2dj:jpj+jpr2dj,jpreci+jpr2di,2) ,                                                     &
130         !
131         &      ztabad(jpiglo,4,jpk) , znorthlocad(jpi,4,jpk) , znorthgloioad(jpi,4,jpk,jpni) ,                        &
132         &      zfoldwkad(jpi,4,jpk) ,                                                                             &
133         !
134         &      ztabad_2d(jpiglo,4)  , znorthlocad_2d(jpi,4)  , znorthgloioad_2d(jpi,4,jpni)  ,                        &
135         &      zfoldwkad_2d(jpi,4)  ,                                                                             &
136         !
137         &      ztabad_e(jpiglo,4+2*jpr2dj) , znorthlocad_e(jpi,4+2*jpr2dj) , znorthgloioad_e(jpi,4+2*jpr2dj,jpni) ,   &
138         !
139         &      STAT=lib_mpp_alloc_adj )
140         !
141      IF( lib_mpp_alloc_adj /= 0 ) THEN
142         WRITE(kumout,cform_war)
143         WRITE(kumout,*) 'lib_mpp_alloc_adj : failed to allocate arrays'
144      ENDIF
145      !
146   END FUNCTION lib_mpp_alloc_adj
147
148   SUBROUTINE mpp_lnk_3d_adj( ptab_ad, cd_type, psgn, cd_mpp, pval )
149      !!----------------------------------------------------------------------
150      !!                  ***  routine mpp_lnk_3d_adj  ***
151      !!
152      !! ** Purpose :   Adjoint of Message passing manadgement
153      !!
154      !! ** Method  :   Use mppsend and mpprecv function for passing mask
155      !!      between processors following neighboring subdomains.
156      !!            domain parameters
157      !!                    nlci   : first dimension of the local subdomain
158      !!                    nlcj   : second dimension of the local subdomain
159      !!                    nbondi : mark for "east-west local boundary"
160      !!                    nbondj : mark for "north-south local boundary"
161      !!                    noea   : number for local neighboring processors
162      !!                    nowe   : number for local neighboring processors
163      !!                    noso   : number for local neighboring processors
164      !!                    nono   : number for local neighboring processors
165      !!
166      !! ** Action  :   ptab_ad with update value at its periphery
167      !!
168      !!----------------------------------------------------------------------
169      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptab_ad  ! 3D array on which the boundary condition is applied
170      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type  ! define the nature of ptab_ad array grid-points
171      !                                                             ! = T , U , V , F , W points
172      REAL(wp)                        , INTENT(in   ) ::   psgn     ! =-1 the sign change across the north fold boundary
173      !                                                             ! =  1. , the sign is kept
174      CHARACTER(len=3), OPTIONAL      , INTENT(in   ) ::   cd_mpp   ! fill the overlap area only
175      REAL(wp)        , OPTIONAL      , INTENT(in   ) ::   pval     ! background value (used at closed boundaries)
176      !!
177      INTEGER  ::   ji, jj, jk, jl             ! dummy loop indices
178      INTEGER  ::   imigr, iihom, ijhom        ! temporary integers
179      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
180      REAL(wp) ::   zland
181      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
182      !!----------------------------------------------------------------------
183
184      t3ns_ad = 0.0_wp ; t3sn_ad = 0.0_wp
185      t3we_ad = 0.0_wp ; t3ew_ad = 0.0_wp
186      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value
187      ELSE                         ;   zland = 0.e0      ! zero by default
188      ENDIF
189      !
190      ! 4. north fold treatment
191      ! -----------------------
192      !
193      IF( npolj /= 0 .AND. .NOT. PRESENT(cd_mpp) ) THEN
194         !
195         SELECT CASE ( jpni )
196         CASE ( 1 )     ;   CALL lbc_nfd_adj      ( ptab_ad, cd_type, psgn )   ! only 1 northern proc, no mpp
197         CASE DEFAULT   ;   CALL mpp_lbc_north_adj( ptab_ad, cd_type, psgn )   ! for all northern procs.
198         END SELECT
199         !
200      ENDIF
201      !
202      !
203      ! 3. North and south directions
204      ! -----------------------------
205      ! always closed : we play only with the neigbours
206      !
207      !                           ! Write Dirichlet lateral conditions
208      ijhom = nlcj-jprecj
209      !
210      SELECT CASE ( nbondj )
211      CASE ( -1 )
212         DO jl = 1, jprecj
213            t3ns_ad(:,jl,:,2) = t3ns_ad(:,jl,:,2) + ptab_ad(:,ijhom+jl,:)
214            ptab_ad(:,ijhom+jl,:) = 0.0_wp
215         END DO
216      CASE ( 0 )
217         DO jl = 1, jprecj
218            t3ns_ad(:,jl,:,2) = t3ns_ad(:,jl,:,2) + ptab_ad(:,ijhom+jl,:)
219            ptab_ad(:,ijhom+jl,:) = 0.0_wp
220            t3sn_ad(:,jl,:,2) = t3sn_ad(:,jl,:,2) + ptab_ad(:,jl      ,:)
221            ptab_ad(:,jl      ,:) = 0.0_wp
222         END DO
223      CASE ( 1 )
224         DO jl = 1, jprecj
225            t3sn_ad(:,jl,:,2) = t3sn_ad(:,jl,:,2) + ptab_ad(:,jl,:)
226            ptab_ad(:,jl,:) = 0.0_wp
227         END DO
228      END SELECT
229      !
230      !                           ! Migrations
231      imigr = jprecj * jpi * jpk
232      !
233      SELECT CASE ( nbondj )
234      CASE ( -1 )
235         CALL mppsend( 4, t3ns_ad(1,1,1,2), imigr, nono, ml_req1 )
236         CALL mpprecv( 3, t3sn_ad(1,1,1,1), imigr, nono )
237         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
238      CASE ( 0 )
239         CALL mppsend( 3, t3sn_ad(1,1,1,2), imigr, noso, ml_req1 )
240         CALL mppsend( 4, t3ns_ad(1,1,1,2), imigr, nono, ml_req2 )
241         CALL mpprecv( 3, t3sn_ad(1,1,1,1), imigr, nono )
242         CALL mpprecv( 4, t3ns_ad(1,1,1,1), imigr, noso )
243         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
244         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
245      CASE ( 1 )
246         CALL mppsend( 3, t3sn_ad(1,1,1,2), imigr, noso, ml_req1 )
247         CALL mpprecv( 4, t3ns_ad(1,1,1,1), imigr, noso )
248         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
249      END SELECT
250      !
251      !
252      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
253         ijhom = nlcj-nrecj
254         DO jl = 1, jprecj
255            ptab_ad(:,jprecj+jl,:) = ptab_ad(:,jprecj+jl,:) + t3ns_ad(:,jl,:,1)
256            t3ns_ad(:,jl,:,1) = 0.0_wp
257            ptab_ad(:,ijhom +jl,:) = ptab_ad(:,ijhom +jl,:) + t3sn_ad(:,jl,:,1)
258            t3sn_ad(:,jl,:,1) = 0.0_wp
259         END DO
260      ENDIF
261      !
262      ! 2. East and west directions exchange
263      ! ------------------------------------
264      !                           ! Write Dirichlet lateral conditions
265      iihom = nlci-jpreci
266      !
267      SELECT CASE ( nbondi )
268      CASE ( -1 )
269         DO jl = 1, jpreci
270            t3ew_ad(:,jl,:,2)     = t3ew_ad(:,jl,:,2) + ptab_ad(iihom+jl,:,:)
271            ptab_ad(iihom+jl,:,:) = 0.0_wp
272         END DO
273      CASE ( 0 )
274         DO jl = 1, jpreci
275            t3ew_ad(:,jl,:,2)     = t3ew_ad(:,jl,:,2) + ptab_ad(iihom+jl,:,:)
276            ptab_ad(iihom+jl,:,:) = 0.0_wp
277            t3we_ad(:,jl,:,2)     = t3we_ad(:,jl,:,2) + ptab_ad(jl      ,:,:)
278            ptab_ad(jl      ,:,:) = 0.0_wp
279         END DO
280      CASE ( 1 )
281         DO jl = 1, jpreci
282            t3we_ad(:,jl,:,2)     = t3we_ad(:,jl,:,2) + ptab_ad(jl      ,:,:)
283            ptab_ad(jl      ,:,:) = 0.0_wp
284         END DO
285      END SELECT
286      !
287      !                           ! Migrations
288      imigr = jpreci * jpj * jpk
289      !
290      SELECT CASE ( nbondi )
291      CASE ( -1 )
292         CALL mppsend( 2, t3ew_ad(1,1,1,2), imigr, noea, ml_req1 )
293         CALL mpprecv( 1, t3we_ad(1,1,1,1), imigr, noea )
294         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
295      CASE ( 0 )
296         CALL mppsend( 1, t3we_ad(1,1,1,2), imigr, nowe, ml_req1 )
297         CALL mppsend( 2, t3ew_ad(1,1,1,2), imigr, noea, ml_req2 )
298         CALL mpprecv( 1, t3we_ad(1,1,1,1), imigr, noea )
299         CALL mpprecv( 2, t3ew_ad(1,1,1,1), imigr, nowe )
300         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
301         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
302      CASE ( 1 )
303         CALL mppsend( 1, t3we_ad(1,1,1,2), imigr, nowe, ml_req1 )
304         CALL mpprecv( 2, t3ew_ad(1,1,1,1), imigr, nowe )
305         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
306      END SELECT
307      !
308      ! we play with the neigbours AND the row number because of the periodicity
309      !
310      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
311      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
312         iihom = nlci-nreci
313         DO jl = 1, jpreci
314            ptab_ad(iihom +jl,:,:) = ptab_ad(iihom +jl,:,:) + t3we_ad(:,jl,:,1)
315            t3we_ad(:,jl,:,1) = 0.0_wp
316            ptab_ad(jpreci+jl,:,:) = ptab_ad(jpreci+jl,:,:) + t3ew_ad(:,jl,:,1)
317            t3ew_ad(:,jl,:,1) = 0.0_wp
318         END DO
319      END SELECT
320      !
321      ! 1. standard boundary treatment
322      ! ------------------------------
323      IF( PRESENT( cd_mpp ) ) THEN      ! only fill added line/raw with existing values
324         !
325         ! WARNING ptab_ad is defined only between nld and nle
326         DO jk = 1, jpk
327            DO ji = nlci+1, jpi                 ! added column(s) (full)
328               ptab_ad(nlei,      nlej   ,jk) = ptab_ad(nlei,nlej     ,jk) + SUM(ptab_ad(ji,nlej+1:jpj   ,jk))
329               ptab_ad(ji  ,nlej+1:jpj   ,jk) = 0.0_wp
330               ptab_ad(nlei,nldj         ,jk) = ptab_ad(nlei,nldj     ,jk) + SUM(ptab_ad(ji,1     :nldj-1,jk))
331               ptab_ad(ji  ,1     :nldj-1,jk) = 0.0_wp
332               ptab_ad(nlei,nldj  :nlej  ,jk) = ptab_ad(nlei,nldj:nlej,jk) + ptab_ad(ji,nldj  :nlej  ,jk)
333               ptab_ad(ji  ,nldj  :nlej  ,jk) = 0.0_wp
334            END DO
335            DO jj = nlcj+1, jpj                 ! added line(s)   (inner only)
336               ptab_ad(nlei         ,nlej,jk) = ptab_ad(nlei     ,nlej,jk) + SUM(ptab_ad(nlei+1:nlci  ,jj,jk))
337               ptab_ad(nlei+1:nlci  ,jj  ,jk) = 0.0_wp
338               ptab_ad(nldi         ,nlej,jk) = ptab_ad(nldi     ,nlej,jk) + SUM(ptab_ad(1     :nldi-1,jj,jk))
339               ptab_ad(1     :nldi-1,jj  ,jk) = 0.0_wp
340               ptab_ad(nldi  :nlei  ,nlej,jk) = ptab_ad(nldi:nlei,nlej,jk) + ptab_ad(nldi  :nlei  ,jj,jk)
341               ptab_ad(nldi  :nlei  ,jj  ,jk) = 0.0_wp
342            END DO
343         END DO
344         !
345      ELSE                              ! standard close or cyclic treatment
346      !
347      !                                   ! North-South boundaries (always closed)
348                                   ptab_ad(:,nlcj-jprecj+1:jpj   ,:) = 0.0_wp       ! north
349      IF( .NOT. cd_type == 'F' )   ptab_ad(:,     1       :jprecj,:) = 0.0_wp       ! south except F-point
350      !                                   ! East-West boundaries
351      !                                        !* Cyclic east-west
352      IF( nbondi == 2 .AND. (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
353         ptab_ad( 2   ,:,:) = ptab_ad(  2  ,:,:) + ptab_ad(jpi,:,:)
354         ptab_ad(jpi  ,:,:) = 0.0_wp
355         ptab_ad(jpim1,:,:) = ptab_ad(jpim1,:,:) + ptab_ad( 1 ,:,:)
356         ptab_ad( 1   ,:,:) = 0.0_wp
357      ELSE                                     !* closed
358         IF( .NOT. cd_type == 'F' )   ptab_ad(     1       :jpreci,:,:) = 0.0_wp    ! south except F-point
359                                      ptab_ad(nlci-jpreci+1:jpi   ,:,:) = 0.0_wp    ! north
360      ENDIF
361      !
362   ENDIF
363      !
364   END SUBROUTINE mpp_lnk_3d_adj
365
366
367   SUBROUTINE mpp_lnk_2d_adj( pt2d_ad, cd_type, psgn, cd_mpp, pval )
368      !!----------------------------------------------------------------------
369      !!                  ***  routine mpp_lnk_2d_adj  ***
370      !!
371      !! ** Purpose :   Adjoint of Message passing manadgement for 2d array
372      !!
373      !! ** Method  :   Use mppsend and mpprecv function for passing mask
374      !!      between processors following neighboring subdomains.
375      !!            domain parameters
376      !!                    nlci   : first dimension of the local subdomain
377      !!                    nlcj   : second dimension of the local subdomain
378      !!                    nbondi : mark for "east-west local boundary"
379      !!                    nbondj : mark for "north-south local boundary"
380      !!                    noea   : number for local neighboring processors
381      !!                    nowe   : number for local neighboring processors
382      !!                    noso   : number for local neighboring processors
383      !!                    nono   : number for local neighboring processors
384      !!
385      !!----------------------------------------------------------------------
386      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   pt2d_ad     ! 2D array on which the boundary condition is applied
387      CHARACTER(len=1)            , INTENT(in   ) ::   cd_type  ! define the nature of ptab_ad array grid-points
388      !                                                         ! = T , U , V , F , W and I points
389      REAL(wp)                    , INTENT(in   ) ::   psgn     ! =-1 the sign change across the north fold boundary
390      !                                                         ! =  1. , the sign is kept
391      CHARACTER(len=3), OPTIONAL  , INTENT(in   ) ::   cd_mpp   ! fill the overlap area only
392      REAL(wp)        , OPTIONAL  , INTENT(in   ) ::   pval     ! background value (used at closed boundaries)
393      !!
394      INTEGER  ::   ji, jj, jl   ! dummy loop indices
395      INTEGER  ::   imigr, iihom, ijhom        ! temporary integers
396      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
397      REAL(wp) ::   zland
398      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
399      !!----------------------------------------------------------------------
400      t2ns_ad = 0.0_wp ; t2sn_ad = 0.0_wp
401      t2we_ad = 0.0_wp ; t2ew_ad = 0.0_wp
402      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value
403      ELSE                         ;   zland = 0.e0      ! zero by default
404      ENDIF
405      !4. north fold treatment
406      !-----------------------
407
408      IF( npolj /= 0 .AND. .NOT. PRESENT(cd_mpp) ) THEN
409         !
410         SELECT CASE ( jpni )
411         CASE ( 1 )
412            CALL lbc_nfd_adj      ( pt2d_ad, cd_type, psgn )   ! only 1 northern proc, no mpp
413         CASE DEFAULT
414            CALL mpp_lbc_north_adj( pt2d_ad, cd_type, psgn )   ! for all northern procs.
415         END SELECT
416         !
417      ENDIF
418
419      !3. North and south directions
420      !-----------------------------
421                                !! Write Dirichlet lateral conditions
422      ijhom = nlcj - jprecj
423      !
424      SELECT CASE ( nbondj )
425      CASE ( -1 )
426         DO jl = 1, jprecj
427            t2ns_ad(:,jl,2)     = t2ns_ad(:,jl,2) + pt2d_ad(:,ijhom+jl)
428            pt2d_ad(:,ijhom+jl) = t2ns_ad(:,jl,2)
429         END DO
430      CASE ( 0 )
431         DO jl = 1, jprecj
432            t2ns_ad(:,jl,2)     = t2ns_ad(:,jl,2) + pt2d_ad(:,ijhom+jl)
433            pt2d_ad(:,ijhom+jl) = 0.0_wp
434            t2sn_ad(:,jl,2)     = t2sn_ad(:,jl,2) + pt2d_ad(:,jl      )
435            pt2d_ad(:,jl      ) = 0.0_wp
436         END DO
437      CASE ( 1 )
438         DO jl = 1, jprecj
439            t2sn_ad(:,jl,2) = t2sn_ad(:,jl,2) + pt2d_ad(:,jl      )
440            pt2d_ad(:,jl      ) = 0.0_wp
441         END DO
442      END SELECT
443      !
444      !                           ! Migrations
445      imigr = jprecj * jpi
446      !
447      SELECT CASE ( nbondj )
448      CASE ( -1 )
449         CALL mppsend( 4, t2ns_ad(1,1,2), imigr, nono, ml_req1 )
450         CALL mpprecv( 3, t2sn_ad(1,1,1), imigr, nono )
451         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
452      CASE ( 0 )
453         CALL mppsend( 3, t2sn_ad(1,1,2), imigr, noso, ml_req1 )
454         CALL mppsend( 4, t2ns_ad(1,1,2), imigr, nono, ml_req2 )
455         CALL mpprecv( 3, t2sn_ad(1,1,1), imigr, nono )
456         CALL mpprecv( 4, t2ns_ad(1,1,1), imigr, noso )
457         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
458         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
459      CASE ( 1 )
460         CALL mppsend( 3, t2sn_ad(1,1,2), imigr, noso, ml_req1 )
461         CALL mpprecv( 4, t2ns_ad(1,1,1), imigr, noso )
462         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
463      END SELECT
464
465      !always closed : we play only with the neigbours
466
467      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
468         ijhom = nlcj-nrecj
469         DO jl = 1, jprecj
470            pt2d_ad(:,jprecj+jl) = pt2d_ad(:,jprecj+jl) + t2ns_ad(:,jl,1)
471            t2ns_ad(:,jl,1) = 0.0_wp
472            pt2d_ad(:,ijhom +jl) = pt2d_ad(:,ijhom +jl) + t2sn_ad(:,jl,1)
473            t2sn_ad(:,jl,1) = 0.0_wp
474         END DO
475      ENDIF
476      !2. East and west directions exchange
477      !------------------------------------
478                                !! Write Dirichlet lateral conditions
479      iihom = nlci - jpreci
480      !
481      SELECT CASE ( nbondi )
482      CASE ( -1 )
483         DO jl = 1, jpreci
484            t2ew_ad(:,jl,2)     = t2ew_ad(:,jl,2) + pt2d_ad(iihom+jl,:)
485            pt2d_ad(iihom+jl,:) = 0.0_wp
486         END DO
487      CASE ( 0 )
488         DO jl = 1, jpreci
489            t2ew_ad(:,jl,2)     = t2ew_ad(:,jl,2) + pt2d_ad(iihom+jl,:)
490            pt2d_ad(iihom+jl,:) = 0.0_wp
491            t2we_ad(:,jl,2)     = t2we_ad(:,jl,2) + pt2d_ad(jl      ,:)
492            pt2d_ad(jl      ,:) = 0.0_wp
493         END DO
494      CASE ( 1 )
495         DO jl = 1, jpreci
496            t2we_ad(:,jl,2) = t2we_ad(:,jl,2) + pt2d_ad(jl,:)
497            pt2d_ad(jl,:)   = 0.0_wp
498         END DO
499      END SELECT
500      !
501      !                           ! Migrations
502      imigr = jpreci * jpj
503      !
504      SELECT CASE ( nbondi )
505      CASE ( -1 )
506         CALL mppsend( 2, t2ew_ad(1,1,2), imigr, noea, ml_req1 )
507         CALL mpprecv( 1, t2we_ad(1,1,1), imigr, noea )
508         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
509      CASE ( 0 )
510         CALL mppsend( 1, t2we_ad(1,1,2), imigr, nowe, ml_req1 )
511         CALL mppsend( 2, t2ew_ad(1,1,2), imigr, noea, ml_req2 )
512         CALL mpprecv( 1, t2we_ad(1,1,1), imigr, noea )
513         CALL mpprecv( 2, t2ew_ad(1,1,1), imigr, nowe )
514         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
515         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
516      CASE ( 1 )
517         CALL mppsend( 1, t2we_ad(1,1,2), imigr, nowe, ml_req1 )
518         CALL mpprecv( 2, t2ew_ad(1,1,1), imigr, nowe )
519         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
520      END SELECT
521      !
522      ! we play with the neigbours AND the row number because of the periodicity
523      !
524      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
525      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
526         iihom = nlci-nreci
527         DO jl = 1, jpreci
528            pt2d_ad(iihom +jl,:) = pt2d_ad(iihom +jl,:) + t2we_ad(:,jl,1)
529            t2we_ad(:,jl,1)      = 0.0_wp
530            pt2d_ad(jpreci+jl,:) = pt2d_ad(jpreci+jl,:) + t2ew_ad(:,jl,1)
531            t2ew_ad(:,jl,1)      = 0.0_wp
532         END DO
533      END SELECT
534      !
535      ! 1. standard boundary treatment
536      ! ------------------------------
537      !
538      IF( PRESENT( cd_mpp ) ) THEN      ! only fill added line/raw with existing values
539         !
540         ! WARNING pt2d is defined only between nld and nle
541         DO ji = nlci+1, jpi                 ! added column(s) (full)
542            pt2d_ad(nlei,       nlej  ) = pt2d_ad(nlei,     nlej) + SUM(pt2d_ad(ji,nlej+1:jpj   ))
543            pt2d_ad(ji  ,nlej+1:jpj   ) = 0.0_wp
544            pt2d_ad(nlei,nldj         ) = pt2d_ad(nlei,nldj     ) + SUM(pt2d_ad(ji,1     :nldj-1))
545            pt2d_ad(ji  ,1     :nldj-1) = 0.0_wp
546            pt2d_ad(nlei,nldj  :nlej  ) = pt2d_ad(nlei,nldj:nlej) + pt2d_ad(ji,nldj  :nlej  )
547            pt2d_ad(ji  ,nldj  :nlej  ) = 0.0_wp
548         END DO
549         DO jj = nlcj+1, jpj                 ! added line(s)   (inner only)
550            pt2d_ad(nlei         ,nlej) = pt2d_ad(     nlei,     nlej) + SUM(pt2d_ad(nlei+1:nlci  , jj))
551            pt2d_ad(nlei+1:nlci  ,jj  ) = 0.0_wp
552            pt2d_ad(nldi         ,nlej) = pt2d_ad(nldi     ,     nlej) + SUM(pt2d_ad(1     :nldi-1, jj))
553            pt2d_ad(1     :nldi-1,jj  ) = 0.0_wp
554            pt2d_ad(nldi  :nlei  ,nlej) = pt2d_ad(nldi:nlei,     nlej) + pt2d_ad(nldi  :nlei  , jj)
555            pt2d_ad(nldi  :nlei  , jj ) = 0.0_wp
556         END DO
557         !
558      ELSE                              ! standard close or cyclic treatment
559         !
560         !                                   ! North-South boundaries (always closed)
561            IF( .NOT. cd_type == 'F' )   pt2d_ad(:,     1       :jprecj) = 0.0_wp !south except F-point
562                                         pt2d_ad(:,nlcj-jprecj+1:jpj   ) = 0.0_wp ! north
563         !                                   ! East-West boundaries
564         IF( nbondi == 2 .AND.   &                ! Cyclic east-west
565            &    (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
566            pt2d_ad(  2  ,:) = pt2d_ad(  2  ,:) + pt2d_ad(jpi,:) ! east
567            pt2d_ad(jpi  ,:) = 0.0_wp
568            pt2d_ad(jpim1,:) = pt2d_ad(jpim1,:) + pt2d_ad( 1 ,:) ! west
569            pt2d_ad( 1   ,:) = 0.0_wp
570         ELSE                                     ! closed
571            IF( .NOT. cd_type == 'F' )   pt2d_ad(     1       :jpreci,:) = 0.0_wp   ! south except F-point
572                                         pt2d_ad(nlci-jpreci+1:jpi   ,:) = 0.0_wp   ! north
573         ENDIF
574         !
575      ENDIF
576
577   END SUBROUTINE mpp_lnk_2d_adj
578
579
580   SUBROUTINE mpp_lnk_3d_gather_adj( ptab1_ad, cd_type1, ptab2_ad, cd_type2, psgn )
581      !!----------------------------------------------------------------------
582      !!                  ***  routine mpp_lnk_3d_gather_adj  ***
583      !!
584      !! ** Purpose :   Adjoint of Message passing manadgement for two 3D arrays
585      !!
586      !! ** Method  :   Use mppsend and mpprecv function for passing mask
587      !!      between processors following neighboring subdomains.
588      !!            domain parameters
589      !!                    nlci   : first dimension of the local subdomain
590      !!                    nlcj   : second dimension of the local subdomain
591      !!                    nbondi : mark for "east-west local boundary"
592      !!                    nbondj : mark for "north-south local boundary"
593      !!                    noea   : number for local neighboring processors
594      !!                    nowe   : number for local neighboring processors
595      !!                    noso   : number for local neighboring processors
596      !!                    nono   : number for local neighboring processors
597      !!
598      !! ** Action  :   ptab1_ad and ptab2_ad  with update value at its periphery
599      !!
600      !!----------------------------------------------------------------------
601      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptab1_ad     ! first and second 3D array on which
602      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptab2_ad     ! the boundary condition is applied
603      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type1  ! nature of ptab1_ad and ptab2_ad arrays
604      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type2  ! i.e. grid-points = T , U , V , F or W points
605      REAL(wp)                        , INTENT(in   ) ::   psgn      ! =-1 the sign change across the north fold boundary
606      !!                                                             ! =  1. , the sign is kept
607      INTEGER  ::   jl   ! dummy loop indices
608      INTEGER  ::   imigr, iihom, ijhom        ! temporary integers
609      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
610      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
611      !!----------------------------------------------------------------------
612      t4ns_ad = 0.0_wp ; t4sn_ad = 0.0_wp
613      t4we_ad = 0.0_wp ; t4ew_ad = 0.0_wp
614      ! 4. north fold treatment
615      ! -----------------------
616      IF( npolj /= 0 ) THEN
617         !
618         SELECT CASE ( jpni )
619         CASE ( 1 )
620            CALL lbc_nfd_adj      ( ptab2_ad, cd_type2, psgn )
621            CALL lbc_nfd_adj      ( ptab1_ad, cd_type1, psgn )   ! only for northern procs.
622         CASE DEFAULT
623            CALL mpp_lbc_north_adj( ptab2_ad, cd_type2, psgn)
624            CALL mpp_lbc_north_adj( ptab1_ad, cd_type1, psgn )   ! for all northern procs.
625         END SELECT
626         !
627      ENDIF
628      !
629      ! 3. North and south directions
630      ! -----------------------------
631      !                           ! Write Dirichlet lateral conditions
632      ijhom = nlcj - jprecj
633      !
634      SELECT CASE ( nbondj )
635      CASE ( -1 )
636         DO jl = 1, jprecj
637            t4ns_ad(:,jl,:,2,2)    = t4ns_ad(:,jl,:,2,2) + ptab2_ad(:,ijhom+jl,:)
638            ptab2_ad(:,ijhom+jl,:) = 0.0_wp
639            t4ns_ad(:,jl,:,1,2)    = t4ns_ad(:,jl,:,1,2) + ptab1_ad(:,ijhom+jl,:)
640            ptab1_ad(:,ijhom+jl,:) = 0.0_wp
641         END DO
642      CASE ( 0 )
643         DO jl = 1, jprecj
644            t4ns_ad(:,jl,:,2,2)    = t4ns_ad(:,jl,:,2,2) + ptab2_ad(:,ijhom+jl,:)
645            ptab2_ad(:,ijhom+jl,:) = 0.0_wp
646            t4sn_ad(:,jl,:,2,2)    = t4sn_ad(:,jl,:,2,2) + ptab2_ad(:,jl      ,:)
647            ptab2_ad(:,jl      ,:) = 0.0_wp
648            t4ns_ad(:,jl,:,1,2)    = t4ns_ad(:,jl,:,1,2) + ptab1_ad(:,ijhom+jl,:)
649            ptab1_ad(:,ijhom+jl,:) = 0.0_wp
650            t4sn_ad(:,jl,:,1,2)    = t4sn_ad(:,jl,:,1,2) + ptab1_ad(:,jl      ,:)
651            ptab1_ad(:,jl      ,:) = 0.0_wp
652         END DO
653      CASE ( 1 )
654         DO jl = 1, jprecj
655            t4sn_ad(:,jl,:,2,2) = t4sn_ad(:,jl,:,2,2) + ptab2_ad(:,jl,:)
656            ptab2_ad(:,jl,:) = 0.0_wp
657            t4sn_ad(:,jl,:,1,2) = t4sn_ad(:,jl,:,1,2) + ptab1_ad(:,jl,:)
658            ptab1_ad(:,jl,:) = 0.0_wp
659         END DO
660      END SELECT
661      !                           ! Migrations
662      imigr = jprecj * jpi * jpk * 2
663      !
664      SELECT CASE ( nbondj )
665      CASE ( -1 )
666         CALL mppsend( 4, t4ns_ad(1,1,1,1,2), imigr, nono, ml_req1 )
667         CALL mpprecv( 3, t4sn_ad(1,1,1,1,1), imigr, nono )
668         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
669      CASE ( 0 )
670         CALL mppsend( 3, t4sn_ad(1,1,1,1,2), imigr, noso, ml_req1 )
671         CALL mppsend( 4, t4ns_ad(1,1,1,1,2), imigr, nono, ml_req2 )
672         CALL mpprecv( 3, t4sn_ad(1,1,1,1,1), imigr, nono )
673         CALL mpprecv( 4, t4ns_ad(1,1,1,1,1), imigr, noso )
674         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
675         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
676      CASE ( 1 )
677         CALL mppsend( 3, t4sn_ad(1,1,1,1,2), imigr, noso, ml_req1 )
678         CALL mpprecv( 4, t4ns_ad(1,1,1,1,1), imigr, noso )
679         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
680      END SELECT
681      !
682      ! always closed : we play only with the neigbours
683      !
684      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
685         ijhom = nlcj - nrecj
686         DO jl = 1, jprecj
687            ptab2_ad(:,jprecj+jl,:) = ptab2_ad(:,jprecj+jl,:) + t4ns_ad(:,jl,:,2,1)
688            t4ns_ad(:,jl,:,2,1)     = 0.0_wp
689            ptab2_ad(:,ijhom +jl,:) = ptab2_ad(:,ijhom +jl,:) + t4sn_ad(:,jl,:,2,1)
690            t4sn_ad(:,jl,:,2,1)     = 0.0_wp
691            ptab1_ad(:,jprecj+jl,:) = ptab1_ad(:,jprecj+jl,:) + t4ns_ad(:,jl,:,1,1)
692            t4ns_ad(:,jl,:,1,1)     = 0.0_wp
693            ptab1_ad(:,ijhom +jl,:) = ptab1_ad(:,ijhom +jl,:) + t4sn_ad(:,jl,:,1,1)
694            t4sn_ad(:,jl,:,1,1)     = 0.0_wp
695         END DO
696      ENDIF
697      !
698      ! 2. East and west directions exchange
699      ! ------------------------------------
700      !                           ! Write Dirichlet lateral conditions
701      iihom = nlci - jpreci
702      !
703      SELECT CASE ( nbondi )
704      CASE ( -1 )
705         DO jl = 1, jpreci
706            t4ew_ad(:,jl,:,2,2)    = t4ew_ad(:,jl,:,2,2) + ptab2_ad(iihom+jl,:,:)
707            ptab2_ad(iihom+jl,:,:) = 0.0_wp
708            t4ew_ad(:,jl,:,1,2)    = t4ew_ad(:,jl,:,1,2) + ptab1_ad(iihom+jl,:,:)
709            ptab1_ad(iihom+jl,:,:) = 0.0_wp
710         END DO
711      CASE ( 0 )
712         DO jl = 1, jpreci
713            t4ew_ad(:,jl,:,2,2)    = t4ew_ad(:,jl,:,2,2) + ptab2_ad(iihom+jl,:,:)
714            ptab2_ad(iihom+jl,:,:) = 0.0_wp
715            t4we_ad(:,jl,:,2,2)    = t4we_ad(:,jl,:,2,2) + ptab2_ad(jl      ,:,:)
716            ptab2_ad(jl      ,:,:) = 0.0_wp
717            t4ew_ad(:,jl,:,1,2)    = t4ew_ad(:,jl,:,1,2) + ptab1_ad(iihom+jl,:,:)
718            ptab1_ad(iihom+jl,:,:) = 0.0_wp
719            t4we_ad(:,jl,:,1,2)    = t4we_ad(:,jl,:,1,2) + ptab1_ad(jl      ,:,:)
720            ptab1_ad(jl      ,:,:) = 0.0_wp
721         END DO
722      CASE ( 1 )
723         DO jl = 1, jpreci
724            t4we_ad(:,jl,:,2,2) = t4we_ad(:,jl,:,2,2) + ptab2_ad(jl      ,:,:)
725            t4we_ad(:,jl,:,1,2) = t4we_ad(:,jl,:,1,2) + ptab1_ad(jl      ,:,:)
726            ptab1_ad(jl      ,:,:) = 0.0_wp
727            ptab2_ad(jl      ,:,:) = 0.0_wp
728         END DO
729      END SELECT
730      !
731      !                           ! Migrations
732      imigr = jpreci * jpj * jpk *2
733      !
734      SELECT CASE ( nbondi )
735      CASE ( -1 )
736         CALL mppsend( 2, t4ew_ad(1,1,1,1,2), imigr, noea, ml_req1 )
737         CALL mpprecv( 1, t4we_ad(1,1,1,1,1), imigr, noea )
738         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
739      CASE ( 0 )
740         CALL mppsend( 1, t4we_ad(1,1,1,1,2), imigr, nowe, ml_req1 )
741         CALL mppsend( 2, t4ew_ad(1,1,1,1,2), imigr, noea, ml_req2 )
742         CALL mpprecv( 1, t4we_ad(1,1,1,1,1), imigr, noea )
743         CALL mpprecv( 2, t4ew_ad(1,1,1,1,1), imigr, nowe )
744         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
745         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
746      CASE ( 1 )
747         CALL mppsend( 1, t4we_ad(1,1,1,1,2), imigr, nowe, ml_req1 )
748         CALL mpprecv( 2, t4ew_ad(1,1,1,1,1), imigr, nowe )
749         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
750      END SELECT
751      !
752      ! we play with the neigbours AND the row number because of the periodicity
753      !
754      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
755      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
756         iihom = nlci-nreci
757         DO jl = 1, jpreci
758            ptab2_ad(iihom +jl,:,:) = ptab2_ad(iihom +jl,:,:) + t4we_ad(:,jl,:,2,1)
759            t4we_ad(:,jl,:,2,1)     = 0.0_wp
760            ptab2_ad(jpreci+jl,:,:) = ptab2_ad(jpreci+jl,:,:) + t4ew_ad(:,jl,:,2,1)
761            t4ew_ad(:,jl,:,2,1)     = 0.0_wp
762            ptab1_ad(iihom +jl,:,:) = ptab1_ad(iihom +jl,:,:) + t4we_ad(:,jl,:,1,1)
763            t4we_ad(:,jl,:,1,1)     = 0.0_wp
764            ptab1_ad(jpreci+jl,:,:) = ptab1_ad(jpreci+jl,:,:) + t4ew_ad(:,jl,:,1,1)
765            t4ew_ad(:,jl,:,1,1)     = 0.0_wp
766         END DO
767      END SELECT
768      ! 1. standard boundary treatment
769      ! ------------------------------
770      !                                      ! East-West boundaries
771      !                                           !* Cyclic east-west
772      !                                      ! North-South boundaries
773                                    ptab2_ad(:,nlcj-jprecj+1:jpj   ,:) = 0.e0
774                                    ptab1_ad(:,nlcj-jprecj+1:jpj   ,:) = 0.e0    ! north
775      IF( .NOT. cd_type2 == 'F' )   ptab2_ad(:,     1       :jprecj,:) = 0.e0
776      IF( .NOT. cd_type1 == 'F' )   ptab1_ad(:,     1       :jprecj,:) = 0.e0    ! south except at F-point
777      IF( nbondi == 2 .AND. (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
778         ptab2_ad(  2  ,:,:) = ptab2_ad(  2  ,:,:) + ptab2_ad(jpi,:,:)
779         ptab2_ad(jpi,:,:)   = 0.0_wp
780         ptab2_ad(jpim1,:,:) = ptab2_ad(jpim1,:,:) + ptab2_ad( 1 ,:,:)
781         ptab2_ad( 1 ,:,:)   = 0.0_wp
782         ptab1_ad(  2  ,:,:) = ptab1_ad(  2  ,:,:) + ptab1_ad(jpi,:,:)
783         ptab1_ad(jpi,:,:)   = 0.0_wp
784         ptab1_ad(jpim1,:,:) = ptab1_ad(jpim1,:,:) + ptab1_ad( 1 ,:,:)
785         ptab1_ad( 1 ,:,:)   = 0.0_wp
786      ELSE                                        !* closed
787         IF( .NOT. cd_type1 == 'F' )   ptab1_ad(     1       :jpreci,:,:) = 0.e0    ! south except at F-point
788         IF( .NOT. cd_type2 == 'F' )   ptab2_ad(     1       :jpreci,:,:) = 0.e0
789                                       ptab1_ad(nlci-jpreci+1:jpi   ,:,:) = 0.e0    ! north
790                                       ptab2_ad(nlci-jpreci+1:jpi   ,:,:) = 0.e0
791      ENDIF
792   END SUBROUTINE mpp_lnk_3d_gather_adj
793
794
795   SUBROUTINE mpp_lnk_2d_e_adj( pt2d_ad, cd_type, psgn )
796      !!----------------------------------------------------------------------
797      !!                  ***  routine mpp_lnk_2d_e_adj ***
798      !!
799      !! ** Purpose :   Adjoint of Message passing manadgement for 2d array (with halo)
800      !!
801      !! ** Method  :   Use mppsend and mpprecv function for passing mask
802      !!      between processors following neighboring subdomains.
803      !!            domain parameters
804      !!                    nlci   : first dimension of the local subdomain
805      !!                    nlcj   : second dimension of the local subdomain
806      !!                    jpr2di : number of rows for extra outer halo
807      !!                    jpr2dj : number of columns for extra outer halo
808      !!                    nbondi : mark for "east-west local boundary"
809      !!                    nbondj : mark for "north-south local boundary"
810      !!                    noea   : number for local neighboring processors
811      !!                    nowe   : number for local neighboring processors
812      !!                    noso   : number for local neighboring processors
813      !!                    nono   : number for local neighboring processors
814      !!
815      !!----------------------------------------------------------------------
816      REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj), INTENT(inout) ::   pt2d_ad  ! 2D array with extra halo
817      CHARACTER(len=1)                                            , INTENT(in   ) ::   cd_type  ! nature of ptab_ad array grid-points
818      !                                                                                         ! = T , U , V , F , W and I points
819      REAL(wp)                                                    , INTENT(in   ) ::   psgn     ! =-1 the sign change across the
820      !!                                                                                        ! north boundary, =  1. otherwise
821      INTEGER  ::   jl   ! dummy loop indices
822      INTEGER  ::   imigr, iihom, ijhom, rank, ierr  ! temporary integers
823      INTEGER  ::   ipreci, iprecj             ! temporary integers
824      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
825      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
826      !!----------------------------------------------------------------------
827      ipreci = jpreci + jpr2di      ! take into account outer extra 2D overlap area
828      iprecj = jprecj + jpr2dj
829      tr2ns_ad(:,:,:) = 0.0_wp ; tr2sn_ad(:,:,:) = 0.0_wp
830      tr2we_ad(:,:,:) = 0.0_wp ; tr2ew_ad(:,:,:) = 0.0_wp
831      ! 3. North and south directions
832      ! -----------------------------
833      !                           ! Write Dirichlet lateral conditions
834      ijhom = nlcj - jprecj
835      !
836      SELECT CASE ( nbondj )
837      CASE ( -1 )
838         DO jl = 1, iprecj
839            tr2ns_ad(:,jl,2) = tr2ns_ad(:,jl,2) + pt2d_ad(:,ijhom+jl)
840            pt2d_ad(:,ijhom+jl) = 0.0_wp
841         END DO
842      CASE ( 0 )
843         DO jl = 1, iprecj
844            tr2ns_ad(:,jl,2)     = tr2ns_ad(:,jl,2) + pt2d_ad(:,ijhom+jl )
845            pt2d_ad(:,ijhom+jl ) = 0.0_wp
846            tr2sn_ad(:,jl,2)     = tr2sn_ad(:,jl,2) + pt2d_ad(:,jl-jpr2dj)
847            pt2d_ad(:,jl-jpr2dj) = 0.0_wp
848         END DO
849      CASE ( 1 )
850         DO jl = 1, iprecj
851            tr2sn_ad(:,jl,2) = tr2sn_ad(:,jl,2) + pt2d_ad(:,jl-jpr2dj)
852            pt2d_ad(:,jl-jpr2dj) = 0.0_wp
853         END DO
854      END SELECT
855      !                           ! Migrations
856      imigr = iprecj * ( jpi + 2*jpr2di )
857      !
858      SELECT CASE ( nbondj )
859      CASE ( -1 )
860         CALL mppsend( 4, tr2ns_ad(1-jpr2di,1,2), imigr, nono, ml_req1 )
861         CALL mpprecv( 3, tr2sn_ad(1-jpr2di,1,1), imigr, nono )
862         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
863      CASE ( 0 )
864         CALL mppsend( 3, tr2sn_ad(1-jpr2di,1,2), imigr, noso, ml_req1 )
865         CALL mppsend( 4, tr2ns_ad(1-jpr2di,1,2), imigr, nono, ml_req2 )
866         CALL mpprecv( 3, tr2sn_ad(1-jpr2di,1,1), imigr, nono )
867         CALL mpprecv( 4, tr2ns_ad(1-jpr2di,1,1), imigr, noso )
868         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
869         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
870      CASE ( 1 )
871         CALL mppsend( 3, tr2sn_ad(1-jpr2di,1,2), imigr, noso, ml_req1 )
872         CALL mpprecv( 4, tr2ns_ad(1-jpr2di,1,1), imigr, noso )
873         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
874      END SELECT
875      !
876      ! always closed : we play only with the neigbours
877      !
878      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
879         ijhom = nlcj-nrecj-jpr2dj
880         DO jl = 1, iprecj
881            pt2d_ad(:,jprecj+jl) = pt2d_ad(:,jprecj+jl) + tr2ns_ad(:,jl,1)
882            tr2ns_ad(:,jl,1) = 0.0_wp
883            pt2d_ad(:,ijhom +jl) = pt2d_ad(:,ijhom +jl) + tr2sn_ad(:,jl,1)
884            tr2sn_ad(:,jl,1) = 0.0_wp
885         END DO
886      ENDIF
887      !
888      ! 2. East and west directions exchange
889      ! ------------------------------------
890      !                           ! Write Dirichlet lateral conditions
891      iihom = nlci - jpreci
892      !
893      SELECT CASE ( nbondi )
894      CASE ( -1 )
895         DO jl = 1, ipreci
896            tr2ew_ad(:,jl,2)    = tr2ew_ad(:,jl,2) + pt2d_ad(iihom+jl,:)
897            pt2d_ad(iihom+jl,:) = 0.0_wp
898         END DO
899      CASE ( 0 )
900         DO jl = 1, ipreci
901            tr2ew_ad(:,jl,2)  = tr2ew_ad(:,jl,2) + pt2d_ad( iihom+jl,:)
902            pt2d_ad( iihom+jl,:) = 0.0_wp
903            tr2we_ad(:,jl,2)  = tr2we_ad(:,jl,2) + pt2d_ad(jl-jpr2di,:)
904            pt2d_ad(jl-jpr2di,:) = 0.0_wp
905         END DO
906      CASE ( 1 )
907         DO jl = 1, ipreci
908            tr2we_ad(:,jl,2)     = tr2we_ad(:,jl,2) + pt2d_ad(jl-jpr2di,:)
909            pt2d_ad(jl-jpr2di,:) = 0.0_wp
910         END DO
911      END SELECT
912      !                           ! Migrations
913      imigr = ipreci * ( jpj + 2*jpr2dj)
914      !
915      SELECT CASE ( nbondi )
916      CASE ( -1 )
917         CALL mppsend( 2, tr2ew_ad(1-jpr2dj,1,2), imigr, noea, ml_req1 )
918         CALL mpprecv( 1, tr2we_ad(1-jpr2dj,1,1), imigr, noea )
919         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
920      CASE ( 0 )
921         CALL mppsend( 1, tr2we_ad(1-jpr2dj,1,2), imigr, nowe, ml_req1 )
922         CALL mppsend( 2, tr2ew_ad(1-jpr2dj,1,2), imigr, noea, ml_req2 )
923         CALL mpprecv( 1, tr2we_ad(1-jpr2dj,1,1), imigr, noea )
924         CALL mpprecv( 2, tr2ew_ad(1-jpr2dj,1,1), imigr, nowe )
925         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
926         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
927      CASE ( 1 )
928         CALL mppsend( 1, tr2we_ad(1-jpr2dj,1,2), imigr, nowe, ml_req1 )
929         CALL mpprecv( 2, tr2ew_ad(1-jpr2dj,1,1), imigr, nowe )
930         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
931      END SELECT
932      !
933      ! we play with the neigbours AND the row number because of the periodicity
934      !
935      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
936      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
937         iihom = nlci-nreci-jpr2di
938         DO jl = 1, ipreci
939            pt2d_ad(iihom +jl,:) = pt2d_ad(iihom +jl,:) + tr2we_ad(:,jl,1)
940            tr2we_ad(:,jl,1)     = 0.0_wp
941            pt2d_ad(jpreci+jl,:) = pt2d_ad(jpreci+jl,:) + tr2ew_ad(:,jl,1)
942            tr2ew_ad(:,jl,1)     = 0.0_wp
943         END DO
944      END SELECT
945      !
946      ! 1. standard boundary treatment
947      ! ------------------------------
948      ! Order matters Here !!!!
949      !
950      ! north fold treatment
951      ! -----------------------
952      IF( npolj /= 0 ) THEN
953         !
954         SELECT CASE ( jpni )
955         CASE ( 1 )     ;   CALL lbc_nfd_adj        ( pt2d_ad(1:jpi,1:jpj+jpr2dj), cd_type, psgn, pr2dj=jpr2dj )
956         CASE DEFAULT   ;   CALL mpp_lbc_north_e_adj( pt2d_ad                    , cd_type, psgn               )
957         END SELECT
958         !
959      ENDIF
960      !                                      ! East-West boundaries
961      !                                           !* Cyclic east-west
962      IF( nbondi == 2 .AND. (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
963         pt2d_ad(     2      :2+jpr2di  ,:) = pt2d_ad(     2      :2+jpr2di  ,:) &
964            &                               + pt2d_ad(    jpi     :jpi+jpr2di,:)! west
965         pt2d_ad(   jpi      :jpi+jpr2di,:) = 0.0_wp
966         pt2d_ad(jpim1-jpr2di:  jpim1   ,:) = pt2d_ad(jpim1-jpr2di:  jpim1   ,:) &
967            &                               + pt2d_ad(1-jpr2di    :     1    ,:)! east
968         pt2d_ad(1-jpr2di    :     1    ,:) = 0.0_wp
969         !
970      ELSE                                        !* closed
971                                      pt2d_ad(nlci-jpreci+1:jpi+jpr2di,:) = 0.e0    ! north
972         IF( .NOT. cd_type == 'F' )   pt2d_ad(  1-jpr2di   :jpreci    ,:) = 0.e0    ! south except at F-point
973      ENDIF
974      !
975      !                                      !* North-South boundaries (always colsed)
976                                   pt2d_ad(:,nlcj-jprecj+1:jpj+jpr2dj) = 0.e0    ! north
977      IF( .NOT. cd_type == 'F' )   pt2d_ad(:,  1-jpr2dj   :  jprecj  ) = 0.e0    ! south except at F-point
978
979
980   END SUBROUTINE mpp_lnk_2d_e_adj
981
982
983   SUBROUTINE mpp_lbc_north_3d_adj( pt3d_ad, cd_type, psgn )
984      !!---------------------------------------------------------------------
985      !!                   ***  routine mpp_lbc_north_3d_adj  ***
986      !!
987      !! ** Purpose :  Adjoint of Ensure proper north fold horizontal bondary condition
988      !!              in mpp configuration in case of jpn1 > 1
989      !!
990      !! ** Method  :   North fold condition and mpp with more than one proc
991      !!              in i-direction require a specific treatment. We gather
992      !!              the 4 northern lines of the global domain on 1 processor
993      !!              and apply lbc north-fold on this sub array. Then we
994      !!              scatter the north fold array back to the processors.
995      !!
996      !!----------------------------------------------------------------------
997      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pt3d_ad      ! 3D array on which the b.c. is applied
998      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type   ! nature of pt3d_ad grid-points
999      !                                                              !   = T ,  U , V , F or W  gridpoints
1000      REAL(wp)                        , INTENT(in   ) ::   psgn      ! = -1. the sign change across the north fold
1001      !!                                                             ! =  1. , the sign is kept
1002      INTEGER ::   ji, jj, jr
1003      INTEGER ::   ierr, itaille, ildi, ilei, iilb
1004      INTEGER ::   ijpj, ijpjm1, ij, iproc
1005      INTEGER, DIMENSION (jpmaxngh)          ::   ml_req_nf          ! for mpi_isend when avoiding mpi_allgather
1006      INTEGER                                ::   ml_err             ! for mpi_isend when avoiding mpi_allgather
1007      INTEGER, DIMENSION(MPI_STATUS_SIZE)    ::   ml_stat            ! for mpi_isend when avoiding mpi_allgather
1008      !!----------------------------------------------------------------------
1009      !
1010      ijpj   = 4
1011      ityp = -1
1012      ijpjm1 = 3
1013      ztabad(:,:,:) = 0.0_wp  ;  znorthlocad (:,:,:)= 0.0_wp  ;  znorthgloioad(:,:,:,:) = 0.0_wp
1014      !
1015      !
1016      DO jj = nlcj, nlcj-ijpj+1, -1          ! Scatter back to pt3d_ad
1017         ij = jj - nlcj + ijpj
1018         DO ji= nlci, 1, -1
1019            ztabad(ji+nimpp-1,ij,:) = ztabad(ji+nimpp-1,ij,:) + pt3d_ad(ji,jj,:)
1020            pt3d_ad(ji,jj,:) = 0.0_wp
1021         END DO
1022      END DO
1023      !
1024      ! The ztabad array has been either:
1025      !  a. Fully populated by the mpi_allgather operation or
1026      !  b. Had the active points for this domain and northern neighbours populated
1027      !     by peer to peer exchanges
1028      ! Either way the array may be folded by lbc_nfd and the result for the span of
1029      ! this domain will be identical.
1030      !
1031      CALL lbc_nfd_adj( ztabad, cd_type, psgn )   ! North fold boundary condition
1032      !
1033      !                                     ! Build in procs of ncomm_north the znorthgloioad
1034      itaille = jpi * jpk * ijpj
1035      IF ( l_north_nogather ) THEN
1036         !
1037         ! Set the exchange type in order to access the correct list of active neighbours
1038         !
1039         SELECT CASE ( cd_type )
1040            CASE ( 'T' , 'W' )
1041               ityp = 1
1042            CASE ( 'U' )
1043               ityp = 2
1044            CASE ( 'V' )
1045               ityp = 3
1046            CASE ( 'F' )
1047               ityp = 4
1048            CASE ( 'I' )
1049               ityp = 5
1050            CASE DEFAULT
1051               ityp = -1                    ! Set a default value for unsupported types which
1052                                            ! will cause a fallback to the mpi_allgather method
1053         END SELECT
1054         IF ( ityp .gt. 0 ) THEN
1055         !
1056            DO jr = 1, nsndto(ityp)
1057               iproc = isendto(jr,ityp) + 1
1058               ildi = nldit (iproc)
1059               ilei = nleit (iproc)
1060               iilb = nimppt(iproc)
1061               DO jj = ijpj, 1, -1
1062                  DO ji = ilei, ildi, -1
1063                     zfoldwkad(ji,jj,:) = ztabad(ji+iilb-1,jj,:)
1064                     ztabad(ji+iilb-1,jj,:) = 0.0_wp
1065                  END DO
1066               END DO
1067               CALL mppsend(5, zfoldwkad, itaille, isendto(jr,ityp), ml_req_nf(jr) )
1068            END DO
1069            DO jr = 1, nsndto(ityp)
1070               CALL mpprecv(5, znorthlocad, itaille, isendto(jr,ityp))
1071            END DO
1072            IF (l_isend) THEN
1073               DO jr = 1, nsndto(ityp)
1074                  CALL mpi_wait(ml_req_nf(jr), ml_stat, ml_err)
1075               END DO
1076            ENDIF
1077            !
1078         ENDIF
1079         !
1080         ! Avoid the use of mpi_allgather by exchanging only with the processes already identified
1081         ! (in nemo_northcomms) as being  involved in this process' northern boundary exchange
1082         !
1083         DO jj = nlcj, nlcj-ijpj+1, -1         ! First put local values into the global array
1084            ij = jj - nlcj + ijpj
1085            DO ji = nlci, 1, -1
1086               pt3d_ad(ji,jj,:) = pt3d_ad(ji,jj,:) + ztabad(ji+nimpp-1,ij,:)
1087               ztabad(ji+nimpp-1,ij,:) = 0.0_wp
1088            END DO
1089         END DO
1090         !
1091      ENDIF
1092      IF ( ityp .lt. 0 ) THEN
1093         DO jr = 1, ndim_rank_north         ! recover the global north array
1094            iproc = nrank_north(jr) + 1
1095            ildi  = nldit (iproc)
1096            ilei  = nleit (iproc)
1097            iilb  = nimppt(iproc)
1098            DO jj = 1, ijpj
1099               DO ji = ildi, ilei
1100                  znorthgloioad(ji,jj,:,jr) = znorthgloioad(ji,jj,:,jr) + ztabad(ji+iilb-1,jj,:)
1101                  ztabad(ji+iilb-1,jj,:) = 0.0_wp
1102               END DO
1103            END DO
1104         END DO
1105         !                                     ! Build in procs of ncomm_north the znorthgloio
1106         itaille = jpi * jpk * ijpj
1107         ! Specific treatment of adjoint of mpi_allgather
1108         znorthgloioad = mpp_sum_nfd(znorthgloioad,jpi,4,jpk,jpni,ncomm_north)
1109         jr=  ndim_rank_north-jpnij+nproc+1
1110         znorthlocad(:,:,:) = znorthgloioad(:,:,:,jr)
1111         !
1112      ENDIF
1113      !
1114      DO jj = nlcj, nlcj - ijpj +1, -1          ! put in znorthlocad the last 4 jlines of pt3d_ad
1115         ij = jj - nlcj + ijpj
1116         pt3d_ad(:,jj,:) = pt3d_ad(:,jj,:) + znorthlocad(:,ij,:)
1117         znorthlocad(:,ij,:) = 0.0_wp
1118      END DO
1119      !
1120   END SUBROUTINE mpp_lbc_north_3d_adj
1121
1122
1123   SUBROUTINE mpp_lbc_north_2d_adj( pt2d_ad, cd_type, psgn)
1124      !!---------------------------------------------------------------------
1125      !!                   ***  routine mpp_lbc_north_2d_adj  ***
1126      !!
1127      !! ** Purpose :   Adjoint of Ensure proper north fold horizontal bondary condition
1128      !!              in mpp configuration in case of jpn1 > 1 (for 2d array )
1129      !!
1130      !! ** Method  :   North fold condition and mpp with more than one proc
1131      !!              in i-direction require a specific treatment. We gather
1132      !!              the 4 northern lines of the global domain on 1 processor
1133      !!              and apply lbc north-fold on this sub array. Then we
1134      !!              scatter the north fold array back to the processors.
1135      !!
1136      !!----------------------------------------------------------------------
1137      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   pt2d_ad      ! 3D array on which the b.c. is applied
1138      CHARACTER(len=1)            , INTENT(in   ) ::   cd_type   ! nature of pt3d_ad grid-points
1139      !                                                          !   = T ,  U , V , F or W  gridpoints
1140      REAL(wp)                    , INTENT(in   ) ::   psgn      ! = -1. the sign change across the north fold
1141      !!                                                             ! =  1. , the sign is kept
1142      INTEGER ::   ji, jj, jr
1143      INTEGER ::   ierr, itaille, ildi, ilei, iilb
1144      INTEGER ::   ijpj, ijpjm1, ij, iproc
1145      INTEGER, DIMENSION (jpmaxngh)      ::   ml_req_nf          ! for mpi_isend when avoiding mpi_allgather
1146      INTEGER                            ::   ml_err             ! for mpi_isend when avoiding mpi_allgather
1147      INTEGER, DIMENSION(MPI_STATUS_SIZE)::   ml_stat            ! for mpi_isend when avoiding mpi_allgather
1148      !!----------------------------------------------------------------------
1149      !
1150      ijpj   = 4
1151      ityp = -1
1152      ijpjm1 = 3
1153      ztabad_2d(:,:) = 0.0_wp ; znorthlocad_2d = 0.0_wp ; znorthgloioad_2d = 0.0_wp
1154      !
1155      DO jj = nlcj, nlcj-ijpj+1, -1             ! Scatter back to pt2d_ad
1156         ij = jj - nlcj + ijpj
1157         DO ji = nlci, 1, -1
1158            ztabad_2d(ji+nimpp-1,ij) = ztabad_2d(ji+nimpp-1,ij) + pt2d_ad(ji,jj)
1159            pt2d_ad(ji,jj) = 0.0_wp
1160         END DO
1161      END DO
1162      !
1163      ! The ztabad array has been either:
1164      !  a. Fully populated by the mpi_allgather operation or
1165      !  b. Had the active points for this domain and northern neighbours populated
1166      !     by peer to peer exchanges
1167      ! Either way the array may be folded by lbc_nfd and the result for the span of
1168      ! this domain will be identical.
1169      !
1170      CALL lbc_nfd_adj( ztabad_2d, cd_type, psgn )   ! North fold boundary condition
1171      !
1172      !
1173      !                                     ! Build in procs of ncomm_north the znorthgloioad_2d
1174      itaille = jpi * ijpj
1175      IF ( l_north_nogather ) THEN
1176      !
1177      ! Set the exchange type in order to access the correct list of active neighbours
1178      !
1179         SELECT CASE ( cd_type )
1180            CASE ( 'T' , 'W' )
1181               ityp = 1
1182            CASE ( 'U' )
1183               ityp = 2
1184            CASE ( 'V' )
1185               ityp = 3
1186            CASE ( 'F' )
1187               ityp = 4
1188            CASE ( 'I' )
1189               ityp = 5
1190            CASE DEFAULT
1191               ityp = -1                    ! Set a default value for unsupported types which
1192         !                                  ! will cause a fallback to the mpi_allgather method
1193         END SELECT
1194         !
1195         IF ( ityp .gt. 0 ) THEN
1196            !
1197            DO jr = nsndto(ityp), 1, -1
1198               iproc = isendto(jr,ityp) + 1
1199               ildi = nldit (iproc)
1200               ilei = nleit (iproc)
1201               iilb = nimppt(iproc)
1202               DO jj = ijpj, 1, -1
1203                  DO ji = ilei, ildi, -1
1204                     zfoldwkad_2d(ji,jj) = ztabad_2d(ji+iilb-1,jj)
1205                     ztabad_2d(ji+iilb-1,jj) = 0.0_wp
1206                  END DO
1207               END DO
1208               CALL mppsend(5, zfoldwkad_2d, itaille, isendto(jr,ityp), ml_req_nf(jr))
1209            END DO
1210            DO jr = nsndto(ityp), 1, -1
1211               CALL mpprecv(5, znorthlocad_2d, itaille, isendto(jr,ityp) )
1212            END DO
1213            !
1214            IF (l_isend) THEN
1215               DO jr = nsndto(ityp), 1, -1
1216                  CALL mpi_wait(ml_req_nf(jr), ml_stat, ml_err)
1217               END DO
1218            ENDIF
1219            !
1220         ENDIF
1221         !
1222         ! Avoid the use of mpi_allgather by exchanging only with the processes already identified
1223         ! (in nemo_northcomms) as being  involved in this process' northern boundary exchange
1224         !
1225         DO jj = nlcj-ijpj+1, nlcj          ! First put local values into the global array
1226            ij = jj - nlcj + ijpj
1227            DO ji = 1, nlci
1228               pt2d_ad(ji,jj) = pt2d_ad(ji,jj) + ztabad_2d(ji+nimpp-1,ij)
1229               ztabad_2d(ji+nimpp-1,ij) = 0.0_wp
1230            END DO
1231         END DO
1232         !
1233      ENDIF
1234      !
1235      IF ( ityp .lt. 0 ) THEN
1236         DO jr = 1, ndim_rank_north            ! recover the global north array
1237            iproc = nrank_north(jr) + 1
1238            ildi = nldit (iproc)
1239            ilei = nleit (iproc)
1240            iilb = nimppt(iproc)
1241            DO jj = 1, ijpj
1242               DO ji = ildi, ilei
1243                  znorthgloioad_2d(ji,jj,jr) = znorthgloioad_2d(ji,jj,jr) + ztabad_2d(ji+iilb-1,jj)
1244                  ztabad_2d(ji+iilb-1,jj) = 0.0_wp
1245               END DO
1246            END DO
1247         END DO
1248         !
1249         znorthgloioad_2d = mpp_sum_nfd(znorthgloioad_2d,jpi,4,jpni,ncomm_north)
1250         jr=  ndim_rank_north-jpnij+nproc+1
1251         znorthlocad_2d(:,:) = znorthgloioad_2d(:,:,jr)
1252         !
1253      ENDIF
1254      DO jj = nlcj, nlcj - ijpj +1, -1          ! put in znorthlocad the last 4 jlines of pt2d_ad
1255         ij = jj - nlcj + ijpj
1256         pt2d_ad(:,jj) = pt2d_ad(:,jj) + znorthlocad_2d(:,ij)
1257         znorthlocad_2d(:,ij) = 0.0_wp
1258      END DO
1259      !
1260   END SUBROUTINE mpp_lbc_north_2d_adj
1261
1262
1263   SUBROUTINE mpp_lbc_north_e_adj( pt2d_ad, cd_type, psgn)
1264      !!---------------------------------------------------------------------
1265      !!                   ***  routine mpp_lbc_north_e_adj  ***
1266      !!
1267      !! ** Purpose : Adjoint of Ensure proper north fold horizontal bondary condition
1268      !!              in mpp configuration in case of jpn1 > 1 and for 2d
1269      !!              array with outer extra halo
1270      !!
1271      !! ** Method  :   North fold condition and mpp with more than one proc
1272      !!              in i-direction require a specific treatment. We gather
1273      !!              the 4+2*jpr2dj northern lines of the global domain on 1
1274      !!              processor and apply lbc north-fold on this sub array.
1275      !!              Then we scatter the north fold array back to the processors.
1276      !!
1277      !!----------------------------------------------------------------------
1278      REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj), INTENT(inout) ::   pt2d_ad     ! 2D array with extra halo
1279      CHARACTER(len=1)                                            , INTENT(in   ) ::   cd_type  ! nature of pt3d_ad grid-points
1280      !                                                                                         !   = T ,  U , V , F or W -points
1281      REAL(wp)                                                    , INTENT(in   ) ::   psgn     ! = -1. the sign change across the
1282      !!                                                                                        ! north fold, =  1. otherwise
1283      INTEGER ::   ji, jj, jr
1284      INTEGER ::   ierr, itaille, ildi, ilei, iilb
1285      INTEGER ::   ijpj, ij, iproc
1286      !!----------------------------------------------------------------------
1287      !
1288      ijpj=4
1289      ztabad_e = 0.e0  ;  znorthlocad_e = 0.0_wp  ;  znorthgloioad_e = 0.0_wp
1290      !
1291      ij = jpr2dj
1292      !! Scatter back to pt2d
1293      DO jj = nlcj - ijpj + 1 , nlcj +jpr2dj
1294      ij  = ij +1
1295         DO ji= 1, nlci
1296            ztabad_e(ji+nimpp-1,ij) = ztabad_e(ji+nimpp-1,ij) + pt2d_ad(ji,jj)
1297            pt2d_ad(ji,jj)        = 0.0_wp
1298         END DO
1299      END DO
1300      !
1301      ! 2. North-Fold boundary conditions
1302      ! ----------------------------------
1303      CALL lbc_nfd_adj( ztabad_e(:,:), cd_type, psgn, jpr2dj)!, pr2dj = jpr2dj )
1304      !
1305      DO jr = 1, ndim_rank_north            ! recover the global north array
1306         iproc = nrank_north(jr) + 1
1307         ildi = nldit (iproc)
1308         ilei = nleit (iproc)
1309         iilb = nimppt(iproc)
1310         DO jj = 1, ijpj+2*jpr2dj
1311            DO ji = ildi, ilei
1312               znorthgloioad_e(ji,jj,jr) = znorthgloioad_e(ji,jj,jr) + ztabad_e(ji+iilb-1,jj)
1313               ztabad_e(ji+iilb-1,jj) = 0.0_wp
1314            END DO
1315         END DO
1316      END DO
1317      !
1318      itaille = jpi * ( ijpj + 2 * jpr2dj )
1319      ! Specific treatment of adjoint of mpi_allgather
1320      znorthgloioad_e = mpp_sum_nfd(znorthgloioad_e,jpi,4,jpni,ncomm_north)
1321      jr=  ndim_rank_north-jpnij+nproc+1
1322      znorthlocad_e(:,:) = znorthgloioad_e(:,:,jr)
1323      !
1324      ij=0
1325      ! put in znorthloc the last 4 jlines of pt2d
1326      DO jj = nlcj - ijpj + 1 - jpr2dj, nlcj +jpr2dj
1327         ij = ij + 1
1328         DO ji = 1, jpi
1329            pt2d_ad(ji,jj)     = pt2d_ad(ji,jj) + znorthlocad_e(ji,ij)
1330            znorthlocad_e(ji,ij) = 0.0_wp
1331         END DO
1332      END DO
1333      !
1334   END SUBROUTINE mpp_lbc_north_e_adj
1335#endif
1336#if defined key_mpp_mpi
1337   FUNCTION mpp_sum_nfd_4d( pval, kn1, kn2, kn3, kn4, kcom )
1338      !!----------------------------------------------------------------------
1339      !!               ***  ROUTINE mpp_sum_nfd_4d ***
1340      !!
1341      !! ** Purpose : Summation of arrays across processors (of kcom group)
1342      !!
1343      !! ** Method  : Pack 4d array to vector, do vector sum and then unpack
1344      !!
1345      !! ** Action  : This does only work for MPI.
1346      !!              It does not work for SHMEM.
1347      !!
1348      !! History :
1349      !!        !  10-11  (F. Vigilant)  Original code
1350      !!----------------------------------------------------------------------
1351      !! * Function return
1352      REAL(wp), DIMENSION(kn1, kn2, kn3, kn4) :: mpp_sum_nfd_4d
1353      !! * Arguments
1354      INTEGER, INTENT(IN) :: kn1, kn2, kn3, kn4
1355      REAL(wp), DIMENSION(kn1, kn2, kn3, kn4), INTENT(IN) :: pval
1356      INTEGER , INTENT( in ), OPTIONAL        :: kcom
1357      !! * Local declarations
1358      REAL(wp), DIMENSION(:), ALLOCATABLE     :: zvec
1359      LOGICAL, DIMENSION(kn1, kn2, kn3, kn4)  :: zmask
1360      REAL(wp), DIMENSION(kn1, kn2, kn3, kn4) :: zfd
1361      INTEGER :: zdim
1362
1363      zdim = kn1 * kn2 * kn3 * kn4
1364      ALLOCATE( zvec(zdim) )
1365
1366      zvec = PACK( pval(1:kn1,1:kn2,1:kn3,1:kn4),.TRUE.)
1367
1368      CALL mpp_sum( zvec, zdim, kcom )
1369
1370      zmask(:,:,:,:) = .TRUE.
1371      mpp_sum_nfd_4d = UNPACK( zvec, zmask, zfd )
1372
1373      DEALLOCATE( zvec )
1374
1375   END FUNCTION mpp_sum_nfd_4d
1376
1377   FUNCTION mpp_sum_nfd_3d( pval, kn1, kn2, kn3, kcom )
1378      !!----------------------------------------------------------------------
1379      !!               ***  ROUTINE mpp_sum_nfd_3d ***
1380      !!
1381      !! ** Purpose : Summation of arrays across processors (of kcom group)
1382      !!
1383      !! ** Method  : Pack 3d array to vector, do vector sum and then unpack
1384      !!
1385      !! ** Action  : This does only work for MPI.
1386      !!              It does not work for SHMEM.
1387      !!
1388      !! History :
1389      !!        !  10-11  (F. Vigilant)  Original code
1390      !!----------------------------------------------------------------------
1391      !! * Function return
1392      REAL(wp), DIMENSION(kn1, kn2, kn3) :: mpp_sum_nfd_3d
1393      !! * Arguments
1394      INTEGER, INTENT(IN) ::kn1, kn2, kn3
1395      REAL(wp), DIMENSION(kn1, kn2, kn3), INTENT(IN) :: pval
1396      INTEGER , INTENT( in ), OPTIONAL        :: kcom
1397      !! * Local declarations
1398      REAL(wp), DIMENSION(:), ALLOCATABLE     :: zvec
1399      LOGICAL, DIMENSION(kn1, kn2, kn3)  :: zmask
1400      REAL(wp), DIMENSION(kn1, kn2, kn3) :: zfd
1401      INTEGER :: zdim
1402
1403      zdim = kn1 * kn2 * kn3
1404      ALLOCATE( zvec(zdim) )
1405
1406      zvec = PACK( pval(1:kn1,1:kn2,1:kn3),.TRUE.)
1407
1408      CALL mpp_sum( zvec, zdim, kcom )
1409
1410      zmask(:,:,:) = .TRUE.
1411      mpp_sum_nfd_3d = UNPACK( zvec, zmask, zfd )
1412
1413      DEALLOCATE( zvec )
1414
1415   END FUNCTION mpp_sum_nfd_3d
1416#else
1417   USE in_out_manager
1418   PUBLIC lib_mpp_alloc_adj
1419CONTAINS
1420    INTEGER FUNCTION lib_mpp_alloc_adj(kumout)          ! Dummy function
1421      INTEGER, INTENT(in) ::   kumout
1422      lib_mpp_alloc_adj = 0
1423   END FUNCTION lib_mpp_alloc_adj
1424   FUNCTION mpp_sum_nfd_4d( pval, kn1, kn2, kn3, kn4, kcom )
1425      !! * Function return
1426      REAL(wp), DIMENSION(kn1, kn2, kn3, kn4) :: mpp_sum_nfd_4d
1427      !! * Arguments
1428      INTEGER, INTENT(IN) :: kn1, kn2, kn3, kn4
1429      REAL(wp), DIMENSION(kn1, kn2, kn3, kn4), INTENT(IN) :: pval
1430      INTEGER , INTENT( in ), OPTIONAL        :: kcom
1431      mpp_sum_nfd_4d = 0.0_wp
1432      WRITE(*,*) 'mpp_sum_nfd_4d: You should not have seen this print! error?'
1433   END FUNCTION mpp_sum_nfd_4d
1434   FUNCTION mpp_sum_nfd_3d( pval, kn1, kn2, kn3, kcom )
1435      !! * Function return
1436      REAL(wp), DIMENSION(kn1, kn2, kn3) :: mpp_sum_nfd_3d
1437      !! * Arguments
1438      INTEGER, INTENT(IN) :: kn1, kn2, kn3
1439      REAL(wp), DIMENSION(kn1, kn2, kn3), INTENT(IN) :: pval
1440      INTEGER , INTENT( in ), OPTIONAL        :: kcom
1441      mpp_sum_nfd_3d = 0.0_wp
1442      WRITE(*,*) 'mpp_sum_nfd_3d: You should not have seen this print! error?'
1443   END FUNCTION mpp_sum_nfd_3d
1444#endif
1445   !!----------------------------------------------------------------------
1446END MODULE lib_mpp_tam
Note: See TracBrowser for help on using the repository browser.