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.F90 in trunk/NEMOGCM/NEMO/OPA_SRC/LBC – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90 @ 3420

Last change on this file since 3420 was 3420, checked in by acc, 12 years ago

Bugfix #977. Minor changes to lib_mpp.F90 to free mpi_group structures after use in mpp_ini_ice

  • Property svn:keywords set to Id
File size: 130.2 KB
Line 
1MODULE lib_mpp
2   !!======================================================================
3   !!                       ***  MODULE  lib_mpp  ***
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   !!----------------------------------------------------------------------
22
23   !!----------------------------------------------------------------------
24   !!   ctl_stop   : update momentum and tracer Kz from a tke scheme
25   !!   ctl_warn   : initialization, namelist read, and parameters control
26   !!   ctl_opn    : Open file and check if required file is available.
27   !!   get_unit    : give the index of an unused logical unit
28   !!----------------------------------------------------------------------
29#if   defined key_mpp_mpi 
30   !!----------------------------------------------------------------------
31   !!   'key_mpp_mpi'             MPI massively parallel processing library
32   !!----------------------------------------------------------------------
33   !!   lib_mpp_alloc : allocate mpp arrays
34   !!   mynode        : indentify the processor unit
35   !!   mpp_lnk       : interface (defined in lbclnk) for message passing of 2d or 3d arrays (mpp_lnk_2d, mpp_lnk_3d)
36   !!   mpp_lnk_3d_gather :  Message passing manadgement for two 3D arrays
37   !!   mpp_lnk_e     : interface (defined in lbclnk) for message passing of 2d array with extra halo (mpp_lnk_2d_e)
38   !!   mpprecv         :
39   !!   mppsend       :   SUBROUTINE mpp_ini_znl
40   !!   mppscatter    :
41   !!   mppgather     :
42   !!   mpp_min       : generic interface for mppmin_int , mppmin_a_int , mppmin_real, mppmin_a_real
43   !!   mpp_max       : generic interface for mppmax_int , mppmax_a_int , mppmax_real, mppmax_a_real
44   !!   mpp_sum       : generic interface for mppsum_int , mppsum_a_int , mppsum_real, mppsum_a_real
45   !!   mpp_minloc    :
46   !!   mpp_maxloc    :
47   !!   mppsync       :
48   !!   mppstop       :
49   !!   mppobc        : variant of mpp_lnk for open boundary condition
50   !!   mpp_ini_north : initialisation of north fold
51   !!   mpp_lbc_north : north fold processors gathering
52   !!   mpp_lbc_north_e : variant of mpp_lbc_north for extra outer halo
53   !!----------------------------------------------------------------------
54   USE dom_oce        ! ocean space and time domain
55   USE lbcnfd         ! north fold treatment
56   USE in_out_manager ! I/O manager
57
58   IMPLICIT NONE
59   PRIVATE
60   
61   PUBLIC   ctl_stop, ctl_warn, get_unit, ctl_opn
62   PUBLIC   mynode, mppstop, mppsync, mpp_comm_free
63   PUBLIC   mpp_ini_north, mpp_lbc_north, mpp_lbc_north_e
64   PUBLIC   mpp_min, mpp_max, mpp_sum, mpp_minloc, mpp_maxloc
65   PUBLIC   mpp_lnk_3d, mpp_lnk_3d_gather, mpp_lnk_2d, mpp_lnk_2d_e
66   PUBLIC   mppscatter, mppgather
67   PUBLIC   mppobc, mpp_ini_ice, mpp_ini_znl
68   PUBLIC   mppsize
69   PUBLIC   lib_mpp_alloc   ! Called in nemogcm.F90
70
71   !! * Interfaces
72   !! define generic interface for these routine as they are called sometimes
73   !! with scalar arguments instead of array arguments, which causes problems
74   !! for the compilation on AIX system as well as NEC and SGI. Ok on COMPACQ
75   INTERFACE mpp_min
76      MODULE PROCEDURE mppmin_a_int, mppmin_int, mppmin_a_real, mppmin_real
77   END INTERFACE
78   INTERFACE mpp_max
79      MODULE PROCEDURE mppmax_a_int, mppmax_int, mppmax_a_real, mppmax_real
80   END INTERFACE
81   INTERFACE mpp_sum
82# if defined key_mpp_rep
83      MODULE PROCEDURE mppsum_a_int, mppsum_int, mppsum_a_real, mppsum_real, &
84                       mppsum_realdd, mppsum_a_realdd
85# else
86      MODULE PROCEDURE mppsum_a_int, mppsum_int, mppsum_a_real, mppsum_real
87# endif
88   END INTERFACE
89   INTERFACE mpp_lbc_north
90      MODULE PROCEDURE mpp_lbc_north_3d, mpp_lbc_north_2d 
91   END INTERFACE
92   INTERFACE mpp_minloc
93      MODULE PROCEDURE mpp_minloc2d ,mpp_minloc3d
94   END INTERFACE
95   INTERFACE mpp_maxloc
96      MODULE PROCEDURE mpp_maxloc2d ,mpp_maxloc3d
97   END INTERFACE
98   
99   !! ========================= !!
100   !!  MPI  variable definition !!
101   !! ========================= !!
102!$AGRIF_DO_NOT_TREAT
103   INCLUDE 'mpif.h'
104!$AGRIF_END_DO_NOT_TREAT
105   
106   LOGICAL, PUBLIC, PARAMETER ::   lk_mpp = .TRUE.    !: mpp flag
107
108   INTEGER, PARAMETER         ::   nprocmax = 2**10   ! maximun dimension (required to be a power of 2)
109   
110   INTEGER ::   mppsize        ! number of process
111   INTEGER ::   mpprank        ! process number  [ 0 - size-1 ]
112!$AGRIF_DO_NOT_TREAT
113   INTEGER, PUBLIC ::   mpi_comm_opa   ! opa local communicator
114!$AGRIF_END_DO_NOT_TREAT
115
116# if defined key_mpp_rep
117   INTEGER :: MPI_SUMDD
118# endif
119
120   ! variables used in case of sea-ice
121   INTEGER, PUBLIC ::   ncomm_ice       !: communicator made by the processors with sea-ice (public so that it can be freed in limthd)
122   INTEGER ::   ngrp_iworld     !  group ID for the world processors (for rheology)
123   INTEGER ::   ngrp_ice        !  group ID for the ice processors (for rheology)
124   INTEGER ::   ndim_rank_ice   !  number of 'ice' processors
125   INTEGER ::   n_ice_root      !  number (in the comm_ice) of proc 0 in the ice comm
126   INTEGER, DIMENSION(:), ALLOCATABLE, SAVE ::   nrank_ice     ! dimension ndim_rank_ice
127
128   ! variables used for zonal integration
129   INTEGER, PUBLIC ::   ncomm_znl       !: communicator made by the processors on the same zonal average
130   LOGICAL, PUBLIC ::   l_znl_root      ! True on the 'left'most processor on the same row
131   INTEGER ::   ngrp_znl        ! group ID for the znl processors
132   INTEGER ::   ndim_rank_znl   ! number of processors on the same zonal average
133   INTEGER, DIMENSION(:), ALLOCATABLE, SAVE ::   nrank_znl  ! dimension ndim_rank_znl, number of the procs into the same znl domain
134   
135   ! North fold condition in mpp_mpi with jpni > 1
136   INTEGER ::   ngrp_world        ! group ID for the world processors
137   INTEGER ::   ngrp_opa          ! group ID for the opa processors
138   INTEGER ::   ngrp_north        ! group ID for the northern processors (to be fold)
139   INTEGER ::   ncomm_north       ! communicator made by the processors belonging to ngrp_north
140   INTEGER ::   ndim_rank_north   ! number of 'sea' processor in the northern line (can be /= jpni !)
141   INTEGER ::   njmppmax          ! value of njmpp for the processors of the northern line
142   INTEGER ::   north_root        ! number (in the comm_opa) of proc 0 in the northern comm
143   INTEGER, DIMENSION(:), ALLOCATABLE, SAVE ::   nrank_north   ! dimension ndim_rank_north
144
145   ! Type of send : standard, buffered, immediate
146   CHARACTER(len=1) ::   cn_mpi_send = 'S'    ! type od mpi send/recieve (S=standard, B=bsend, I=isend)
147   LOGICAL          ::   l_isend = .FALSE.   ! isend use indicator (T if cn_mpi_send='I')
148   INTEGER          ::   nn_buffer = 0       ! size of the buffer in case of mpi_bsend
149     
150   REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE :: tampon  ! buffer in case of bsend
151
152   ! message passing arrays
153   REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE, SAVE ::   t4ns, t4sn   ! 2 x 3d for north-south & south-north
154   REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE, SAVE ::   t4ew, t4we   ! 2 x 3d for east-west & west-east
155   REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE, SAVE ::   t4p1, t4p2   ! 2 x 3d for north fold
156   REAL(wp), DIMENSION(:,:,:,:)  , ALLOCATABLE, SAVE ::   t3ns, t3sn   ! 3d for north-south & south-north
157   REAL(wp), DIMENSION(:,:,:,:)  , ALLOCATABLE, SAVE ::   t3ew, t3we   ! 3d for east-west & west-east
158   REAL(wp), DIMENSION(:,:,:,:)  , ALLOCATABLE, SAVE ::   t3p1, t3p2   ! 3d for north fold
159   REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   t2ns, t2sn   ! 2d for north-south & south-north
160   REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   t2ew, t2we   ! 2d for east-west & west-east
161   REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   t2p1, t2p2   ! 2d for north fold
162   REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   tr2ns, tr2sn ! 2d for north-south & south-north + extra outer halo
163   REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   tr2ew, tr2we ! 2d for east-west   & west-east   + extra outer halo
164
165   ! Arrays used in mpp_lbc_north_3d()
166   REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE, SAVE   ::   ztab, znorthloc
167   REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, SAVE   ::   znorthgloio
168   REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE, SAVE   ::   zfoldwk      ! Workspace for message transfers avoiding mpi_allgather
169
170   ! Arrays used in mpp_lbc_north_2d()
171   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   ztab_2d, znorthloc_2d
172   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE    ::   znorthgloio_2d
173   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   zfoldwk_2d    ! Workspace for message transfers avoiding mpi_allgather
174
175   ! Arrays used in mpp_lbc_north_e()
176   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   ztab_e, znorthloc_e
177   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE    ::   znorthgloio_e
178
179   ! North fold arrays used to minimise the use of allgather operations. Set in nemo_northcomms (nemogcm) so need to be public
180   INTEGER, PUBLIC,  PARAMETER :: jpmaxngh = 8                 ! Assumed maximum number of active neighbours
181   INTEGER, PUBLIC,  PARAMETER :: jptyps   = 5                 ! Number of different neighbour lists to be used for northfold exchanges
182   INTEGER, PUBLIC,  DIMENSION (jpmaxngh,jptyps)    ::   isendto
183   INTEGER, PUBLIC,  DIMENSION (jptyps)             ::   nsndto
184   LOGICAL, PUBLIC                                  ::   ln_nnogather     = .FALSE.  ! namelist control of northfold comms
185   LOGICAL, PUBLIC                                  ::   l_north_nogather = .FALSE.  ! internal control of northfold comms
186   INTEGER, PUBLIC                                  ::   ityp
187   !!----------------------------------------------------------------------
188   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
189   !! $Id$
190   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
191   !!----------------------------------------------------------------------
192CONTAINS
193
194   INTEGER FUNCTION lib_mpp_alloc( kumout )
195      !!----------------------------------------------------------------------
196      !!              ***  routine lib_mpp_alloc  ***
197      !!----------------------------------------------------------------------
198      INTEGER, INTENT(in) ::   kumout   ! ocean.output logical unit
199      !!----------------------------------------------------------------------
200      !
201      ALLOCATE( t4ns(jpi,jprecj,jpk,2,2) , t4sn(jpi,jprecj,jpk,2,2) ,                                            &
202         &      t4ew(jpj,jpreci,jpk,2,2) , t4we(jpj,jpreci,jpk,2,2) ,                                            &
203         &      t4p1(jpi,jprecj,jpk,2,2) , t4p2(jpi,jprecj,jpk,2,2) ,                                            &
204         &      t3ns(jpi,jprecj,jpk,2)   , t3sn(jpi,jprecj,jpk,2)   ,                                            &
205         &      t3ew(jpj,jpreci,jpk,2)   , t3we(jpj,jpreci,jpk,2)   ,                                            &
206         &      t3p1(jpi,jprecj,jpk,2)   , t3p2(jpi,jprecj,jpk,2)   ,                                            &
207         &      t2ns(jpi,jprecj    ,2)   , t2sn(jpi,jprecj    ,2)   ,                                            &
208         &      t2ew(jpj,jpreci    ,2)   , t2we(jpj,jpreci    ,2)   ,                                            &
209         &      t2p1(jpi,jprecj    ,2)   , t2p2(jpi,jprecj    ,2)   ,                                            &
210         !
211         &      tr2ns(1-jpr2di:jpi+jpr2di,jprecj+jpr2dj,2) ,                                                     &
212         &      tr2sn(1-jpr2di:jpi+jpr2di,jprecj+jpr2dj,2) ,                                                     &
213         &      tr2ew(1-jpr2dj:jpj+jpr2dj,jpreci+jpr2di,2) ,                                                     &
214         &      tr2we(1-jpr2dj:jpj+jpr2dj,jpreci+jpr2di,2) ,                                                     &
215         !
216         &      ztab(jpiglo,4,jpk) , znorthloc(jpi,4,jpk) , znorthgloio(jpi,4,jpk,jpni) ,                        &
217         &      zfoldwk(jpi,4,jpk) ,                                                                             &
218         !
219         &      ztab_2d(jpiglo,4)  , znorthloc_2d(jpi,4)  , znorthgloio_2d(jpi,4,jpni)  ,                        &
220         &      zfoldwk_2d(jpi,4)  ,                                                                             &
221         !
222         &      ztab_e(jpiglo,4+2*jpr2dj) , znorthloc_e(jpi,4+2*jpr2dj) , znorthgloio_e(jpi,4+2*jpr2dj,jpni) ,   &
223         !
224         &      STAT=lib_mpp_alloc )
225         !
226      IF( lib_mpp_alloc /= 0 ) THEN
227         WRITE(kumout,cform_war)
228         WRITE(kumout,*) 'lib_mpp_alloc : failed to allocate arrays'
229      ENDIF
230      !
231   END FUNCTION lib_mpp_alloc
232
233
234   FUNCTION mynode( ldtxt, kumnam, kstop, localComm )
235      !!----------------------------------------------------------------------
236      !!                  ***  routine mynode  ***
237      !!                   
238      !! ** Purpose :   Find processor unit
239      !!----------------------------------------------------------------------
240      CHARACTER(len=*),DIMENSION(:), INTENT(  out) ::   ldtxt 
241      INTEGER                      , INTENT(in   ) ::   kumnam       ! namelist logical unit
242      INTEGER                      , INTENT(inout) ::   kstop        ! stop indicator
243      INTEGER, OPTIONAL            , INTENT(in   ) ::   localComm
244      !
245      INTEGER ::   mynode, ierr, code, ji, ii
246      LOGICAL ::   mpi_was_called
247      !
248      NAMELIST/nammpp/ cn_mpi_send, nn_buffer, jpni, jpnj, jpnij, ln_nnogather
249      !!----------------------------------------------------------------------
250      !
251      ii = 1
252      WRITE(ldtxt(ii),*)                                                                          ;   ii = ii + 1
253      WRITE(ldtxt(ii),*) 'mynode : mpi initialisation'                                            ;   ii = ii + 1
254      WRITE(ldtxt(ii),*) '~~~~~~ '                                                                ;   ii = ii + 1
255      !
256      jpni = -1; jpnj = -1; jpnij = -1
257      REWIND( kumnam )               ! Namelist namrun : parameters of the run
258      READ  ( kumnam, nammpp )
259      !                              ! control print
260      WRITE(ldtxt(ii),*) '   Namelist nammpp'                                                     ;   ii = ii + 1
261      WRITE(ldtxt(ii),*) '      mpi send type                      cn_mpi_send = ', cn_mpi_send   ;   ii = ii + 1
262      WRITE(ldtxt(ii),*) '      size in bytes of exported buffer   nn_buffer   = ', nn_buffer     ;   ii = ii + 1
263
264#if defined key_agrif
265      IF( .NOT. Agrif_Root() ) THEN
266         jpni  = Agrif_Parent(jpni ) 
267         jpnj  = Agrif_Parent(jpnj )
268         jpnij = Agrif_Parent(jpnij)
269      ENDIF
270#endif
271
272      IF(jpnij < 1)THEN
273         ! If jpnij is not specified in namelist then we calculate it - this
274         ! means there will be no land cutting out.
275         jpnij = jpni * jpnj
276      END IF
277
278      IF( (jpni < 1) .OR. (jpnj < 1) )THEN
279         WRITE(ldtxt(ii),*) '      jpni, jpnj and jpnij will be calculated automatically'; ii = ii + 1
280      ELSE
281         WRITE(ldtxt(ii),*) '      processor grid extent in i         jpni = ',jpni; ii = ii + 1
282         WRITE(ldtxt(ii),*) '      processor grid extent in j         jpnj = ',jpnj; ii = ii + 1
283         WRITE(ldtxt(ii),*) '      number of local domains           jpnij = ',jpnij; ii = ii +1
284      END IF
285
286      WRITE(ldtxt(ii),*) '      avoid use of mpi_allgather at the north fold  ln_nnogather = ', ln_nnogather  ; ii = ii + 1
287
288      CALL mpi_initialized ( mpi_was_called, code )
289      IF( code /= MPI_SUCCESS ) THEN
290         DO ji = 1, SIZE(ldtxt) 
291            IF( TRIM(ldtxt(ji)) /= '' )   WRITE(*,*) ldtxt(ji)      ! control print of mynode
292         END DO         
293         WRITE(*, cform_err)
294         WRITE(*, *) 'lib_mpp: Error in routine mpi_initialized'
295         CALL mpi_abort( mpi_comm_world, code, ierr )
296      ENDIF
297
298      IF( mpi_was_called ) THEN
299         !
300         SELECT CASE ( cn_mpi_send )
301         CASE ( 'S' )                ! Standard mpi send (blocking)
302            WRITE(ldtxt(ii),*) '           Standard blocking mpi send (send)'                     ;   ii = ii + 1
303         CASE ( 'B' )                ! Buffer mpi send (blocking)
304            WRITE(ldtxt(ii),*) '           Buffer blocking mpi send (bsend)'                      ;   ii = ii + 1
305            IF( Agrif_Root() )   CALL mpi_init_opa( ldtxt, ii, ierr ) 
306         CASE ( 'I' )                ! Immediate mpi send (non-blocking send)
307            WRITE(ldtxt(ii),*) '           Immediate non-blocking send (isend)'                   ;   ii = ii + 1
308            l_isend = .TRUE.
309         CASE DEFAULT
310            WRITE(ldtxt(ii),cform_err)                                                            ;   ii = ii + 1
311            WRITE(ldtxt(ii),*) '           bad value for cn_mpi_send = ', cn_mpi_send             ;   ii = ii + 1
312            kstop = kstop + 1
313         END SELECT
314      ELSE IF ( PRESENT(localComm) .and. .not. mpi_was_called ) THEN
315         WRITE(ldtxt(ii),*) ' lib_mpp: You cannot provide a local communicator '                  ;   ii = ii + 1
316         WRITE(ldtxt(ii),*) '          without calling MPI_Init before ! '                        ;   ii = ii + 1
317         kstop = kstop + 1
318      ELSE
319         SELECT CASE ( cn_mpi_send )
320         CASE ( 'S' )                ! Standard mpi send (blocking)
321            WRITE(ldtxt(ii),*) '           Standard blocking mpi send (send)'                     ;   ii = ii + 1
322            CALL mpi_init( ierr )
323         CASE ( 'B' )                ! Buffer mpi send (blocking)
324            WRITE(ldtxt(ii),*) '           Buffer blocking mpi send (bsend)'                      ;   ii = ii + 1
325            IF( Agrif_Root() )   CALL mpi_init_opa( ldtxt, ii, ierr )
326         CASE ( 'I' )                ! Immediate mpi send (non-blocking send)
327            WRITE(ldtxt(ii),*) '           Immediate non-blocking send (isend)'                   ;   ii = ii + 1
328            l_isend = .TRUE.
329            CALL mpi_init( ierr )
330         CASE DEFAULT
331            WRITE(ldtxt(ii),cform_err)                                                            ;   ii = ii + 1
332            WRITE(ldtxt(ii),*) '           bad value for cn_mpi_send = ', cn_mpi_send             ;   ii = ii + 1
333            kstop = kstop + 1
334         END SELECT
335         !
336      ENDIF
337
338      IF( PRESENT(localComm) ) THEN
339         IF( Agrif_Root() ) THEN
340            mpi_comm_opa = localComm
341         ENDIF
342      ELSE
343         CALL mpi_comm_dup( mpi_comm_world, mpi_comm_opa, code)
344         IF( code /= MPI_SUCCESS ) THEN
345            DO ji = 1, SIZE(ldtxt) 
346               IF( TRIM(ldtxt(ji)) /= '' )   WRITE(*,*) ldtxt(ji)      ! control print of mynode
347            END DO
348            WRITE(*, cform_err)
349            WRITE(*, *) ' lib_mpp: Error in routine mpi_comm_dup'
350            CALL mpi_abort( mpi_comm_world, code, ierr )
351         ENDIF
352      ENDIF
353
354      CALL mpi_comm_rank( mpi_comm_opa, mpprank, ierr )
355      CALL mpi_comm_size( mpi_comm_opa, mppsize, ierr )
356      mynode = mpprank
357      !
358#if defined key_mpp_rep
359      CALL MPI_OP_CREATE(DDPDD_MPI, .TRUE., MPI_SUMDD, ierr)
360#endif
361      !
362   END FUNCTION mynode
363
364
365   SUBROUTINE mpp_lnk_3d( ptab, cd_type, psgn, cd_mpp, pval )
366      !!----------------------------------------------------------------------
367      !!                  ***  routine mpp_lnk_3d  ***
368      !!
369      !! ** Purpose :   Message passing manadgement
370      !!
371      !! ** Method  :   Use mppsend and mpprecv function for passing mask
372      !!      between processors following neighboring subdomains.
373      !!            domain parameters
374      !!                    nlci   : first dimension of the local subdomain
375      !!                    nlcj   : second dimension of the local subdomain
376      !!                    nbondi : mark for "east-west local boundary"
377      !!                    nbondj : mark for "north-south local boundary"
378      !!                    noea   : number for local neighboring processors
379      !!                    nowe   : number for local neighboring processors
380      !!                    noso   : number for local neighboring processors
381      !!                    nono   : number for local neighboring processors
382      !!
383      !! ** Action  :   ptab with update value at its periphery
384      !!
385      !!----------------------------------------------------------------------
386      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptab     ! 3D array on which the boundary condition is applied
387      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type  ! define the nature of ptab array grid-points
388      !                                                             ! = T , U , V , F , W 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, jk, 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
401      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value
402      ELSE                         ;   zland = 0.e0      ! zero by default
403      ENDIF
404
405      ! 1. standard boundary treatment
406      ! ------------------------------
407      IF( PRESENT( cd_mpp ) ) THEN      ! only fill added line/raw with existing values
408         !
409         ! WARNING ptab is defined only between nld and nle
410         DO jk = 1, jpk
411            DO jj = nlcj+1, jpj                 ! added line(s)   (inner only)
412               ptab(nldi  :nlei  , jj          ,jk) = ptab(nldi:nlei,     nlej,jk)   
413               ptab(1     :nldi-1, jj          ,jk) = ptab(nldi     ,     nlej,jk)
414               ptab(nlei+1:nlci  , jj          ,jk) = ptab(     nlei,     nlej,jk)
415            END DO
416            DO ji = nlci+1, jpi                 ! added column(s) (full)
417               ptab(ji           ,nldj  :nlej  ,jk) = ptab(     nlei,nldj:nlej,jk)
418               ptab(ji           ,1     :nldj-1,jk) = ptab(     nlei,nldj     ,jk)
419               ptab(ji           ,nlej+1:jpj   ,jk) = ptab(     nlei,     nlej,jk)
420            END DO
421         END DO
422         !
423      ELSE                              ! standard close or cyclic treatment
424         !
425         !                                   ! East-West boundaries
426         !                                        !* Cyclic east-west
427         IF( nbondi == 2 .AND. (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
428            ptab( 1 ,:,:) = ptab(jpim1,:,:)
429            ptab(jpi,:,:) = ptab(  2  ,:,:)
430         ELSE                                     !* closed
431            IF( .NOT. cd_type == 'F' )   ptab(     1       :jpreci,:,:) = zland    ! south except F-point
432                                         ptab(nlci-jpreci+1:jpi   ,:,:) = zland    ! north
433         ENDIF
434         !                                   ! North-South boundaries (always closed)
435         IF( .NOT. cd_type == 'F' )   ptab(:,     1       :jprecj,:) = zland       ! south except F-point
436                                      ptab(:,nlcj-jprecj+1:jpj   ,:) = zland       ! north
437         !
438      ENDIF
439
440      ! 2. East and west directions exchange
441      ! ------------------------------------
442      ! we play with the neigbours AND the row number because of the periodicity
443      !
444      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
445      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
446         iihom = nlci-nreci
447         DO jl = 1, jpreci
448            t3ew(:,jl,:,1) = ptab(jpreci+jl,:,:)
449            t3we(:,jl,:,1) = ptab(iihom +jl,:,:)
450         END DO
451      END SELECT 
452      !
453      !                           ! Migrations
454      imigr = jpreci * jpj * jpk
455      !
456      SELECT CASE ( nbondi ) 
457      CASE ( -1 )
458         CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req1 )
459         CALL mpprecv( 1, t3ew(1,1,1,2), imigr, noea )
460         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
461      CASE ( 0 )
462         CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 )
463         CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req2 )
464         CALL mpprecv( 1, t3ew(1,1,1,2), imigr, noea )
465         CALL mpprecv( 2, t3we(1,1,1,2), imigr, nowe )
466         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
467         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
468      CASE ( 1 )
469         CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 )
470         CALL mpprecv( 2, t3we(1,1,1,2), imigr, nowe )
471         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
472      END SELECT
473      !
474      !                           ! Write Dirichlet lateral conditions
475      iihom = nlci-jpreci
476      !
477      SELECT CASE ( nbondi )
478      CASE ( -1 )
479         DO jl = 1, jpreci
480            ptab(iihom+jl,:,:) = t3ew(:,jl,:,2)
481         END DO
482      CASE ( 0 ) 
483         DO jl = 1, jpreci
484            ptab(jl      ,:,:) = t3we(:,jl,:,2)
485            ptab(iihom+jl,:,:) = t3ew(:,jl,:,2)
486         END DO
487      CASE ( 1 )
488         DO jl = 1, jpreci
489            ptab(jl      ,:,:) = t3we(:,jl,:,2)
490         END DO
491      END SELECT
492
493
494      ! 3. North and south directions
495      ! -----------------------------
496      ! always closed : we play only with the neigbours
497      !
498      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
499         ijhom = nlcj-nrecj
500         DO jl = 1, jprecj
501            t3sn(:,jl,:,1) = ptab(:,ijhom +jl,:)
502            t3ns(:,jl,:,1) = ptab(:,jprecj+jl,:)
503         END DO
504      ENDIF
505      !
506      !                           ! Migrations
507      imigr = jprecj * jpi * jpk
508      !
509      SELECT CASE ( nbondj )     
510      CASE ( -1 )
511         CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req1 )
512         CALL mpprecv( 3, t3ns(1,1,1,2), imigr, nono )
513         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
514      CASE ( 0 )
515         CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 )
516         CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req2 )
517         CALL mpprecv( 3, t3ns(1,1,1,2), imigr, nono )
518         CALL mpprecv( 4, t3sn(1,1,1,2), imigr, noso )
519         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
520         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
521      CASE ( 1 ) 
522         CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 )
523         CALL mpprecv( 4, t3sn(1,1,1,2), imigr, noso )
524         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
525      END SELECT
526      !
527      !                           ! Write Dirichlet lateral conditions
528      ijhom = nlcj-jprecj
529      !
530      SELECT CASE ( nbondj )
531      CASE ( -1 )
532         DO jl = 1, jprecj
533            ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2)
534         END DO
535      CASE ( 0 ) 
536         DO jl = 1, jprecj
537            ptab(:,jl      ,:) = t3sn(:,jl,:,2)
538            ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2)
539         END DO
540      CASE ( 1 )
541         DO jl = 1, jprecj
542            ptab(:,jl,:) = t3sn(:,jl,:,2)
543         END DO
544      END SELECT
545
546
547      ! 4. north fold treatment
548      ! -----------------------
549      !
550      IF( npolj /= 0 .AND. .NOT. PRESENT(cd_mpp) ) THEN
551         !
552         SELECT CASE ( jpni )
553         CASE ( 1 )     ;   CALL lbc_nfd      ( ptab, cd_type, psgn )   ! only 1 northern proc, no mpp
554         CASE DEFAULT   ;   CALL mpp_lbc_north( ptab, cd_type, psgn )   ! for all northern procs.
555         END SELECT
556         !
557      ENDIF
558      !
559   END SUBROUTINE mpp_lnk_3d
560
561
562   SUBROUTINE mpp_lnk_2d( pt2d, cd_type, psgn, cd_mpp, pval )
563      !!----------------------------------------------------------------------
564      !!                  ***  routine mpp_lnk_2d  ***
565      !!                 
566      !! ** Purpose :   Message passing manadgement for 2d array
567      !!
568      !! ** Method  :   Use mppsend and mpprecv function for passing mask
569      !!      between processors following neighboring subdomains.
570      !!            domain parameters
571      !!                    nlci   : first dimension of the local subdomain
572      !!                    nlcj   : second dimension of the local subdomain
573      !!                    nbondi : mark for "east-west local boundary"
574      !!                    nbondj : mark for "north-south local boundary"
575      !!                    noea   : number for local neighboring processors
576      !!                    nowe   : number for local neighboring processors
577      !!                    noso   : number for local neighboring processors
578      !!                    nono   : number for local neighboring processors
579      !!
580      !!----------------------------------------------------------------------
581      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   pt2d     ! 2D array on which the boundary condition is applied
582      CHARACTER(len=1)            , INTENT(in   ) ::   cd_type  ! define the nature of ptab array grid-points
583      !                                                         ! = T , U , V , F , W and I points
584      REAL(wp)                    , INTENT(in   ) ::   psgn     ! =-1 the sign change across the north fold boundary
585      !                                                         ! =  1. , the sign is kept
586      CHARACTER(len=3), OPTIONAL  , INTENT(in   ) ::   cd_mpp   ! fill the overlap area only
587      REAL(wp)        , OPTIONAL  , INTENT(in   ) ::   pval     ! background value (used at closed boundaries)
588      !!
589      INTEGER  ::   ji, jj, jl   ! dummy loop indices
590      INTEGER  ::   imigr, iihom, ijhom        ! temporary integers
591      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
592      REAL(wp) ::   zland
593      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
594      !!----------------------------------------------------------------------
595
596      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value
597      ELSE                         ;   zland = 0.e0      ! zero by default
598      ENDIF
599
600      ! 1. standard boundary treatment
601      ! ------------------------------
602      !
603      IF( PRESENT( cd_mpp ) ) THEN      ! only fill added line/raw with existing values
604         !
605         ! WARNING pt2d is defined only between nld and nle
606         DO jj = nlcj+1, jpj                 ! added line(s)   (inner only)
607            pt2d(nldi  :nlei  , jj          ) = pt2d(nldi:nlei,     nlej)   
608            pt2d(1     :nldi-1, jj          ) = pt2d(nldi     ,     nlej)
609            pt2d(nlei+1:nlci  , jj          ) = pt2d(     nlei,     nlej)
610         END DO
611         DO ji = nlci+1, jpi                 ! added column(s) (full)
612            pt2d(ji           ,nldj  :nlej  ) = pt2d(     nlei,nldj:nlej)
613            pt2d(ji           ,1     :nldj-1) = pt2d(     nlei,nldj     )
614            pt2d(ji           ,nlej+1:jpj   ) = pt2d(     nlei,     nlej)
615         END DO
616         !
617      ELSE                              ! standard close or cyclic treatment
618         !
619         !                                   ! East-West boundaries
620         IF( nbondi == 2 .AND.   &                ! Cyclic east-west
621            &    (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
622            pt2d( 1 ,:) = pt2d(jpim1,:)                                    ! west
623            pt2d(jpi,:) = pt2d(  2  ,:)                                    ! east
624         ELSE                                     ! closed
625            IF( .NOT. cd_type == 'F' )   pt2d(     1       :jpreci,:) = zland    ! south except F-point
626                                         pt2d(nlci-jpreci+1:jpi   ,:) = zland    ! north
627         ENDIF
628         !                                   ! North-South boundaries (always closed)
629            IF( .NOT. cd_type == 'F' )   pt2d(:,     1       :jprecj) = zland    !south except F-point
630                                         pt2d(:,nlcj-jprecj+1:jpj   ) = zland    ! north
631         !
632      ENDIF
633
634      ! 2. East and west directions exchange
635      ! ------------------------------------
636      ! we play with the neigbours AND the row number because of the periodicity
637      !
638      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
639      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
640         iihom = nlci-nreci
641         DO jl = 1, jpreci
642            t2ew(:,jl,1) = pt2d(jpreci+jl,:)
643            t2we(:,jl,1) = pt2d(iihom +jl,:)
644         END DO
645      END SELECT
646      !
647      !                           ! Migrations
648      imigr = jpreci * jpj
649      !
650      SELECT CASE ( nbondi )
651      CASE ( -1 )
652         CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req1 )
653         CALL mpprecv( 1, t2ew(1,1,2), imigr, noea )
654         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
655      CASE ( 0 )
656         CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 )
657         CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req2 )
658         CALL mpprecv( 1, t2ew(1,1,2), imigr, noea )
659         CALL mpprecv( 2, t2we(1,1,2), imigr, nowe )
660         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
661         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
662      CASE ( 1 )
663         CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 )
664         CALL mpprecv( 2, t2we(1,1,2), imigr, nowe )
665         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
666      END SELECT
667      !
668      !                           ! Write Dirichlet lateral conditions
669      iihom = nlci - jpreci
670      !
671      SELECT CASE ( nbondi )
672      CASE ( -1 )
673         DO jl = 1, jpreci
674            pt2d(iihom+jl,:) = t2ew(:,jl,2)
675         END DO
676      CASE ( 0 )
677         DO jl = 1, jpreci
678            pt2d(jl      ,:) = t2we(:,jl,2)
679            pt2d(iihom+jl,:) = t2ew(:,jl,2)
680         END DO
681      CASE ( 1 )
682         DO jl = 1, jpreci
683            pt2d(jl      ,:) = t2we(:,jl,2)
684         END DO
685      END SELECT
686
687
688      ! 3. North and south directions
689      ! -----------------------------
690      ! always closed : we play only with the neigbours
691      !
692      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
693         ijhom = nlcj-nrecj
694         DO jl = 1, jprecj
695            t2sn(:,jl,1) = pt2d(:,ijhom +jl)
696            t2ns(:,jl,1) = pt2d(:,jprecj+jl)
697         END DO
698      ENDIF
699      !
700      !                           ! Migrations
701      imigr = jprecj * jpi
702      !
703      SELECT CASE ( nbondj )
704      CASE ( -1 )
705         CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req1 )
706         CALL mpprecv( 3, t2ns(1,1,2), imigr, nono )
707         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
708      CASE ( 0 )
709         CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 )
710         CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req2 )
711         CALL mpprecv( 3, t2ns(1,1,2), imigr, nono )
712         CALL mpprecv( 4, t2sn(1,1,2), imigr, noso )
713         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
714         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
715      CASE ( 1 )
716         CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 )
717         CALL mpprecv( 4, t2sn(1,1,2), imigr, noso )
718         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
719      END SELECT
720      !
721      !                           ! Write Dirichlet lateral conditions
722      ijhom = nlcj - jprecj
723      !
724      SELECT CASE ( nbondj )
725      CASE ( -1 )
726         DO jl = 1, jprecj
727            pt2d(:,ijhom+jl) = t2ns(:,jl,2)
728         END DO
729      CASE ( 0 )
730         DO jl = 1, jprecj
731            pt2d(:,jl      ) = t2sn(:,jl,2)
732            pt2d(:,ijhom+jl) = t2ns(:,jl,2)
733         END DO
734      CASE ( 1 ) 
735         DO jl = 1, jprecj
736            pt2d(:,jl      ) = t2sn(:,jl,2)
737         END DO
738      END SELECT
739
740
741      ! 4. north fold treatment
742      ! -----------------------
743      !
744      IF( npolj /= 0 .AND. .NOT. PRESENT(cd_mpp) ) THEN
745         !
746         SELECT CASE ( jpni )
747         CASE ( 1 )     ;   CALL lbc_nfd      ( pt2d, cd_type, psgn )   ! only 1 northern proc, no mpp
748         CASE DEFAULT   ;   CALL mpp_lbc_north( pt2d, cd_type, psgn )   ! for all northern procs.
749         END SELECT
750         !
751      ENDIF
752      !
753   END SUBROUTINE mpp_lnk_2d
754
755
756   SUBROUTINE mpp_lnk_3d_gather( ptab1, cd_type1, ptab2, cd_type2, psgn )
757      !!----------------------------------------------------------------------
758      !!                  ***  routine mpp_lnk_3d_gather  ***
759      !!
760      !! ** Purpose :   Message passing manadgement for two 3D arrays
761      !!
762      !! ** Method  :   Use mppsend and mpprecv function for passing mask
763      !!      between processors following neighboring subdomains.
764      !!            domain parameters
765      !!                    nlci   : first dimension of the local subdomain
766      !!                    nlcj   : second dimension of the local subdomain
767      !!                    nbondi : mark for "east-west local boundary"
768      !!                    nbondj : mark for "north-south local boundary"
769      !!                    noea   : number for local neighboring processors
770      !!                    nowe   : number for local neighboring processors
771      !!                    noso   : number for local neighboring processors
772      !!                    nono   : number for local neighboring processors
773      !!
774      !! ** Action  :   ptab1 and ptab2  with update value at its periphery
775      !!
776      !!----------------------------------------------------------------------
777      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptab1     ! first and second 3D array on which
778      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptab2     ! the boundary condition is applied
779      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type1  ! nature of ptab1 and ptab2 arrays
780      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type2  ! i.e. grid-points = T , U , V , F or W points
781      REAL(wp)                        , INTENT(in   ) ::   psgn      ! =-1 the sign change across the north fold boundary
782      !!                                                             ! =  1. , the sign is kept
783      INTEGER  ::   jl   ! dummy loop indices
784      INTEGER  ::   imigr, iihom, ijhom        ! temporary integers
785      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
786      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
787      !!----------------------------------------------------------------------
788
789      ! 1. standard boundary treatment
790      ! ------------------------------
791      !                                      ! East-West boundaries
792      !                                           !* Cyclic east-west
793      IF( nbondi == 2 .AND. (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
794         ptab1( 1 ,:,:) = ptab1(jpim1,:,:)
795         ptab1(jpi,:,:) = ptab1(  2  ,:,:)
796         ptab2( 1 ,:,:) = ptab2(jpim1,:,:)
797         ptab2(jpi,:,:) = ptab2(  2  ,:,:)
798      ELSE                                        !* closed
799         IF( .NOT. cd_type1 == 'F' )   ptab1(     1       :jpreci,:,:) = 0.e0    ! south except at F-point
800         IF( .NOT. cd_type2 == 'F' )   ptab2(     1       :jpreci,:,:) = 0.e0
801                                       ptab1(nlci-jpreci+1:jpi   ,:,:) = 0.e0    ! north
802                                       ptab2(nlci-jpreci+1:jpi   ,:,:) = 0.e0
803      ENDIF
804
805     
806      !                                      ! North-South boundaries
807      IF( .NOT. cd_type1 == 'F' )   ptab1(:,     1       :jprecj,:) = 0.e0    ! south except at F-point
808      IF( .NOT. cd_type2 == 'F' )   ptab2(:,     1       :jprecj,:) = 0.e0
809                                    ptab1(:,nlcj-jprecj+1:jpj   ,:) = 0.e0    ! north
810                                    ptab2(:,nlcj-jprecj+1:jpj   ,:) = 0.e0
811
812
813      ! 2. East and west directions exchange
814      ! ------------------------------------
815      ! we play with the neigbours AND the row number because of the periodicity
816      !
817      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
818      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
819         iihom = nlci-nreci
820         DO jl = 1, jpreci
821            t4ew(:,jl,:,1,1) = ptab1(jpreci+jl,:,:)
822            t4we(:,jl,:,1,1) = ptab1(iihom +jl,:,:)
823            t4ew(:,jl,:,2,1) = ptab2(jpreci+jl,:,:)
824            t4we(:,jl,:,2,1) = ptab2(iihom +jl,:,:)
825         END DO
826      END SELECT
827      !
828      !                           ! Migrations
829      imigr = jpreci * jpj * jpk *2
830      !
831      SELECT CASE ( nbondi ) 
832      CASE ( -1 )
833         CALL mppsend( 2, t4we(1,1,1,1,1), imigr, noea, ml_req1 )
834         CALL mpprecv( 1, t4ew(1,1,1,1,2), imigr, noea )
835         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
836      CASE ( 0 )
837         CALL mppsend( 1, t4ew(1,1,1,1,1), imigr, nowe, ml_req1 )
838         CALL mppsend( 2, t4we(1,1,1,1,1), imigr, noea, ml_req2 )
839         CALL mpprecv( 1, t4ew(1,1,1,1,2), imigr, noea )
840         CALL mpprecv( 2, t4we(1,1,1,1,2), imigr, nowe )
841         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
842         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
843      CASE ( 1 )
844         CALL mppsend( 1, t4ew(1,1,1,1,1), imigr, nowe, ml_req1 )
845         CALL mpprecv( 2, t4we(1,1,1,1,2), imigr, nowe )
846         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
847      END SELECT
848      !
849      !                           ! Write Dirichlet lateral conditions
850      iihom = nlci - jpreci
851      !
852      SELECT CASE ( nbondi )
853      CASE ( -1 )
854         DO jl = 1, jpreci
855            ptab1(iihom+jl,:,:) = t4ew(:,jl,:,1,2)
856            ptab2(iihom+jl,:,:) = t4ew(:,jl,:,2,2)
857         END DO
858      CASE ( 0 ) 
859         DO jl = 1, jpreci
860            ptab1(jl      ,:,:) = t4we(:,jl,:,1,2)
861            ptab1(iihom+jl,:,:) = t4ew(:,jl,:,1,2)
862            ptab2(jl      ,:,:) = t4we(:,jl,:,2,2)
863            ptab2(iihom+jl,:,:) = t4ew(:,jl,:,2,2)
864         END DO
865      CASE ( 1 )
866         DO jl = 1, jpreci
867            ptab1(jl      ,:,:) = t4we(:,jl,:,1,2)
868            ptab2(jl      ,:,:) = t4we(:,jl,:,2,2)
869         END DO
870      END SELECT
871
872
873      ! 3. North and south directions
874      ! -----------------------------
875      ! always closed : we play only with the neigbours
876      !
877      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
878         ijhom = nlcj - nrecj
879         DO jl = 1, jprecj
880            t4sn(:,jl,:,1,1) = ptab1(:,ijhom +jl,:)
881            t4ns(:,jl,:,1,1) = ptab1(:,jprecj+jl,:)
882            t4sn(:,jl,:,2,1) = ptab2(:,ijhom +jl,:)
883            t4ns(:,jl,:,2,1) = ptab2(:,jprecj+jl,:)
884         END DO
885      ENDIF
886      !
887      !                           ! Migrations
888      imigr = jprecj * jpi * jpk * 2
889      !
890      SELECT CASE ( nbondj )     
891      CASE ( -1 )
892         CALL mppsend( 4, t4sn(1,1,1,1,1), imigr, nono, ml_req1 )
893         CALL mpprecv( 3, t4ns(1,1,1,1,2), imigr, nono )
894         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
895      CASE ( 0 )
896         CALL mppsend( 3, t4ns(1,1,1,1,1), imigr, noso, ml_req1 )
897         CALL mppsend( 4, t4sn(1,1,1,1,1), imigr, nono, ml_req2 )
898         CALL mpprecv( 3, t4ns(1,1,1,1,2), imigr, nono )
899         CALL mpprecv( 4, t4sn(1,1,1,1,2), imigr, noso )
900         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
901         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
902      CASE ( 1 ) 
903         CALL mppsend( 3, t4ns(1,1,1,1,1), imigr, noso, ml_req1 )
904         CALL mpprecv( 4, t4sn(1,1,1,1,2), imigr, noso )
905         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
906      END SELECT
907      !
908      !                           ! Write Dirichlet lateral conditions
909      ijhom = nlcj - jprecj
910      !
911      SELECT CASE ( nbondj )
912      CASE ( -1 )
913         DO jl = 1, jprecj
914            ptab1(:,ijhom+jl,:) = t4ns(:,jl,:,1,2)
915            ptab2(:,ijhom+jl,:) = t4ns(:,jl,:,2,2)
916         END DO
917      CASE ( 0 ) 
918         DO jl = 1, jprecj
919            ptab1(:,jl      ,:) = t4sn(:,jl,:,1,2)
920            ptab1(:,ijhom+jl,:) = t4ns(:,jl,:,1,2)
921            ptab2(:,jl      ,:) = t4sn(:,jl,:,2,2)
922            ptab2(:,ijhom+jl,:) = t4ns(:,jl,:,2,2)
923         END DO
924      CASE ( 1 )
925         DO jl = 1, jprecj
926            ptab1(:,jl,:) = t4sn(:,jl,:,1,2)
927            ptab2(:,jl,:) = t4sn(:,jl,:,2,2)
928         END DO
929      END SELECT
930
931
932      ! 4. north fold treatment
933      ! -----------------------
934      IF( npolj /= 0 ) THEN
935         !
936         SELECT CASE ( jpni )
937         CASE ( 1 )                                           
938            CALL lbc_nfd      ( ptab1, cd_type1, psgn )   ! only for northern procs.
939            CALL lbc_nfd      ( ptab2, cd_type2, psgn )
940         CASE DEFAULT
941            CALL mpp_lbc_north( ptab1, cd_type1, psgn )   ! for all northern procs.
942            CALL mpp_lbc_north (ptab2, cd_type2, psgn)
943         END SELECT 
944         !
945      ENDIF
946      !
947   END SUBROUTINE mpp_lnk_3d_gather
948
949
950   SUBROUTINE mpp_lnk_2d_e( pt2d, cd_type, psgn )
951      !!----------------------------------------------------------------------
952      !!                  ***  routine mpp_lnk_2d_e  ***
953      !!                 
954      !! ** Purpose :   Message passing manadgement for 2d array (with halo)
955      !!
956      !! ** Method  :   Use mppsend and mpprecv function for passing mask
957      !!      between processors following neighboring subdomains.
958      !!            domain parameters
959      !!                    nlci   : first dimension of the local subdomain
960      !!                    nlcj   : second dimension of the local subdomain
961      !!                    jpr2di : number of rows for extra outer halo
962      !!                    jpr2dj : number of columns for extra outer halo
963      !!                    nbondi : mark for "east-west local boundary"
964      !!                    nbondj : mark for "north-south local boundary"
965      !!                    noea   : number for local neighboring processors
966      !!                    nowe   : number for local neighboring processors
967      !!                    noso   : number for local neighboring processors
968      !!                    nono   : number for local neighboring processors
969      !!
970      !!----------------------------------------------------------------------
971      REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj), INTENT(inout) ::   pt2d     ! 2D array with extra halo
972      CHARACTER(len=1)                                            , INTENT(in   ) ::   cd_type  ! nature of ptab array grid-points
973      !                                                                                         ! = T , U , V , F , W and I points
974      REAL(wp)                                                    , INTENT(in   ) ::   psgn     ! =-1 the sign change across the
975      !!                                                                                        ! north boundary, =  1. otherwise
976      INTEGER  ::   jl   ! dummy loop indices
977      INTEGER  ::   imigr, iihom, ijhom        ! temporary integers
978      INTEGER  ::   ipreci, iprecj             ! temporary integers
979      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
980      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
981      !!----------------------------------------------------------------------
982
983      ipreci = jpreci + jpr2di      ! take into account outer extra 2D overlap area
984      iprecj = jprecj + jpr2dj
985
986
987      ! 1. standard boundary treatment
988      ! ------------------------------
989      ! Order matters Here !!!!
990      !
991      !                                      !* North-South boundaries (always colsed)
992      IF( .NOT. cd_type == 'F' )   pt2d(:,  1-jpr2dj   :  jprecj  ) = 0.e0    ! south except at F-point
993                                   pt2d(:,nlcj-jprecj+1:jpj+jpr2dj) = 0.e0    ! north
994                               
995      !                                      ! East-West boundaries
996      !                                           !* Cyclic east-west
997      IF( nbondi == 2 .AND. (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
998         pt2d(1-jpr2di:     1    ,:) = pt2d(jpim1-jpr2di:  jpim1 ,:)       ! east
999         pt2d(   jpi  :jpi+jpr2di,:) = pt2d(     2      :2+jpr2di,:)       ! west
1000         !
1001      ELSE                                        !* closed
1002         IF( .NOT. cd_type == 'F' )   pt2d(  1-jpr2di   :jpreci    ,:) = 0.e0    ! south except at F-point
1003                                      pt2d(nlci-jpreci+1:jpi+jpr2di,:) = 0.e0    ! north
1004      ENDIF
1005      !
1006
1007      ! north fold treatment
1008      ! -----------------------
1009      IF( npolj /= 0 ) THEN
1010         !
1011         SELECT CASE ( jpni )
1012         CASE ( 1 )     ;   CALL lbc_nfd        ( pt2d(1:jpi,1:jpj+jpr2dj), cd_type, psgn, pr2dj=jpr2dj )
1013         CASE DEFAULT   ;   CALL mpp_lbc_north_e( pt2d                    , cd_type, psgn               )
1014         END SELECT 
1015         !
1016      ENDIF
1017
1018      ! 2. East and west directions exchange
1019      ! ------------------------------------
1020      ! we play with the neigbours AND the row number because of the periodicity
1021      !
1022      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
1023      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
1024         iihom = nlci-nreci-jpr2di
1025         DO jl = 1, ipreci
1026            tr2ew(:,jl,1) = pt2d(jpreci+jl,:)
1027            tr2we(:,jl,1) = pt2d(iihom +jl,:)
1028         END DO
1029      END SELECT
1030      !
1031      !                           ! Migrations
1032      imigr = ipreci * ( jpj + 2*jpr2dj)
1033      !
1034      SELECT CASE ( nbondi )
1035      CASE ( -1 )
1036         CALL mppsend( 2, tr2we(1-jpr2dj,1,1), imigr, noea, ml_req1 )
1037         CALL mpprecv( 1, tr2ew(1-jpr2dj,1,2), imigr, noea )
1038         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1039      CASE ( 0 )
1040         CALL mppsend( 1, tr2ew(1-jpr2dj,1,1), imigr, nowe, ml_req1 )
1041         CALL mppsend( 2, tr2we(1-jpr2dj,1,1), imigr, noea, ml_req2 )
1042         CALL mpprecv( 1, tr2ew(1-jpr2dj,1,2), imigr, noea )
1043         CALL mpprecv( 2, tr2we(1-jpr2dj,1,2), imigr, nowe )
1044         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1045         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
1046      CASE ( 1 )
1047         CALL mppsend( 1, tr2ew(1-jpr2dj,1,1), imigr, nowe, ml_req1 )
1048         CALL mpprecv( 2, tr2we(1-jpr2dj,1,2), imigr, nowe )
1049         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1050      END SELECT
1051      !
1052      !                           ! Write Dirichlet lateral conditions
1053      iihom = nlci - jpreci
1054      !
1055      SELECT CASE ( nbondi )
1056      CASE ( -1 )
1057         DO jl = 1, ipreci
1058            pt2d(iihom+jl,:) = tr2ew(:,jl,2)
1059         END DO
1060      CASE ( 0 )
1061         DO jl = 1, ipreci
1062            pt2d(jl-jpr2di,:) = tr2we(:,jl,2)
1063            pt2d( iihom+jl,:) = tr2ew(:,jl,2)
1064         END DO
1065      CASE ( 1 )
1066         DO jl = 1, ipreci
1067            pt2d(jl-jpr2di,:) = tr2we(:,jl,2)
1068         END DO
1069      END SELECT
1070
1071
1072      ! 3. North and south directions
1073      ! -----------------------------
1074      ! always closed : we play only with the neigbours
1075      !
1076      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
1077         ijhom = nlcj-nrecj-jpr2dj
1078         DO jl = 1, iprecj
1079            tr2sn(:,jl,1) = pt2d(:,ijhom +jl)
1080            tr2ns(:,jl,1) = pt2d(:,jprecj+jl)
1081         END DO
1082      ENDIF
1083      !
1084      !                           ! Migrations
1085      imigr = iprecj * ( jpi + 2*jpr2di )
1086      !
1087      SELECT CASE ( nbondj )
1088      CASE ( -1 )
1089         CALL mppsend( 4, tr2sn(1-jpr2di,1,1), imigr, nono, ml_req1 )
1090         CALL mpprecv( 3, tr2ns(1-jpr2di,1,2), imigr, nono )
1091         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1092      CASE ( 0 )
1093         CALL mppsend( 3, tr2ns(1-jpr2di,1,1), imigr, noso, ml_req1 )
1094         CALL mppsend( 4, tr2sn(1-jpr2di,1,1), imigr, nono, ml_req2 )
1095         CALL mpprecv( 3, tr2ns(1-jpr2di,1,2), imigr, nono )
1096         CALL mpprecv( 4, tr2sn(1-jpr2di,1,2), imigr, noso )
1097         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1098         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
1099      CASE ( 1 )
1100         CALL mppsend( 3, tr2ns(1-jpr2di,1,1), imigr, noso, ml_req1 )
1101         CALL mpprecv( 4, tr2sn(1-jpr2di,1,2), imigr, noso )
1102         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1103      END SELECT
1104      !
1105      !                           ! Write Dirichlet lateral conditions
1106      ijhom = nlcj - jprecj 
1107      !
1108      SELECT CASE ( nbondj )
1109      CASE ( -1 )
1110         DO jl = 1, iprecj
1111            pt2d(:,ijhom+jl) = tr2ns(:,jl,2)
1112         END DO
1113      CASE ( 0 )
1114         DO jl = 1, iprecj
1115            pt2d(:,jl-jpr2dj) = tr2sn(:,jl,2)
1116            pt2d(:,ijhom+jl ) = tr2ns(:,jl,2)
1117         END DO
1118      CASE ( 1 ) 
1119         DO jl = 1, iprecj
1120            pt2d(:,jl-jpr2dj) = tr2sn(:,jl,2)
1121         END DO
1122      END SELECT
1123
1124   END SUBROUTINE mpp_lnk_2d_e
1125
1126
1127   SUBROUTINE mppsend( ktyp, pmess, kbytes, kdest, md_req )
1128      !!----------------------------------------------------------------------
1129      !!                  ***  routine mppsend  ***
1130      !!                   
1131      !! ** Purpose :   Send messag passing array
1132      !!
1133      !!----------------------------------------------------------------------
1134      REAL(wp), INTENT(inout) ::   pmess(*)   ! array of real
1135      INTEGER , INTENT(in   ) ::   kbytes     ! size of the array pmess
1136      INTEGER , INTENT(in   ) ::   kdest      ! receive process number
1137      INTEGER , INTENT(in   ) ::   ktyp       ! tag of the message
1138      INTEGER , INTENT(in   ) ::   md_req     ! argument for isend
1139      !!
1140      INTEGER ::   iflag
1141      !!----------------------------------------------------------------------
1142      !
1143      SELECT CASE ( cn_mpi_send )
1144      CASE ( 'S' )                ! Standard mpi send (blocking)
1145         CALL mpi_send ( pmess, kbytes, mpi_double_precision, kdest , ktyp, mpi_comm_opa        , iflag )
1146      CASE ( 'B' )                ! Buffer mpi send (blocking)
1147         CALL mpi_bsend( pmess, kbytes, mpi_double_precision, kdest , ktyp, mpi_comm_opa        , iflag )
1148      CASE ( 'I' )                ! Immediate mpi send (non-blocking send)
1149         ! be carefull, one more argument here : the mpi request identifier..
1150         CALL mpi_isend( pmess, kbytes, mpi_double_precision, kdest , ktyp, mpi_comm_opa, md_req, iflag )
1151      END SELECT
1152      !
1153   END SUBROUTINE mppsend
1154
1155
1156   SUBROUTINE mpprecv( ktyp, pmess, kbytes, ksource )
1157      !!----------------------------------------------------------------------
1158      !!                  ***  routine mpprecv  ***
1159      !!
1160      !! ** Purpose :   Receive messag passing array
1161      !!
1162      !!----------------------------------------------------------------------
1163      REAL(wp), INTENT(inout) ::   pmess(*)   ! array of real
1164      INTEGER , INTENT(in   ) ::   kbytes     ! suze of the array pmess
1165      INTEGER , INTENT(in   ) ::   ktyp       ! Tag of the recevied message
1166      INTEGER, OPTIONAL, INTENT(in) :: ksource    ! source process number
1167      !!
1168      INTEGER :: istatus(mpi_status_size)
1169      INTEGER :: iflag
1170      INTEGER :: use_source
1171      !!----------------------------------------------------------------------
1172      !
1173
1174      ! If a specific process number has been passed to the receive call,
1175      ! use that one. Default is to use mpi_any_source
1176      use_source=mpi_any_source
1177      if(present(ksource)) then
1178         use_source=ksource
1179      end if
1180
1181      CALL mpi_recv( pmess, kbytes, mpi_double_precision, use_source, ktyp, mpi_comm_opa, istatus, iflag )
1182      !
1183   END SUBROUTINE mpprecv
1184
1185
1186   SUBROUTINE mppgather( ptab, kp, pio )
1187      !!----------------------------------------------------------------------
1188      !!                   ***  routine mppgather  ***
1189      !!                   
1190      !! ** Purpose :   Transfert between a local subdomain array and a work
1191      !!     array which is distributed following the vertical level.
1192      !!
1193      !!----------------------------------------------------------------------
1194      REAL(wp), DIMENSION(jpi,jpj),       INTENT(in   ) ::   ptab   ! subdomain input array
1195      INTEGER ,                           INTENT(in   ) ::   kp     ! record length
1196      REAL(wp), DIMENSION(jpi,jpj,jpnij), INTENT(  out) ::   pio    ! subdomain input array
1197      !!
1198      INTEGER :: itaille, ierror   ! temporary integer
1199      !!---------------------------------------------------------------------
1200      !
1201      itaille = jpi * jpj
1202      CALL mpi_gather( ptab, itaille, mpi_double_precision, pio, itaille     ,   &
1203         &                            mpi_double_precision, kp , mpi_comm_opa, ierror ) 
1204      !
1205   END SUBROUTINE mppgather
1206
1207
1208   SUBROUTINE mppscatter( pio, kp, ptab )
1209      !!----------------------------------------------------------------------
1210      !!                  ***  routine mppscatter  ***
1211      !!
1212      !! ** Purpose :   Transfert between awork array which is distributed
1213      !!      following the vertical level and the local subdomain array.
1214      !!
1215      !!----------------------------------------------------------------------
1216      REAL(wp), DIMENSION(jpi,jpj,jpnij)  ::  pio        ! output array
1217      INTEGER                             ::   kp        ! Tag (not used with MPI
1218      REAL(wp), DIMENSION(jpi,jpj)        ::  ptab       ! subdomain array input
1219      !!
1220      INTEGER :: itaille, ierror   ! temporary integer
1221      !!---------------------------------------------------------------------
1222      !
1223      itaille=jpi*jpj
1224      !
1225      CALL mpi_scatter( pio, itaille, mpi_double_precision, ptab, itaille     ,   &
1226         &                            mpi_double_precision, kp  , mpi_comm_opa, ierror )
1227      !
1228   END SUBROUTINE mppscatter
1229
1230
1231   SUBROUTINE mppmax_a_int( ktab, kdim, kcom )
1232      !!----------------------------------------------------------------------
1233      !!                  ***  routine mppmax_a_int  ***
1234      !!
1235      !! ** Purpose :   Find maximum value in an integer layout array
1236      !!
1237      !!----------------------------------------------------------------------
1238      INTEGER , INTENT(in   )                  ::   kdim   ! size of array
1239      INTEGER , INTENT(inout), DIMENSION(kdim) ::   ktab   ! input array
1240      INTEGER , INTENT(in   ), OPTIONAL        ::   kcom   !
1241      !!
1242      INTEGER :: ierror, localcomm   ! temporary integer
1243      INTEGER, DIMENSION(kdim) ::   iwork
1244      !!----------------------------------------------------------------------
1245      !
1246      localcomm = mpi_comm_opa
1247      IF( PRESENT(kcom) )   localcomm = kcom
1248      !
1249      CALL mpi_allreduce( ktab, iwork, kdim, mpi_integer, mpi_max, localcomm, ierror )
1250      !
1251      ktab(:) = iwork(:)
1252      !
1253   END SUBROUTINE mppmax_a_int
1254
1255
1256   SUBROUTINE mppmax_int( ktab, kcom )
1257      !!----------------------------------------------------------------------
1258      !!                  ***  routine mppmax_int  ***
1259      !!
1260      !! ** Purpose :   Find maximum value in an integer layout array
1261      !!
1262      !!----------------------------------------------------------------------
1263      INTEGER, INTENT(inout)           ::   ktab      ! ???
1264      INTEGER, INTENT(in   ), OPTIONAL ::   kcom      ! ???
1265      !!
1266      INTEGER ::   ierror, iwork, localcomm   ! temporary integer
1267      !!----------------------------------------------------------------------
1268      !
1269      localcomm = mpi_comm_opa 
1270      IF( PRESENT(kcom) )   localcomm = kcom
1271      !
1272      CALL mpi_allreduce( ktab, iwork, 1, mpi_integer, mpi_max, localcomm, ierror)
1273      !
1274      ktab = iwork
1275      !
1276   END SUBROUTINE mppmax_int
1277
1278
1279   SUBROUTINE mppmin_a_int( ktab, kdim, kcom )
1280      !!----------------------------------------------------------------------
1281      !!                  ***  routine mppmin_a_int  ***
1282      !!
1283      !! ** Purpose :   Find minimum value in an integer layout array
1284      !!
1285      !!----------------------------------------------------------------------
1286      INTEGER , INTENT( in  )                  ::   kdim        ! size of array
1287      INTEGER , INTENT(inout), DIMENSION(kdim) ::   ktab        ! input array
1288      INTEGER , INTENT( in  ), OPTIONAL        ::   kcom        ! input array
1289      !!
1290      INTEGER ::   ierror, localcomm   ! temporary integer
1291      INTEGER, DIMENSION(kdim) ::   iwork
1292      !!----------------------------------------------------------------------
1293      !
1294      localcomm = mpi_comm_opa
1295      IF( PRESENT(kcom) )   localcomm = kcom
1296      !
1297      CALL mpi_allreduce( ktab, iwork, kdim, mpi_integer, mpi_min, localcomm, ierror )
1298      !
1299      ktab(:) = iwork(:)
1300      !
1301   END SUBROUTINE mppmin_a_int
1302
1303
1304   SUBROUTINE mppmin_int( ktab, kcom )
1305      !!----------------------------------------------------------------------
1306      !!                  ***  routine mppmin_int  ***
1307      !!
1308      !! ** Purpose :   Find minimum value in an integer layout array
1309      !!
1310      !!----------------------------------------------------------------------
1311      INTEGER, INTENT(inout) ::   ktab      ! ???
1312      INTEGER , INTENT( in  ), OPTIONAL        ::   kcom        ! input array
1313      !!
1314      INTEGER ::  ierror, iwork, localcomm
1315      !!----------------------------------------------------------------------
1316      !
1317      localcomm = mpi_comm_opa
1318      IF( PRESENT(kcom) )   localcomm = kcom
1319      !
1320     CALL mpi_allreduce( ktab, iwork, 1, mpi_integer, mpi_min, localcomm, ierror )
1321      !
1322      ktab = iwork
1323      !
1324   END SUBROUTINE mppmin_int
1325
1326
1327   SUBROUTINE mppsum_a_int( ktab, kdim )
1328      !!----------------------------------------------------------------------
1329      !!                  ***  routine mppsum_a_int  ***
1330      !!                   
1331      !! ** Purpose :   Global integer sum, 1D array case
1332      !!
1333      !!----------------------------------------------------------------------
1334      INTEGER, INTENT(in   )                   ::   kdim      ! ???
1335      INTEGER, INTENT(inout), DIMENSION (kdim) ::   ktab      ! ???
1336      !!
1337      INTEGER :: ierror
1338      INTEGER, DIMENSION (kdim) ::  iwork
1339      !!----------------------------------------------------------------------
1340      !
1341      CALL mpi_allreduce( ktab, iwork, kdim, mpi_integer, mpi_sum, mpi_comm_opa, ierror )
1342      !
1343      ktab(:) = iwork(:)
1344      !
1345   END SUBROUTINE mppsum_a_int
1346
1347
1348   SUBROUTINE mppsum_int( ktab )
1349      !!----------------------------------------------------------------------
1350      !!                 ***  routine mppsum_int  ***
1351      !!                 
1352      !! ** Purpose :   Global integer sum
1353      !!
1354      !!----------------------------------------------------------------------
1355      INTEGER, INTENT(inout) ::   ktab
1356      !!
1357      INTEGER :: ierror, iwork
1358      !!----------------------------------------------------------------------
1359      !
1360      CALL mpi_allreduce( ktab, iwork, 1, mpi_integer, mpi_sum, mpi_comm_opa, ierror )
1361      !
1362      ktab = iwork
1363      !
1364   END SUBROUTINE mppsum_int
1365
1366
1367   SUBROUTINE mppmax_a_real( ptab, kdim, kcom )
1368      !!----------------------------------------------------------------------
1369      !!                 ***  routine mppmax_a_real  ***
1370      !!                 
1371      !! ** Purpose :   Maximum
1372      !!
1373      !!----------------------------------------------------------------------
1374      INTEGER , INTENT(in   )                  ::   kdim
1375      REAL(wp), INTENT(inout), DIMENSION(kdim) ::   ptab
1376      INTEGER , INTENT(in   ), OPTIONAL        ::   kcom
1377      !!
1378      INTEGER :: ierror, localcomm
1379      REAL(wp), DIMENSION(kdim) ::  zwork
1380      !!----------------------------------------------------------------------
1381      !
1382      localcomm = mpi_comm_opa
1383      IF( PRESENT(kcom) ) localcomm = kcom
1384      !
1385      CALL mpi_allreduce( ptab, zwork, kdim, mpi_double_precision, mpi_max, localcomm, ierror )
1386      ptab(:) = zwork(:)
1387      !
1388   END SUBROUTINE mppmax_a_real
1389
1390
1391   SUBROUTINE mppmax_real( ptab, kcom )
1392      !!----------------------------------------------------------------------
1393      !!                  ***  routine mppmax_real  ***
1394      !!                   
1395      !! ** Purpose :   Maximum
1396      !!
1397      !!----------------------------------------------------------------------
1398      REAL(wp), INTENT(inout)           ::   ptab   ! ???
1399      INTEGER , INTENT(in   ), OPTIONAL ::   kcom   ! ???
1400      !!
1401      INTEGER  ::   ierror, localcomm
1402      REAL(wp) ::   zwork
1403      !!----------------------------------------------------------------------
1404      !
1405      localcomm = mpi_comm_opa 
1406      IF( PRESENT(kcom) )   localcomm = kcom
1407      !
1408      CALL mpi_allreduce( ptab, zwork, 1, mpi_double_precision, mpi_max, localcomm, ierror )
1409      ptab = zwork
1410      !
1411   END SUBROUTINE mppmax_real
1412
1413
1414   SUBROUTINE mppmin_a_real( ptab, kdim, kcom )
1415      !!----------------------------------------------------------------------
1416      !!                 ***  routine mppmin_a_real  ***
1417      !!                 
1418      !! ** Purpose :   Minimum of REAL, array case
1419      !!
1420      !!-----------------------------------------------------------------------
1421      INTEGER , INTENT(in   )                  ::   kdim
1422      REAL(wp), INTENT(inout), DIMENSION(kdim) ::   ptab
1423      INTEGER , INTENT(in   ), OPTIONAL        ::   kcom
1424      !!
1425      INTEGER :: ierror, localcomm
1426      REAL(wp), DIMENSION(kdim) ::   zwork
1427      !!-----------------------------------------------------------------------
1428      !
1429      localcomm = mpi_comm_opa 
1430      IF( PRESENT(kcom) ) localcomm = kcom
1431      !
1432      CALL mpi_allreduce( ptab, zwork, kdim, mpi_double_precision, mpi_min, localcomm, ierror )
1433      ptab(:) = zwork(:)
1434      !
1435   END SUBROUTINE mppmin_a_real
1436
1437
1438   SUBROUTINE mppmin_real( ptab, kcom )
1439      !!----------------------------------------------------------------------
1440      !!                  ***  routine mppmin_real  ***
1441      !!
1442      !! ** Purpose :   minimum of REAL, scalar case
1443      !!
1444      !!-----------------------------------------------------------------------
1445      REAL(wp), INTENT(inout)           ::   ptab        !
1446      INTEGER , INTENT(in   ), OPTIONAL :: kcom
1447      !!
1448      INTEGER  ::   ierror
1449      REAL(wp) ::   zwork
1450      INTEGER :: localcomm
1451      !!-----------------------------------------------------------------------
1452      !
1453      localcomm = mpi_comm_opa 
1454      IF( PRESENT(kcom) )   localcomm = kcom
1455      !
1456      CALL mpi_allreduce( ptab, zwork, 1, mpi_double_precision, mpi_min, localcomm, ierror )
1457      ptab = zwork
1458      !
1459   END SUBROUTINE mppmin_real
1460
1461
1462   SUBROUTINE mppsum_a_real( ptab, kdim, kcom )
1463      !!----------------------------------------------------------------------
1464      !!                  ***  routine mppsum_a_real  ***
1465      !!
1466      !! ** Purpose :   global sum, REAL ARRAY argument case
1467      !!
1468      !!-----------------------------------------------------------------------
1469      INTEGER , INTENT( in )                     ::   kdim      ! size of ptab
1470      REAL(wp), DIMENSION(kdim), INTENT( inout ) ::   ptab      ! input array
1471      INTEGER , INTENT( in ), OPTIONAL           :: kcom
1472      !!
1473      INTEGER                   ::   ierror    ! temporary integer
1474      INTEGER                   ::   localcomm 
1475      REAL(wp), DIMENSION(kdim) ::   zwork     ! temporary workspace
1476      !!-----------------------------------------------------------------------
1477      !
1478      localcomm = mpi_comm_opa 
1479      IF( PRESENT(kcom) )   localcomm = kcom
1480      !
1481      CALL mpi_allreduce( ptab, zwork, kdim, mpi_double_precision, mpi_sum, localcomm, ierror )
1482      ptab(:) = zwork(:)
1483      !
1484   END SUBROUTINE mppsum_a_real
1485
1486
1487   SUBROUTINE mppsum_real( ptab, kcom )
1488      !!----------------------------------------------------------------------
1489      !!                  ***  routine mppsum_real  ***
1490      !!             
1491      !! ** Purpose :   global sum, SCALAR argument case
1492      !!
1493      !!-----------------------------------------------------------------------
1494      REAL(wp), INTENT(inout)           ::   ptab   ! input scalar
1495      INTEGER , INTENT(in   ), OPTIONAL ::   kcom
1496      !!
1497      INTEGER  ::   ierror, localcomm 
1498      REAL(wp) ::   zwork
1499      !!-----------------------------------------------------------------------
1500      !
1501      localcomm = mpi_comm_opa 
1502      IF( PRESENT(kcom) ) localcomm = kcom
1503      !
1504      CALL mpi_allreduce( ptab, zwork, 1, mpi_double_precision, mpi_sum, localcomm, ierror )
1505      ptab = zwork
1506      !
1507   END SUBROUTINE mppsum_real
1508
1509# if defined key_mpp_rep
1510   SUBROUTINE mppsum_realdd( ytab, kcom )
1511      !!----------------------------------------------------------------------
1512      !!                  ***  routine mppsum_realdd ***
1513      !!
1514      !! ** Purpose :   global sum in Massively Parallel Processing
1515      !!                SCALAR argument case for double-double precision
1516      !!
1517      !!-----------------------------------------------------------------------
1518      COMPLEX(wp), INTENT(inout)         :: ytab    ! input scalar
1519      INTEGER , INTENT( in  ), OPTIONAL :: kcom
1520
1521      !! * Local variables   (MPI version)
1522      INTEGER  ::    ierror
1523      INTEGER  ::   localcomm
1524      COMPLEX(wp) :: zwork
1525
1526      localcomm = mpi_comm_opa
1527      IF( PRESENT(kcom) ) localcomm = kcom
1528
1529      ! reduce local sums into global sum
1530      CALL MPI_ALLREDUCE (ytab, zwork, 1, MPI_DOUBLE_COMPLEX, &
1531                       MPI_SUMDD,localcomm,ierror)
1532      ytab = zwork
1533
1534   END SUBROUTINE mppsum_realdd
1535 
1536 
1537   SUBROUTINE mppsum_a_realdd( ytab, kdim, kcom )
1538      !!----------------------------------------------------------------------
1539      !!                  ***  routine mppsum_a_realdd  ***
1540      !!
1541      !! ** Purpose :   global sum in Massively Parallel Processing
1542      !!                COMPLEX ARRAY case for double-double precision
1543      !!
1544      !!-----------------------------------------------------------------------
1545      INTEGER , INTENT( in )                        ::   kdim      ! size of ytab
1546      COMPLEX(wp), DIMENSION(kdim), INTENT( inout ) ::   ytab      ! input array
1547      INTEGER , INTENT( in  ), OPTIONAL :: kcom
1548
1549      !! * Local variables   (MPI version)
1550      INTEGER                      :: ierror    ! temporary integer
1551      INTEGER                      ::   localcomm
1552      COMPLEX(wp), DIMENSION(kdim) :: zwork     ! temporary workspace
1553
1554      localcomm = mpi_comm_opa
1555      IF( PRESENT(kcom) ) localcomm = kcom
1556
1557      CALL MPI_ALLREDUCE (ytab, zwork, kdim, MPI_DOUBLE_COMPLEX, &
1558                       MPI_SUMDD,localcomm,ierror)
1559      ytab(:) = zwork(:)
1560
1561   END SUBROUTINE mppsum_a_realdd
1562# endif   
1563   
1564   SUBROUTINE mpp_minloc2d( ptab, pmask, pmin, ki,kj )
1565      !!------------------------------------------------------------------------
1566      !!             ***  routine mpp_minloc  ***
1567      !!
1568      !! ** Purpose :   Compute the global minimum of an array ptab
1569      !!              and also give its global position
1570      !!
1571      !! ** Method  :   Use MPI_ALLREDUCE with MPI_MINLOC
1572      !!
1573      !!--------------------------------------------------------------------------
1574      REAL(wp), DIMENSION (jpi,jpj), INTENT(in   ) ::   ptab    ! Local 2D array
1575      REAL(wp), DIMENSION (jpi,jpj), INTENT(in   ) ::   pmask   ! Local mask
1576      REAL(wp)                     , INTENT(  out) ::   pmin    ! Global minimum of ptab
1577      INTEGER                      , INTENT(  out) ::   ki, kj   ! index of minimum in global frame
1578      !!
1579      INTEGER , DIMENSION(2)   ::   ilocs
1580      INTEGER :: ierror
1581      REAL(wp) ::   zmin   ! local minimum
1582      REAL(wp), DIMENSION(2,1) ::   zain, zaout
1583      !!-----------------------------------------------------------------------
1584      !
1585      zmin  = MINVAL( ptab(:,:) , mask= pmask == 1.e0 )
1586      ilocs = MINLOC( ptab(:,:) , mask= pmask == 1.e0 )
1587      !
1588      ki = ilocs(1) + nimpp - 1
1589      kj = ilocs(2) + njmpp - 1
1590      !
1591      zain(1,:)=zmin
1592      zain(2,:)=ki+10000.*kj
1593      !
1594      CALL MPI_ALLREDUCE( zain,zaout, 1, MPI_2DOUBLE_PRECISION,MPI_MINLOC,MPI_COMM_OPA,ierror)
1595      !
1596      pmin = zaout(1,1)
1597      kj = INT(zaout(2,1)/10000.)
1598      ki = INT(zaout(2,1) - 10000.*kj )
1599      !
1600   END SUBROUTINE mpp_minloc2d
1601
1602
1603   SUBROUTINE mpp_minloc3d( ptab, pmask, pmin, ki, kj ,kk)
1604      !!------------------------------------------------------------------------
1605      !!             ***  routine mpp_minloc  ***
1606      !!
1607      !! ** Purpose :   Compute the global minimum of an array ptab
1608      !!              and also give its global position
1609      !!
1610      !! ** Method  :   Use MPI_ALLREDUCE with MPI_MINLOC
1611      !!
1612      !!--------------------------------------------------------------------------
1613      REAL(wp), DIMENSION (jpi,jpj,jpk), INTENT(in   ) ::   ptab         ! Local 2D array
1614      REAL(wp), DIMENSION (jpi,jpj,jpk), INTENT(in   ) ::   pmask        ! Local mask
1615      REAL(wp)                         , INTENT(  out) ::   pmin         ! Global minimum of ptab
1616      INTEGER                          , INTENT(  out) ::   ki, kj, kk   ! index of minimum in global frame
1617      !!
1618      INTEGER  ::   ierror
1619      REAL(wp) ::   zmin     ! local minimum
1620      INTEGER , DIMENSION(3)   ::   ilocs
1621      REAL(wp), DIMENSION(2,1) ::   zain, zaout
1622      !!-----------------------------------------------------------------------
1623      !
1624      zmin  = MINVAL( ptab(:,:,:) , mask= pmask == 1.e0 )
1625      ilocs = MINLOC( ptab(:,:,:) , mask= pmask == 1.e0 )
1626      !
1627      ki = ilocs(1) + nimpp - 1
1628      kj = ilocs(2) + njmpp - 1
1629      kk = ilocs(3)
1630      !
1631      zain(1,:)=zmin
1632      zain(2,:)=ki+10000.*kj+100000000.*kk
1633      !
1634      CALL MPI_ALLREDUCE( zain,zaout, 1, MPI_2DOUBLE_PRECISION,MPI_MINLOC,MPI_COMM_OPA,ierror)
1635      !
1636      pmin = zaout(1,1)
1637      kk   = INT( zaout(2,1) / 100000000. )
1638      kj   = INT( zaout(2,1) - kk * 100000000. ) / 10000
1639      ki   = INT( zaout(2,1) - kk * 100000000. -kj * 10000. )
1640      !
1641   END SUBROUTINE mpp_minloc3d
1642
1643
1644   SUBROUTINE mpp_maxloc2d( ptab, pmask, pmax, ki, kj )
1645      !!------------------------------------------------------------------------
1646      !!             ***  routine mpp_maxloc  ***
1647      !!
1648      !! ** Purpose :   Compute the global maximum of an array ptab
1649      !!              and also give its global position
1650      !!
1651      !! ** Method  :   Use MPI_ALLREDUCE with MPI_MINLOC
1652      !!
1653      !!--------------------------------------------------------------------------
1654      REAL(wp), DIMENSION (jpi,jpj), INTENT(in   ) ::   ptab     ! Local 2D array
1655      REAL(wp), DIMENSION (jpi,jpj), INTENT(in   ) ::   pmask    ! Local mask
1656      REAL(wp)                     , INTENT(  out) ::   pmax     ! Global maximum of ptab
1657      INTEGER                      , INTENT(  out) ::   ki, kj   ! index of maximum in global frame
1658      !! 
1659      INTEGER  :: ierror
1660      INTEGER, DIMENSION (2)   ::   ilocs
1661      REAL(wp) :: zmax   ! local maximum
1662      REAL(wp), DIMENSION(2,1) ::   zain, zaout
1663      !!-----------------------------------------------------------------------
1664      !
1665      zmax  = MAXVAL( ptab(:,:) , mask= pmask == 1.e0 )
1666      ilocs = MAXLOC( ptab(:,:) , mask= pmask == 1.e0 )
1667      !
1668      ki = ilocs(1) + nimpp - 1
1669      kj = ilocs(2) + njmpp - 1
1670      !
1671      zain(1,:) = zmax
1672      zain(2,:) = ki + 10000. * kj
1673      !
1674      CALL MPI_ALLREDUCE( zain,zaout, 1, MPI_2DOUBLE_PRECISION,MPI_MAXLOC,MPI_COMM_OPA,ierror)
1675      !
1676      pmax = zaout(1,1)
1677      kj   = INT( zaout(2,1) / 10000.     )
1678      ki   = INT( zaout(2,1) - 10000.* kj )
1679      !
1680   END SUBROUTINE mpp_maxloc2d
1681
1682
1683   SUBROUTINE mpp_maxloc3d( ptab, pmask, pmax, ki, kj, kk )
1684      !!------------------------------------------------------------------------
1685      !!             ***  routine mpp_maxloc  ***
1686      !!
1687      !! ** Purpose :  Compute the global maximum of an array ptab
1688      !!              and also give its global position
1689      !!
1690      !! ** Method : Use MPI_ALLREDUCE with MPI_MINLOC
1691      !!
1692      !!--------------------------------------------------------------------------
1693      REAL(wp), DIMENSION (jpi,jpj,jpk), INTENT(in   ) ::   ptab         ! Local 2D array
1694      REAL(wp), DIMENSION (jpi,jpj,jpk), INTENT(in   ) ::   pmask        ! Local mask
1695      REAL(wp)                         , INTENT(  out) ::   pmax         ! Global maximum of ptab
1696      INTEGER                          , INTENT(  out) ::   ki, kj, kk   ! index of maximum in global frame
1697      !!   
1698      REAL(wp) :: zmax   ! local maximum
1699      REAL(wp), DIMENSION(2,1) ::   zain, zaout
1700      INTEGER , DIMENSION(3)   ::   ilocs
1701      INTEGER :: ierror
1702      !!-----------------------------------------------------------------------
1703      !
1704      zmax  = MAXVAL( ptab(:,:,:) , mask= pmask == 1.e0 )
1705      ilocs = MAXLOC( ptab(:,:,:) , mask= pmask == 1.e0 )
1706      !
1707      ki = ilocs(1) + nimpp - 1
1708      kj = ilocs(2) + njmpp - 1
1709      kk = ilocs(3)
1710      !
1711      zain(1,:)=zmax
1712      zain(2,:)=ki+10000.*kj+100000000.*kk
1713      !
1714      CALL MPI_ALLREDUCE( zain,zaout, 1, MPI_2DOUBLE_PRECISION,MPI_MAXLOC,MPI_COMM_OPA,ierror)
1715      !
1716      pmax = zaout(1,1)
1717      kk   = INT( zaout(2,1) / 100000000. )
1718      kj   = INT( zaout(2,1) - kk * 100000000. ) / 10000
1719      ki   = INT( zaout(2,1) - kk * 100000000. -kj * 10000. )
1720      !
1721   END SUBROUTINE mpp_maxloc3d
1722
1723
1724   SUBROUTINE mppsync()
1725      !!----------------------------------------------------------------------
1726      !!                  ***  routine mppsync  ***
1727      !!                   
1728      !! ** Purpose :   Massively parallel processors, synchroneous
1729      !!
1730      !!-----------------------------------------------------------------------
1731      INTEGER :: ierror
1732      !!-----------------------------------------------------------------------
1733      !
1734      CALL mpi_barrier( mpi_comm_opa, ierror )
1735      !
1736   END SUBROUTINE mppsync
1737
1738
1739   SUBROUTINE mppstop
1740      !!----------------------------------------------------------------------
1741      !!                  ***  routine mppstop  ***
1742      !!                   
1743      !! ** purpose :   Stop massively parallel processors method
1744      !!
1745      !!----------------------------------------------------------------------
1746      INTEGER ::   info
1747      !!----------------------------------------------------------------------
1748      !
1749      CALL mppsync
1750      CALL mpi_finalize( info )
1751      !
1752   END SUBROUTINE mppstop
1753
1754
1755   SUBROUTINE mppobc( ptab, kd1, kd2, kl, kk, ktype, kij , kumout)
1756      !!----------------------------------------------------------------------
1757      !!                  ***  routine mppobc  ***
1758      !!
1759      !! ** Purpose :   Message passing manadgement for open boundary
1760      !!     conditions array
1761      !!
1762      !! ** Method  :   Use mppsend and mpprecv function for passing mask
1763      !!       between processors following neighboring subdomains.
1764      !!       domain parameters
1765      !!                    nlci   : first dimension of the local subdomain
1766      !!                    nlcj   : second dimension of the local subdomain
1767      !!                    nbondi : mark for "east-west local boundary"
1768      !!                    nbondj : mark for "north-south local boundary"
1769      !!                    noea   : number for local neighboring processors
1770      !!                    nowe   : number for local neighboring processors
1771      !!                    noso   : number for local neighboring processors
1772      !!                    nono   : number for local neighboring processors
1773      !!
1774      !!----------------------------------------------------------------------
1775      USE wrk_nemo        ! Memory allocation
1776      !
1777      INTEGER , INTENT(in   )                     ::   kd1, kd2   ! starting and ending indices
1778      INTEGER , INTENT(in   )                     ::   kl         ! index of open boundary
1779      INTEGER , INTENT(in   )                     ::   kk         ! vertical dimension
1780      INTEGER , INTENT(in   )                     ::   ktype      ! define north/south or east/west cdt
1781      !                                                           !  = 1  north/south  ;  = 2  east/west
1782      INTEGER , INTENT(in   )                     ::   kij        ! horizontal dimension
1783      INTEGER , INTENT(in   )                     ::   kumout     ! ocean.output logical unit
1784      REAL(wp), INTENT(inout), DIMENSION(kij,kk)  ::   ptab       ! variable array
1785      !
1786      INTEGER ::   ji, jj, jk, jl        ! dummy loop indices
1787      INTEGER ::   iipt0, iipt1, ilpt1   ! local integers
1788      INTEGER ::   ijpt0, ijpt1          !   -       -
1789      INTEGER ::   imigr, iihom, ijhom   !   -       -
1790      INTEGER ::   ml_req1, ml_req2, ml_err    ! for key_mpi_isend
1791      INTEGER ::   ml_stat(MPI_STATUS_SIZE)    ! for key_mpi_isend
1792      REAL(wp), POINTER, DIMENSION(:,:) ::   ztab   ! temporary workspace
1793      !!----------------------------------------------------------------------
1794
1795      CALL wrk_alloc( jpi,jpj, ztab )
1796
1797      ! boundary condition initialization
1798      ! ---------------------------------
1799      ztab(:,:) = 0.e0
1800      !
1801      IF( ktype==1 ) THEN                                  ! north/south boundaries
1802         iipt0 = MAX( 1, MIN(kd1 - nimpp+1, nlci     ) )
1803         iipt1 = MAX( 0, MIN(kd2 - nimpp+1, nlci - 1 ) )
1804         ilpt1 = MAX( 1, MIN(kd2 - nimpp+1, nlci     ) )
1805         ijpt0 = MAX( 1, MIN(kl  - njmpp+1, nlcj     ) )
1806         ijpt1 = MAX( 0, MIN(kl  - njmpp+1, nlcj - 1 ) )
1807      ELSEIF( ktype==2 ) THEN                              ! east/west boundaries
1808         iipt0 = MAX( 1, MIN(kl  - nimpp+1, nlci     ) )
1809         iipt1 = MAX( 0, MIN(kl  - nimpp+1, nlci - 1 ) )
1810         ijpt0 = MAX( 1, MIN(kd1 - njmpp+1, nlcj     ) )
1811         ijpt1 = MAX( 0, MIN(kd2 - njmpp+1, nlcj - 1 ) )
1812         ilpt1 = MAX( 1, MIN(kd2 - njmpp+1, nlcj     ) )
1813      ELSE
1814         WRITE(kumout, cform_err)
1815         WRITE(kumout,*) 'mppobc : bad ktype'
1816         CALL mppstop
1817      ENDIF
1818     
1819      ! Communication level by level
1820      ! ----------------------------
1821!!gm Remark : this is very time consumming!!!
1822      !                                         ! ------------------------ !
1823      DO jk = 1, kk                             !   Loop over the levels   !
1824         !                                      ! ------------------------ !
1825         !
1826         IF( ktype == 1 ) THEN                               ! north/south boundaries
1827            DO jj = ijpt0, ijpt1
1828               DO ji = iipt0, iipt1
1829                  ztab(ji,jj) = ptab(ji,jk)
1830               END DO
1831            END DO
1832         ELSEIF( ktype == 2 ) THEN                           ! east/west boundaries
1833            DO jj = ijpt0, ijpt1
1834               DO ji = iipt0, iipt1
1835                  ztab(ji,jj) = ptab(jj,jk)
1836               END DO
1837            END DO
1838         ENDIF
1839
1840
1841         ! 1. East and west directions
1842         ! ---------------------------
1843         !
1844         IF( nbondi /= 2 ) THEN         ! Read Dirichlet lateral conditions
1845            iihom = nlci-nreci
1846            DO jl = 1, jpreci
1847               t2ew(:,jl,1) = ztab(jpreci+jl,:)
1848               t2we(:,jl,1) = ztab(iihom +jl,:)
1849            END DO
1850         ENDIF
1851         !
1852         !                              ! Migrations
1853         imigr=jpreci*jpj
1854         !
1855         IF( nbondi == -1 ) THEN
1856            CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req1 )
1857            CALL mpprecv( 1, t2ew(1,1,2), imigr, noea )
1858            IF(l_isend)   CALL mpi_wait( ml_req1, ml_stat, ml_err )
1859         ELSEIF( nbondi == 0 ) THEN
1860            CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 )
1861            CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req2 )
1862            CALL mpprecv( 1, t2ew(1,1,2), imigr, noea )
1863            CALL mpprecv( 2, t2we(1,1,2), imigr, nowe )
1864            IF(l_isend)   CALL mpi_wait( ml_req1, ml_stat, ml_err )
1865            IF(l_isend)   CALL mpi_wait( ml_req2, ml_stat, ml_err )
1866         ELSEIF( nbondi == 1 ) THEN
1867            CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 )
1868            CALL mpprecv( 2, t2we(1,1,2), imigr, nowe )
1869            IF(l_isend) CALL mpi_wait( ml_req1, ml_stat, ml_err )
1870         ENDIF
1871         !
1872         !                              ! Write Dirichlet lateral conditions
1873         iihom = nlci-jpreci
1874         !
1875         IF( nbondi == 0 .OR. nbondi == 1 ) THEN
1876            DO jl = 1, jpreci
1877               ztab(jl,:) = t2we(:,jl,2)
1878            END DO
1879         ENDIF
1880         IF( nbondi == -1 .OR. nbondi == 0 ) THEN
1881            DO jl = 1, jpreci
1882               ztab(iihom+jl,:) = t2ew(:,jl,2)
1883            END DO
1884         ENDIF
1885
1886
1887         ! 2. North and south directions
1888         ! -----------------------------
1889         !
1890         IF( nbondj /= 2 ) THEN         ! Read Dirichlet lateral conditions
1891            ijhom = nlcj-nrecj
1892            DO jl = 1, jprecj
1893               t2sn(:,jl,1) = ztab(:,ijhom +jl)
1894               t2ns(:,jl,1) = ztab(:,jprecj+jl)
1895            END DO
1896         ENDIF
1897         !
1898         !                              ! Migrations
1899         imigr = jprecj * jpi
1900         !
1901         IF( nbondj == -1 ) THEN
1902            CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req1 )
1903            CALL mpprecv( 3, t2ns(1,1,2), imigr, nono )
1904            IF(l_isend) CALL mpi_wait( ml_req1, ml_stat, ml_err )
1905         ELSEIF( nbondj == 0 ) THEN
1906            CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 )
1907            CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req2 )
1908            CALL mpprecv( 3, t2ns(1,1,2), imigr, nono )
1909            CALL mpprecv( 4, t2sn(1,1,2), imigr, noso )
1910            IF( l_isend )   CALL mpi_wait( ml_req1, ml_stat, ml_err )
1911            IF( l_isend )   CALL mpi_wait( ml_req2, ml_stat, ml_err )
1912         ELSEIF( nbondj == 1 ) THEN
1913            CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 )
1914            CALL mpprecv( 4, t2sn(1,1,2), imigr, noso)
1915            IF( l_isend )   CALL mpi_wait( ml_req1, ml_stat, ml_err )
1916         ENDIF
1917         !
1918         !                              ! Write Dirichlet lateral conditions
1919         ijhom = nlcj - jprecj
1920         IF( nbondj == 0 .OR. nbondj == 1 ) THEN
1921            DO jl = 1, jprecj
1922               ztab(:,jl) = t2sn(:,jl,2)
1923            END DO
1924         ENDIF
1925         IF( nbondj == 0 .OR. nbondj == -1 ) THEN
1926            DO jl = 1, jprecj
1927               ztab(:,ijhom+jl) = t2ns(:,jl,2)
1928            END DO
1929         ENDIF
1930         IF( ktype==1 .AND. kd1 <= jpi+nimpp-1 .AND. nimpp <= kd2 ) THEN
1931            DO jj = ijpt0, ijpt1            ! north/south boundaries
1932               DO ji = iipt0,ilpt1
1933                  ptab(ji,jk) = ztab(ji,jj) 
1934               END DO
1935            END DO
1936         ELSEIF( ktype==2 .AND. kd1 <= jpj+njmpp-1 .AND. njmpp <= kd2 ) THEN
1937            DO jj = ijpt0, ilpt1            ! east/west boundaries
1938               DO ji = iipt0,iipt1
1939                  ptab(jj,jk) = ztab(ji,jj) 
1940               END DO
1941            END DO
1942         ENDIF
1943         !
1944      END DO
1945      !
1946      CALL wrk_dealloc( jpi,jpj, ztab )
1947      !
1948   END SUBROUTINE mppobc
1949   
1950
1951   SUBROUTINE mpp_comm_free( kcom )
1952      !!----------------------------------------------------------------------
1953      !!----------------------------------------------------------------------
1954      INTEGER, INTENT(in) ::   kcom
1955      !!
1956      INTEGER :: ierr
1957      !!----------------------------------------------------------------------
1958      !
1959      CALL MPI_COMM_FREE(kcom, ierr)
1960      !
1961   END SUBROUTINE mpp_comm_free
1962
1963
1964   SUBROUTINE mpp_ini_ice( pindic, kumout )
1965      !!----------------------------------------------------------------------
1966      !!               ***  routine mpp_ini_ice  ***
1967      !!
1968      !! ** Purpose :   Initialize special communicator for ice areas
1969      !!      condition together with global variables needed in the ddmpp folding
1970      !!
1971      !! ** Method  : - Look for ice processors in ice routines
1972      !!              - Put their number in nrank_ice
1973      !!              - Create groups for the world processors and the ice processors
1974      !!              - Create a communicator for ice processors
1975      !!
1976      !! ** output
1977      !!      njmppmax = njmpp for northern procs
1978      !!      ndim_rank_ice = number of processors with ice
1979      !!      nrank_ice (ndim_rank_ice) = ice processors
1980      !!      ngrp_iworld = group ID for the world processors
1981      !!      ngrp_ice = group ID for the ice processors
1982      !!      ncomm_ice = communicator for the ice procs.
1983      !!      n_ice_root = number (in the world) of proc 0 in the ice comm.
1984      !!
1985      !!----------------------------------------------------------------------
1986      INTEGER, INTENT(in) ::   pindic
1987      INTEGER, INTENT(in) ::   kumout   ! ocean.output logical unit
1988      !!
1989      INTEGER :: jjproc
1990      INTEGER :: ii, ierr
1991      INTEGER, ALLOCATABLE, DIMENSION(:) ::   kice
1992      INTEGER, ALLOCATABLE, DIMENSION(:) ::   zwork
1993      !!----------------------------------------------------------------------
1994      !
1995      ! Since this is just an init routine and these arrays are of length jpnij
1996      ! then don't use wrk_nemo module - just allocate and deallocate.
1997      ALLOCATE( kice(jpnij), zwork(jpnij), STAT=ierr )
1998      IF( ierr /= 0 ) THEN
1999         WRITE(kumout, cform_err)
2000         WRITE(kumout,*) 'mpp_ini_ice : failed to allocate 2, 1D arrays (jpnij in length)'
2001         CALL mppstop
2002      ENDIF
2003
2004      ! Look for how many procs with sea-ice
2005      !
2006      kice = 0
2007      DO jjproc = 1, jpnij
2008         IF( jjproc == narea .AND. pindic .GT. 0 )   kice(jjproc) = 1   
2009      END DO
2010      !
2011      zwork = 0
2012      CALL MPI_ALLREDUCE( kice, zwork, jpnij, mpi_integer, mpi_sum, mpi_comm_opa, ierr )
2013      ndim_rank_ice = SUM( zwork )         
2014
2015      ! Allocate the right size to nrank_north
2016      IF( ALLOCATED ( nrank_ice ) )   DEALLOCATE( nrank_ice )
2017      ALLOCATE( nrank_ice(ndim_rank_ice) )
2018      !
2019      ii = 0     
2020      nrank_ice = 0
2021      DO jjproc = 1, jpnij
2022         IF( zwork(jjproc) == 1) THEN
2023            ii = ii + 1
2024            nrank_ice(ii) = jjproc -1 
2025         ENDIF
2026      END DO
2027
2028      ! Create the world group
2029      CALL MPI_COMM_GROUP( mpi_comm_opa, ngrp_iworld, ierr )
2030
2031      ! Create the ice group from the world group
2032      CALL MPI_GROUP_INCL( ngrp_iworld, ndim_rank_ice, nrank_ice, ngrp_ice, ierr )
2033
2034      ! Create the ice communicator , ie the pool of procs with sea-ice
2035      CALL MPI_COMM_CREATE( mpi_comm_opa, ngrp_ice, ncomm_ice, ierr )
2036
2037      ! Find proc number in the world of proc 0 in the north
2038      ! The following line seems to be useless, we just comment & keep it as reminder
2039      ! CALL MPI_GROUP_TRANSLATE_RANKS(ngrp_ice,1,0,ngrp_iworld,n_ice_root,ierr)
2040      !
2041      CALL MPI_GROUP_FREE(ngrp_ice, ierr)
2042      CALL MPI_GROUP_FREE(ngrp_iworld, ierr)
2043
2044      DEALLOCATE(kice, zwork)
2045      !
2046   END SUBROUTINE mpp_ini_ice
2047
2048
2049   SUBROUTINE mpp_ini_znl( kumout )
2050      !!----------------------------------------------------------------------
2051      !!               ***  routine mpp_ini_znl  ***
2052      !!
2053      !! ** Purpose :   Initialize special communicator for computing zonal sum
2054      !!
2055      !! ** Method  : - Look for processors in the same row
2056      !!              - Put their number in nrank_znl
2057      !!              - Create group for the znl processors
2058      !!              - Create a communicator for znl processors
2059      !!              - Determine if processor should write znl files
2060      !!
2061      !! ** output
2062      !!      ndim_rank_znl = number of processors on the same row
2063      !!      ngrp_znl = group ID for the znl processors
2064      !!      ncomm_znl = communicator for the ice procs.
2065      !!      n_znl_root = number (in the world) of proc 0 in the ice comm.
2066      !!
2067      !!----------------------------------------------------------------------
2068      INTEGER, INTENT(in) ::   kumout   ! ocean.output logical units
2069      !
2070      INTEGER :: jproc      ! dummy loop integer
2071      INTEGER :: ierr, ii   ! local integer
2072      INTEGER, ALLOCATABLE, DIMENSION(:) ::   kwork
2073      !!----------------------------------------------------------------------
2074      !-$$     WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - ngrp_world     : ', ngrp_world
2075      !-$$     WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - mpi_comm_world : ', mpi_comm_world
2076      !-$$     WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - mpi_comm_opa   : ', mpi_comm_opa
2077      !
2078      ALLOCATE( kwork(jpnij), STAT=ierr )
2079      IF( ierr /= 0 ) THEN
2080         WRITE(kumout, cform_err)
2081         WRITE(kumout,*) 'mpp_ini_znl : failed to allocate 1D array of length jpnij'
2082         CALL mppstop
2083      ENDIF
2084
2085      IF( jpnj == 1 ) THEN
2086         ngrp_znl  = ngrp_world
2087         ncomm_znl = mpi_comm_opa
2088      ELSE
2089         !
2090         CALL MPI_ALLGATHER ( njmpp, 1, mpi_integer, kwork, 1, mpi_integer, mpi_comm_opa, ierr )
2091         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - kwork pour njmpp : ', kwork
2092         !-$$        CALL flush(numout)
2093         !
2094         ! Count number of processors on the same row
2095         ndim_rank_znl = 0
2096         DO jproc=1,jpnij
2097            IF ( kwork(jproc) == njmpp ) THEN
2098               ndim_rank_znl = ndim_rank_znl + 1
2099            ENDIF
2100         END DO
2101         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - ndim_rank_znl : ', ndim_rank_znl
2102         !-$$        CALL flush(numout)
2103         ! Allocate the right size to nrank_znl
2104         IF (ALLOCATED (nrank_znl)) DEALLOCATE(nrank_znl)
2105         ALLOCATE(nrank_znl(ndim_rank_znl))
2106         ii = 0     
2107         nrank_znl (:) = 0
2108         DO jproc=1,jpnij
2109            IF ( kwork(jproc) == njmpp) THEN
2110               ii = ii + 1
2111               nrank_znl(ii) = jproc -1 
2112            ENDIF
2113         END DO
2114         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - nrank_znl : ', nrank_znl
2115         !-$$        CALL flush(numout)
2116
2117         ! Create the opa group
2118         CALL MPI_COMM_GROUP(mpi_comm_opa,ngrp_opa,ierr)
2119         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - ngrp_opa : ', ngrp_opa
2120         !-$$        CALL flush(numout)
2121
2122         ! Create the znl group from the opa group
2123         CALL MPI_GROUP_INCL  ( ngrp_opa, ndim_rank_znl, nrank_znl, ngrp_znl, ierr )
2124         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - ngrp_znl ', ngrp_znl
2125         !-$$        CALL flush(numout)
2126
2127         ! Create the znl communicator from the opa communicator, ie the pool of procs in the same row
2128         CALL MPI_COMM_CREATE ( mpi_comm_opa, ngrp_znl, ncomm_znl, ierr )
2129         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - ncomm_znl ', ncomm_znl
2130         !-$$        CALL flush(numout)
2131         !
2132      END IF
2133
2134      ! Determines if processor if the first (starting from i=1) on the row
2135      IF ( jpni == 1 ) THEN
2136         l_znl_root = .TRUE.
2137      ELSE
2138         l_znl_root = .FALSE.
2139         kwork (1) = nimpp
2140         CALL mpp_min ( kwork(1), kcom = ncomm_znl)
2141         IF ( nimpp == kwork(1)) l_znl_root = .TRUE.
2142      END IF
2143
2144      DEALLOCATE(kwork)
2145
2146   END SUBROUTINE mpp_ini_znl
2147
2148
2149   SUBROUTINE mpp_ini_north
2150      !!----------------------------------------------------------------------
2151      !!               ***  routine mpp_ini_north  ***
2152      !!
2153      !! ** Purpose :   Initialize special communicator for north folding
2154      !!      condition together with global variables needed in the mpp folding
2155      !!
2156      !! ** Method  : - Look for northern processors
2157      !!              - Put their number in nrank_north
2158      !!              - Create groups for the world processors and the north processors
2159      !!              - Create a communicator for northern processors
2160      !!
2161      !! ** output
2162      !!      njmppmax = njmpp for northern procs
2163      !!      ndim_rank_north = number of processors in the northern line
2164      !!      nrank_north (ndim_rank_north) = number  of the northern procs.
2165      !!      ngrp_world = group ID for the world processors
2166      !!      ngrp_north = group ID for the northern processors
2167      !!      ncomm_north = communicator for the northern procs.
2168      !!      north_root = number (in the world) of proc 0 in the northern comm.
2169      !!
2170      !!----------------------------------------------------------------------
2171      INTEGER ::   ierr
2172      INTEGER ::   jjproc
2173      INTEGER ::   ii, ji
2174      !!----------------------------------------------------------------------
2175      !
2176      njmppmax = MAXVAL( njmppt )
2177      !
2178      ! Look for how many procs on the northern boundary
2179      ndim_rank_north = 0
2180      DO jjproc = 1, jpnij
2181         IF( njmppt(jjproc) == njmppmax )   ndim_rank_north = ndim_rank_north + 1
2182      END DO
2183      !
2184      ! Allocate the right size to nrank_north
2185      IF (ALLOCATED (nrank_north)) DEALLOCATE(nrank_north)
2186      ALLOCATE( nrank_north(ndim_rank_north) )
2187
2188      ! Fill the nrank_north array with proc. number of northern procs.
2189      ! Note : the rank start at 0 in MPI
2190      ii = 0
2191      DO ji = 1, jpnij
2192         IF ( njmppt(ji) == njmppmax   ) THEN
2193            ii=ii+1
2194            nrank_north(ii)=ji-1
2195         END IF
2196      END DO
2197      !
2198      ! create the world group
2199      CALL MPI_COMM_GROUP( mpi_comm_opa, ngrp_world, ierr )
2200      !
2201      ! Create the North group from the world group
2202      CALL MPI_GROUP_INCL( ngrp_world, ndim_rank_north, nrank_north, ngrp_north, ierr )
2203      !
2204      ! Create the North communicator , ie the pool of procs in the north group
2205      CALL MPI_COMM_CREATE( mpi_comm_opa, ngrp_north, ncomm_north, ierr )
2206      !
2207   END SUBROUTINE mpp_ini_north
2208
2209
2210   SUBROUTINE mpp_lbc_north_3d( pt3d, cd_type, psgn )
2211      !!---------------------------------------------------------------------
2212      !!                   ***  routine mpp_lbc_north_3d  ***
2213      !!
2214      !! ** Purpose :   Ensure proper north fold horizontal bondary condition
2215      !!              in mpp configuration in case of jpn1 > 1
2216      !!
2217      !! ** Method  :   North fold condition and mpp with more than one proc
2218      !!              in i-direction require a specific treatment. We gather
2219      !!              the 4 northern lines of the global domain on 1 processor
2220      !!              and apply lbc north-fold on this sub array. Then we
2221      !!              scatter the north fold array back to the processors.
2222      !!
2223      !!----------------------------------------------------------------------
2224      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pt3d      ! 3D array on which the b.c. is applied
2225      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type   ! nature of pt3d grid-points
2226      !                                                              !   = T ,  U , V , F or W  gridpoints
2227      REAL(wp)                        , INTENT(in   ) ::   psgn      ! = -1. the sign change across the north fold
2228      !!                                                             ! =  1. , the sign is kept
2229      INTEGER ::   ji, jj, jr
2230      INTEGER ::   ierr, itaille, ildi, ilei, iilb
2231      INTEGER ::   ijpj, ijpjm1, ij, iproc
2232      INTEGER, DIMENSION (jpmaxngh)          ::   ml_req_nf          ! for mpi_isend when avoiding mpi_allgather
2233      INTEGER                                ::   ml_err             ! for mpi_isend when avoiding mpi_allgather
2234      INTEGER, DIMENSION(MPI_STATUS_SIZE)    ::   ml_stat            ! for mpi_isend when avoiding mpi_allgather
2235      !!----------------------------------------------------------------------
2236      !   
2237      ijpj   = 4
2238      ityp = -1
2239      ijpjm1 = 3
2240      ztab(:,:,:) = 0.e0
2241      !
2242      DO jj = nlcj - ijpj +1, nlcj          ! put in znorthloc the last 4 jlines of pt3d
2243         ij = jj - nlcj + ijpj
2244         znorthloc(:,ij,:) = pt3d(:,jj,:)
2245      END DO
2246      !
2247      !                                     ! Build in procs of ncomm_north the znorthgloio
2248      itaille = jpi * jpk * ijpj
2249      IF ( l_north_nogather ) THEN
2250         !
2251         ! Avoid the use of mpi_allgather by exchanging only with the processes already identified
2252         ! (in nemo_northcomms) as being  involved in this process' northern boundary exchange
2253         !
2254         DO jj = nlcj-ijpj+1, nlcj          ! First put local values into the global array
2255            ij = jj - nlcj + ijpj
2256            DO ji = 1, nlci
2257               ztab(ji+nimpp-1,ij,:) = pt3d(ji,jj,:)
2258            END DO
2259         END DO
2260
2261         !
2262         ! Set the exchange type in order to access the correct list of active neighbours
2263         !
2264         SELECT CASE ( cd_type )
2265            CASE ( 'T' , 'W' )
2266               ityp = 1
2267            CASE ( 'U' )
2268               ityp = 2
2269            CASE ( 'V' )
2270               ityp = 3
2271            CASE ( 'F' )
2272               ityp = 4
2273            CASE ( 'I' )
2274               ityp = 5
2275            CASE DEFAULT
2276               ityp = -1                    ! Set a default value for unsupported types which
2277                                            ! will cause a fallback to the mpi_allgather method
2278         END SELECT
2279         IF ( ityp .gt. 0 ) THEN
2280
2281            DO jr = 1,nsndto(ityp)
2282               CALL mppsend(5, znorthloc, itaille, isendto(jr,ityp), ml_req_nf(jr) )
2283            END DO
2284            DO jr = 1,nsndto(ityp)
2285               CALL mpprecv(5, zfoldwk, itaille, isendto(jr,ityp))
2286               iproc = isendto(jr,ityp) + 1
2287               ildi = nldit (iproc)
2288               ilei = nleit (iproc)
2289               iilb = nimppt(iproc)
2290               DO jj = 1, ijpj
2291                  DO ji = ildi, ilei
2292                     ztab(ji+iilb-1,jj,:) = zfoldwk(ji,jj,:)
2293                  END DO
2294               END DO
2295            END DO
2296            IF (l_isend) THEN
2297               DO jr = 1,nsndto(ityp)
2298                  CALL mpi_wait(ml_req_nf(jr), ml_stat, ml_err)
2299               END DO
2300            ENDIF
2301
2302         ENDIF
2303
2304      ENDIF
2305
2306      IF ( ityp .lt. 0 ) THEN
2307         CALL MPI_ALLGATHER( znorthloc  , itaille, MPI_DOUBLE_PRECISION,                &
2308            &                znorthgloio, itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr )
2309         !
2310         DO jr = 1, ndim_rank_north         ! recover the global north array
2311            iproc = nrank_north(jr) + 1
2312            ildi  = nldit (iproc)
2313            ilei  = nleit (iproc)
2314            iilb  = nimppt(iproc)
2315            DO jj = 1, ijpj
2316               DO ji = ildi, ilei
2317                  ztab(ji+iilb-1,jj,:) = znorthgloio(ji,jj,:,jr)
2318               END DO
2319            END DO
2320         END DO
2321      ENDIF
2322      !
2323      ! The ztab array has been either:
2324      !  a. Fully populated by the mpi_allgather operation or
2325      !  b. Had the active points for this domain and northern neighbours populated
2326      !     by peer to peer exchanges
2327      ! Either way the array may be folded by lbc_nfd and the result for the span of
2328      ! this domain will be identical.
2329      !
2330      CALL lbc_nfd( ztab, cd_type, psgn )   ! North fold boundary condition
2331      !
2332      DO jj = nlcj-ijpj+1, nlcj             ! Scatter back to pt3d
2333         ij = jj - nlcj + ijpj
2334         DO ji= 1, nlci
2335            pt3d(ji,jj,:) = ztab(ji+nimpp-1,ij,:)
2336         END DO
2337      END DO
2338      !
2339   END SUBROUTINE mpp_lbc_north_3d
2340
2341
2342   SUBROUTINE mpp_lbc_north_2d( pt2d, cd_type, psgn)
2343      !!---------------------------------------------------------------------
2344      !!                   ***  routine mpp_lbc_north_2d  ***
2345      !!
2346      !! ** Purpose :   Ensure proper north fold horizontal bondary condition
2347      !!              in mpp configuration in case of jpn1 > 1 (for 2d array )
2348      !!
2349      !! ** Method  :   North fold condition and mpp with more than one proc
2350      !!              in i-direction require a specific treatment. We gather
2351      !!              the 4 northern lines of the global domain on 1 processor
2352      !!              and apply lbc north-fold on this sub array. Then we
2353      !!              scatter the north fold array back to the processors.
2354      !!
2355      !!----------------------------------------------------------------------
2356      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   pt2d      ! 3D array on which the b.c. is applied
2357      CHARACTER(len=1)            , INTENT(in   ) ::   cd_type   ! nature of pt3d grid-points
2358      !                                                          !   = T ,  U , V , F or W  gridpoints
2359      REAL(wp)                    , INTENT(in   ) ::   psgn      ! = -1. the sign change across the north fold
2360      !!                                                             ! =  1. , the sign is kept
2361      INTEGER ::   ji, jj, jr
2362      INTEGER ::   ierr, itaille, ildi, ilei, iilb
2363      INTEGER ::   ijpj, ijpjm1, ij, iproc
2364      INTEGER, DIMENSION (jpmaxngh)      ::   ml_req_nf          ! for mpi_isend when avoiding mpi_allgather
2365      INTEGER                            ::   ml_err             ! for mpi_isend when avoiding mpi_allgather
2366      INTEGER, DIMENSION(MPI_STATUS_SIZE)::   ml_stat            ! for mpi_isend when avoiding mpi_allgather
2367      !!----------------------------------------------------------------------
2368      !
2369      ijpj   = 4
2370      ityp = -1
2371      ijpjm1 = 3
2372      ztab_2d(:,:) = 0.e0
2373      !
2374      DO jj = nlcj-ijpj+1, nlcj             ! put in znorthloc_2d the last 4 jlines of pt2d
2375         ij = jj - nlcj + ijpj
2376         znorthloc_2d(:,ij) = pt2d(:,jj)
2377      END DO
2378
2379      !                                     ! Build in procs of ncomm_north the znorthgloio_2d
2380      itaille = jpi * ijpj
2381      IF ( l_north_nogather ) THEN
2382         !
2383         ! Avoid the use of mpi_allgather by exchanging only with the processes already identified
2384         ! (in nemo_northcomms) as being  involved in this process' northern boundary exchange
2385         !
2386         DO jj = nlcj-ijpj+1, nlcj          ! First put local values into the global array
2387            ij = jj - nlcj + ijpj
2388            DO ji = 1, nlci
2389               ztab_2d(ji+nimpp-1,ij) = pt2d(ji,jj)
2390            END DO
2391         END DO
2392
2393         !
2394         ! Set the exchange type in order to access the correct list of active neighbours
2395         !
2396         SELECT CASE ( cd_type )
2397            CASE ( 'T' , 'W' )
2398               ityp = 1
2399            CASE ( 'U' )
2400               ityp = 2
2401            CASE ( 'V' )
2402               ityp = 3
2403            CASE ( 'F' )
2404               ityp = 4
2405            CASE ( 'I' )
2406               ityp = 5
2407            CASE DEFAULT
2408               ityp = -1                    ! Set a default value for unsupported types which
2409                                            ! will cause a fallback to the mpi_allgather method
2410         END SELECT
2411
2412         IF ( ityp .gt. 0 ) THEN
2413
2414            DO jr = 1,nsndto(ityp)
2415               CALL mppsend(5, znorthloc_2d, itaille, isendto(jr,ityp), ml_req_nf(jr) )
2416            END DO
2417            DO jr = 1,nsndto(ityp)
2418               CALL mpprecv(5, zfoldwk_2d, itaille, isendto(jr,ityp))
2419               iproc = isendto(jr,ityp) + 1
2420               ildi = nldit (iproc)
2421               ilei = nleit (iproc)
2422               iilb = nimppt(iproc)
2423               DO jj = 1, ijpj
2424                  DO ji = ildi, ilei
2425                     ztab_2d(ji+iilb-1,jj) = zfoldwk_2d(ji,jj)
2426                  END DO
2427               END DO
2428            END DO
2429            IF (l_isend) THEN
2430               DO jr = 1,nsndto(ityp)
2431                  CALL mpi_wait(ml_req_nf(jr), ml_stat, ml_err)
2432               END DO
2433            ENDIF
2434
2435         ENDIF
2436
2437      ENDIF
2438
2439      IF ( ityp .lt. 0 ) THEN
2440         CALL MPI_ALLGATHER( znorthloc_2d  , itaille, MPI_DOUBLE_PRECISION,        &
2441            &                znorthgloio_2d, itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr )
2442         !
2443         DO jr = 1, ndim_rank_north            ! recover the global north array
2444            iproc = nrank_north(jr) + 1
2445            ildi = nldit (iproc)
2446            ilei = nleit (iproc)
2447            iilb = nimppt(iproc)
2448            DO jj = 1, ijpj
2449               DO ji = ildi, ilei
2450                  ztab_2d(ji+iilb-1,jj) = znorthgloio_2d(ji,jj,jr)
2451               END DO
2452            END DO
2453         END DO
2454      ENDIF
2455      !
2456      ! The ztab array has been either:
2457      !  a. Fully populated by the mpi_allgather operation or
2458      !  b. Had the active points for this domain and northern neighbours populated
2459      !     by peer to peer exchanges
2460      ! Either way the array may be folded by lbc_nfd and the result for the span of
2461      ! this domain will be identical.
2462      !
2463      CALL lbc_nfd( ztab_2d, cd_type, psgn )   ! North fold boundary condition
2464      !
2465      !
2466      DO jj = nlcj-ijpj+1, nlcj             ! Scatter back to pt2d
2467         ij = jj - nlcj + ijpj
2468         DO ji = 1, nlci
2469            pt2d(ji,jj) = ztab_2d(ji+nimpp-1,ij)
2470         END DO
2471      END DO
2472      !
2473   END SUBROUTINE mpp_lbc_north_2d
2474
2475
2476   SUBROUTINE mpp_lbc_north_e( pt2d, cd_type, psgn)
2477      !!---------------------------------------------------------------------
2478      !!                   ***  routine mpp_lbc_north_2d  ***
2479      !!
2480      !! ** Purpose :   Ensure proper north fold horizontal bondary condition
2481      !!              in mpp configuration in case of jpn1 > 1 and for 2d
2482      !!              array with outer extra halo
2483      !!
2484      !! ** Method  :   North fold condition and mpp with more than one proc
2485      !!              in i-direction require a specific treatment. We gather
2486      !!              the 4+2*jpr2dj northern lines of the global domain on 1
2487      !!              processor and apply lbc north-fold on this sub array.
2488      !!              Then we scatter the north fold array back to the processors.
2489      !!
2490      !!----------------------------------------------------------------------
2491      REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj), INTENT(inout) ::   pt2d     ! 2D array with extra halo
2492      CHARACTER(len=1)                                            , INTENT(in   ) ::   cd_type  ! nature of pt3d grid-points
2493      !                                                                                         !   = T ,  U , V , F or W -points
2494      REAL(wp)                                                    , INTENT(in   ) ::   psgn     ! = -1. the sign change across the 
2495      !!                                                                                        ! north fold, =  1. otherwise
2496      INTEGER ::   ji, jj, jr
2497      INTEGER ::   ierr, itaille, ildi, ilei, iilb
2498      INTEGER ::   ijpj, ij, iproc
2499      !!----------------------------------------------------------------------
2500      !
2501      ijpj=4
2502      ztab_e(:,:) = 0.e0
2503
2504      ij=0
2505      ! put in znorthloc_e the last 4 jlines of pt2d
2506      DO jj = nlcj - ijpj + 1 - jpr2dj, nlcj +jpr2dj
2507         ij = ij + 1
2508         DO ji = 1, jpi
2509            znorthloc_e(ji,ij)=pt2d(ji,jj)
2510         END DO
2511      END DO
2512      !
2513      itaille = jpi * ( ijpj + 2 * jpr2dj )
2514      CALL MPI_ALLGATHER( znorthloc_e(1,1)  , itaille, MPI_DOUBLE_PRECISION,    &
2515         &                znorthgloio_e(1,1,1), itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr )
2516      !
2517      DO jr = 1, ndim_rank_north            ! recover the global north array
2518         iproc = nrank_north(jr) + 1
2519         ildi = nldit (iproc)
2520         ilei = nleit (iproc)
2521         iilb = nimppt(iproc)
2522         DO jj = 1, ijpj+2*jpr2dj
2523            DO ji = ildi, ilei
2524               ztab_e(ji+iilb-1,jj) = znorthgloio_e(ji,jj,jr)
2525            END DO
2526         END DO
2527      END DO
2528
2529
2530      ! 2. North-Fold boundary conditions
2531      ! ----------------------------------
2532      CALL lbc_nfd( ztab_e(:,:), cd_type, psgn, pr2dj = jpr2dj )
2533
2534      ij = jpr2dj
2535      !! Scatter back to pt2d
2536      DO jj = nlcj - ijpj + 1 , nlcj +jpr2dj
2537      ij  = ij +1 
2538         DO ji= 1, nlci
2539            pt2d(ji,jj) = ztab_e(ji+nimpp-1,ij)
2540         END DO
2541      END DO
2542      !
2543   END SUBROUTINE mpp_lbc_north_e
2544
2545
2546   SUBROUTINE mpi_init_opa( ldtxt, ksft, code )
2547      !!---------------------------------------------------------------------
2548      !!                   ***  routine mpp_init.opa  ***
2549      !!
2550      !! ** Purpose :: export and attach a MPI buffer for bsend
2551      !!
2552      !! ** Method  :: define buffer size in namelist, if 0 no buffer attachment
2553      !!            but classical mpi_init
2554      !!
2555      !! History :: 01/11 :: IDRIS initial version for IBM only 
2556      !!            08/04 :: R. Benshila, generalisation
2557      !!---------------------------------------------------------------------
2558      CHARACTER(len=*),DIMENSION(:), INTENT(  out) ::   ldtxt 
2559      INTEGER                      , INTENT(inout) ::   ksft
2560      INTEGER                      , INTENT(  out) ::   code
2561      INTEGER                                      ::   ierr, ji
2562      LOGICAL                                      ::   mpi_was_called
2563      !!---------------------------------------------------------------------
2564      !
2565      CALL mpi_initialized( mpi_was_called, code )      ! MPI initialization
2566      IF ( code /= MPI_SUCCESS ) THEN
2567         DO ji = 1, SIZE(ldtxt) 
2568            IF( TRIM(ldtxt(ji)) /= '' )   WRITE(*,*) ldtxt(ji)      ! control print of mynode
2569         END DO         
2570         WRITE(*, cform_err)
2571         WRITE(*, *) ' lib_mpp: Error in routine mpi_initialized'
2572         CALL mpi_abort( mpi_comm_world, code, ierr )
2573      ENDIF
2574      !
2575      IF( .NOT. mpi_was_called ) THEN
2576         CALL mpi_init( code )
2577         CALL mpi_comm_dup( mpi_comm_world, mpi_comm_opa, code )
2578         IF ( code /= MPI_SUCCESS ) THEN
2579            DO ji = 1, SIZE(ldtxt) 
2580               IF( TRIM(ldtxt(ji)) /= '' )   WRITE(*,*) ldtxt(ji)      ! control print of mynode
2581            END DO
2582            WRITE(*, cform_err)
2583            WRITE(*, *) ' lib_mpp: Error in routine mpi_comm_dup'
2584            CALL mpi_abort( mpi_comm_world, code, ierr )
2585         ENDIF
2586      ENDIF
2587      !
2588      IF( nn_buffer > 0 ) THEN
2589         WRITE(ldtxt(ksft),*) 'mpi_bsend, buffer allocation of  : ', nn_buffer   ;   ksft = ksft + 1
2590         ! Buffer allocation and attachment
2591         ALLOCATE( tampon(nn_buffer), stat = ierr )
2592         IF( ierr /= 0 ) THEN
2593            DO ji = 1, SIZE(ldtxt) 
2594               IF( TRIM(ldtxt(ji)) /= '' )   WRITE(*,*) ldtxt(ji)      ! control print of mynode
2595            END DO
2596            WRITE(*, cform_err)
2597            WRITE(*, *) ' lib_mpp: Error in ALLOCATE', ierr
2598            CALL mpi_abort( mpi_comm_world, code, ierr )
2599         END IF
2600         CALL mpi_buffer_attach( tampon, nn_buffer, code )
2601      ENDIF
2602      !
2603   END SUBROUTINE mpi_init_opa
2604
2605#if defined key_mpp_rep
2606   SUBROUTINE DDPDD_MPI (ydda, yddb, ilen, itype)
2607      !!---------------------------------------------------------------------
2608      !!   Routine DDPDD_MPI: used by reduction operator MPI_SUMDD
2609      !!
2610      !!   Modification of original codes written by David H. Bailey
2611      !!   This subroutine computes yddb(i) = ydda(i)+yddb(i)
2612      !!---------------------------------------------------------------------
2613      INTEGER, INTENT(in)                         :: ilen, itype
2614      COMPLEX(wp), DIMENSION(ilen), INTENT(in)     :: ydda
2615      COMPLEX(wp), DIMENSION(ilen), INTENT(inout)  :: yddb
2616      !
2617      REAL(wp) :: zerr, zt1, zt2    ! local work variables
2618      INTEGER :: ji, ztmp           ! local scalar
2619
2620      ztmp = itype   ! avoid compilation warning
2621
2622      DO ji=1,ilen
2623      ! Compute ydda + yddb using Knuth's trick.
2624         zt1  = real(ydda(ji)) + real(yddb(ji))
2625         zerr = zt1 - real(ydda(ji))
2626         zt2  = ((real(yddb(ji)) - zerr) + (real(ydda(ji)) - (zt1 - zerr))) &
2627                + aimag(ydda(ji)) + aimag(yddb(ji))
2628
2629         ! The result is zt1 + zt2, after normalization.
2630         yddb(ji) = cmplx ( zt1 + zt2, zt2 - ((zt1 + zt2) - zt1),wp )
2631      END DO
2632
2633   END SUBROUTINE DDPDD_MPI
2634#endif
2635
2636#else
2637   !!----------------------------------------------------------------------
2638   !!   Default case:            Dummy module        share memory computing
2639   !!----------------------------------------------------------------------
2640   USE in_out_manager
2641
2642   INTERFACE mpp_sum
2643      MODULE PROCEDURE mpp_sum_a2s, mpp_sum_as, mpp_sum_ai, mpp_sum_s, mpp_sum_i, mppsum_realdd, mppsum_a_realdd
2644   END INTERFACE
2645   INTERFACE mpp_max
2646      MODULE PROCEDURE mppmax_a_int, mppmax_int, mppmax_a_real, mppmax_real
2647   END INTERFACE
2648   INTERFACE mpp_min
2649      MODULE PROCEDURE mppmin_a_int, mppmin_int, mppmin_a_real, mppmin_real
2650   END INTERFACE
2651   INTERFACE mppobc
2652      MODULE PROCEDURE mppobc_1d, mppobc_2d, mppobc_3d, mppobc_4d
2653   END INTERFACE
2654   INTERFACE mpp_minloc
2655      MODULE PROCEDURE mpp_minloc2d ,mpp_minloc3d
2656   END INTERFACE
2657   INTERFACE mpp_maxloc
2658      MODULE PROCEDURE mpp_maxloc2d ,mpp_maxloc3d
2659   END INTERFACE
2660
2661   LOGICAL, PUBLIC, PARAMETER ::   lk_mpp = .FALSE.      !: mpp flag
2662   LOGICAL, PUBLIC            ::   ln_nnogather  = .FALSE.  !: namelist control of northfold comms (needed here in case "key_mpp_mpi" is not used)
2663   INTEGER :: ncomm_ice
2664   !!----------------------------------------------------------------------
2665CONTAINS
2666
2667   INTEGER FUNCTION lib_mpp_alloc(kumout)          ! Dummy function
2668      INTEGER, INTENT(in) ::   kumout
2669      lib_mpp_alloc = 0
2670   END FUNCTION lib_mpp_alloc
2671
2672   FUNCTION mynode( ldtxt, kumnam, kstop, localComm ) RESULT (function_value)
2673      INTEGER, OPTIONAL            , INTENT(in   ) ::   localComm
2674      CHARACTER(len=*),DIMENSION(:) ::   ldtxt 
2675      INTEGER ::   kumnam, kstop
2676      IF( PRESENT( localComm ) .OR. .NOT.PRESENT( localComm ) )   function_value = 0
2677      IF( .FALSE. )   ldtxt(:) = 'never done'
2678   END FUNCTION mynode
2679
2680   SUBROUTINE mppsync                       ! Dummy routine
2681   END SUBROUTINE mppsync
2682
2683   SUBROUTINE mpp_sum_as( parr, kdim, kcom )      ! Dummy routine
2684      REAL   , DIMENSION(:) :: parr
2685      INTEGER               :: kdim
2686      INTEGER, OPTIONAL     :: kcom 
2687      WRITE(*,*) 'mpp_sum_as: You should not have seen this print! error?', kdim, parr(1), kcom
2688   END SUBROUTINE mpp_sum_as
2689
2690   SUBROUTINE mpp_sum_a2s( parr, kdim, kcom )      ! Dummy routine
2691      REAL   , DIMENSION(:,:) :: parr
2692      INTEGER               :: kdim
2693      INTEGER, OPTIONAL     :: kcom 
2694      WRITE(*,*) 'mpp_sum_a2s: You should not have seen this print! error?', kdim, parr(1,1), kcom
2695   END SUBROUTINE mpp_sum_a2s
2696
2697   SUBROUTINE mpp_sum_ai( karr, kdim, kcom )      ! Dummy routine
2698      INTEGER, DIMENSION(:) :: karr
2699      INTEGER               :: kdim
2700      INTEGER, OPTIONAL     :: kcom 
2701      WRITE(*,*) 'mpp_sum_ai: You should not have seen this print! error?', kdim, karr(1), kcom
2702   END SUBROUTINE mpp_sum_ai
2703
2704   SUBROUTINE mpp_sum_s( psca, kcom )            ! Dummy routine
2705      REAL                  :: psca
2706      INTEGER, OPTIONAL     :: kcom 
2707      WRITE(*,*) 'mpp_sum_s: You should not have seen this print! error?', psca, kcom
2708   END SUBROUTINE mpp_sum_s
2709
2710   SUBROUTINE mpp_sum_i( kint, kcom )            ! Dummy routine
2711      integer               :: kint
2712      INTEGER, OPTIONAL     :: kcom 
2713      WRITE(*,*) 'mpp_sum_i: You should not have seen this print! error?', kint, kcom
2714   END SUBROUTINE mpp_sum_i
2715
2716   SUBROUTINE mppsum_realdd( ytab, kcom )
2717      COMPLEX(wp), INTENT(inout)         :: ytab    ! input scalar
2718      INTEGER , INTENT( in  ), OPTIONAL :: kcom
2719      WRITE(*,*) 'mppsum_realdd: You should not have seen this print! error?', ytab
2720   END SUBROUTINE mppsum_realdd
2721 
2722   SUBROUTINE mppsum_a_realdd( ytab, kdim, kcom )
2723      INTEGER , INTENT( in )                        ::   kdim      ! size of ytab
2724      COMPLEX(wp), DIMENSION(kdim), INTENT( inout ) ::   ytab      ! input array
2725      INTEGER , INTENT( in  ), OPTIONAL :: kcom
2726      WRITE(*,*) 'mppsum_a_realdd: You should not have seen this print! error?', kdim, ytab(1), kcom
2727   END SUBROUTINE mppsum_a_realdd
2728
2729   SUBROUTINE mppmax_a_real( parr, kdim, kcom )
2730      REAL   , DIMENSION(:) :: parr
2731      INTEGER               :: kdim
2732      INTEGER, OPTIONAL     :: kcom 
2733      WRITE(*,*) 'mppmax_a_real: You should not have seen this print! error?', kdim, parr(1), kcom
2734   END SUBROUTINE mppmax_a_real
2735
2736   SUBROUTINE mppmax_real( psca, kcom )
2737      REAL                  :: psca
2738      INTEGER, OPTIONAL     :: kcom 
2739      WRITE(*,*) 'mppmax_real: You should not have seen this print! error?', psca, kcom
2740   END SUBROUTINE mppmax_real
2741
2742   SUBROUTINE mppmin_a_real( parr, kdim, kcom )
2743      REAL   , DIMENSION(:) :: parr
2744      INTEGER               :: kdim
2745      INTEGER, OPTIONAL     :: kcom 
2746      WRITE(*,*) 'mppmin_a_real: You should not have seen this print! error?', kdim, parr(1), kcom
2747   END SUBROUTINE mppmin_a_real
2748
2749   SUBROUTINE mppmin_real( psca, kcom )
2750      REAL                  :: psca
2751      INTEGER, OPTIONAL     :: kcom 
2752      WRITE(*,*) 'mppmin_real: You should not have seen this print! error?', psca, kcom
2753   END SUBROUTINE mppmin_real
2754
2755   SUBROUTINE mppmax_a_int( karr, kdim ,kcom)
2756      INTEGER, DIMENSION(:) :: karr
2757      INTEGER               :: kdim
2758      INTEGER, OPTIONAL     :: kcom 
2759      WRITE(*,*) 'mppmax_a_int: You should not have seen this print! error?', kdim, karr(1), kcom
2760   END SUBROUTINE mppmax_a_int
2761
2762   SUBROUTINE mppmax_int( kint, kcom)
2763      INTEGER               :: kint
2764      INTEGER, OPTIONAL     :: kcom 
2765      WRITE(*,*) 'mppmax_int: You should not have seen this print! error?', kint, kcom
2766   END SUBROUTINE mppmax_int
2767
2768   SUBROUTINE mppmin_a_int( karr, kdim, kcom )
2769      INTEGER, DIMENSION(:) :: karr
2770      INTEGER               :: kdim
2771      INTEGER, OPTIONAL     :: kcom 
2772      WRITE(*,*) 'mppmin_a_int: You should not have seen this print! error?', kdim, karr(1), kcom
2773   END SUBROUTINE mppmin_a_int
2774
2775   SUBROUTINE mppmin_int( kint, kcom )
2776      INTEGER               :: kint
2777      INTEGER, OPTIONAL     :: kcom 
2778      WRITE(*,*) 'mppmin_int: You should not have seen this print! error?', kint, kcom
2779   END SUBROUTINE mppmin_int
2780
2781   SUBROUTINE mppobc_1d( parr, kd1, kd2, kl, kk, ktype, kij, knum )
2782      INTEGER  ::   kd1, kd2, kl , kk, ktype, kij, knum
2783      REAL, DIMENSION(:) ::   parr           ! variable array
2784      WRITE(*,*) 'mppobc: You should not have seen this print! error?', parr(1), kd1, kd2, kl, kk, ktype, kij, knum
2785   END SUBROUTINE mppobc_1d
2786
2787   SUBROUTINE mppobc_2d( parr, kd1, kd2, kl, kk, ktype, kij, knum )
2788      INTEGER  ::   kd1, kd2, kl , kk, ktype, kij, knum
2789      REAL, DIMENSION(:,:) ::   parr           ! variable array
2790      WRITE(*,*) 'mppobc: You should not have seen this print! error?', parr(1,1), kd1, kd2, kl, kk, ktype, kij, knum
2791   END SUBROUTINE mppobc_2d
2792
2793   SUBROUTINE mppobc_3d( parr, kd1, kd2, kl, kk, ktype, kij, knum )
2794      INTEGER  ::   kd1, kd2, kl , kk, ktype, kij, knum
2795      REAL, DIMENSION(:,:,:) ::   parr           ! variable array
2796      WRITE(*,*) 'mppobc: You should not have seen this print! error?', parr(1,1,1), kd1, kd2, kl, kk, ktype, kij, knum
2797   END SUBROUTINE mppobc_3d
2798
2799   SUBROUTINE mppobc_4d( parr, kd1, kd2, kl, kk, ktype, kij, knum )
2800      INTEGER  ::   kd1, kd2, kl , kk, ktype, kij, knum
2801      REAL, DIMENSION(:,:,:,:) ::   parr           ! variable array
2802      WRITE(*,*) 'mppobc: You should not have seen this print! error?', parr(1,1,1,1), kd1, kd2, kl, kk, ktype, kij, knum
2803   END SUBROUTINE mppobc_4d
2804
2805   SUBROUTINE mpp_minloc2d( ptab, pmask, pmin, ki, kj )
2806      REAL                   :: pmin
2807      REAL , DIMENSION (:,:) :: ptab, pmask
2808      INTEGER :: ki, kj
2809      WRITE(*,*) 'mpp_minloc2d: You should not have seen this print! error?', pmin, ki, kj, ptab(1,1), pmask(1,1)
2810   END SUBROUTINE mpp_minloc2d
2811
2812   SUBROUTINE mpp_minloc3d( ptab, pmask, pmin, ki, kj, kk )
2813      REAL                     :: pmin
2814      REAL , DIMENSION (:,:,:) :: ptab, pmask
2815      INTEGER :: ki, kj, kk
2816      WRITE(*,*) 'mpp_minloc3d: You should not have seen this print! error?', pmin, ki, kj, kk, ptab(1,1,1), pmask(1,1,1)
2817   END SUBROUTINE mpp_minloc3d
2818
2819   SUBROUTINE mpp_maxloc2d( ptab, pmask, pmax, ki, kj )
2820      REAL                   :: pmax
2821      REAL , DIMENSION (:,:) :: ptab, pmask
2822      INTEGER :: ki, kj
2823      WRITE(*,*) 'mpp_maxloc2d: You should not have seen this print! error?', pmax, ki, kj, ptab(1,1), pmask(1,1)
2824   END SUBROUTINE mpp_maxloc2d
2825
2826   SUBROUTINE mpp_maxloc3d( ptab, pmask, pmax, ki, kj, kk )
2827      REAL                     :: pmax
2828      REAL , DIMENSION (:,:,:) :: ptab, pmask
2829      INTEGER :: ki, kj, kk
2830      WRITE(*,*) 'mpp_maxloc3d: You should not have seen this print! error?', pmax, ki, kj, kk, ptab(1,1,1), pmask(1,1,1)
2831   END SUBROUTINE mpp_maxloc3d
2832
2833   SUBROUTINE mppstop
2834      WRITE(*,*) 'mppstop: You should not have seen this print if running in mpp mode! error?...'
2835      WRITE(*,*) 'mppstop: ..otherwise this is a stop condition raised by ctl_stop in single processor mode'
2836      STOP
2837   END SUBROUTINE mppstop
2838
2839   SUBROUTINE mpp_ini_ice( kcom, knum )
2840      INTEGER :: kcom, knum
2841      WRITE(*,*) 'mpp_ini_ice: You should not have seen this print! error?', kcom, knum
2842   END SUBROUTINE mpp_ini_ice
2843
2844   SUBROUTINE mpp_ini_znl( knum )
2845      INTEGER :: knum
2846      WRITE(*,*) 'mpp_ini_znl: You should not have seen this print! error?', knum
2847   END SUBROUTINE mpp_ini_znl
2848
2849   SUBROUTINE mpp_comm_free( kcom )
2850      INTEGER :: kcom
2851      WRITE(*,*) 'mpp_comm_free: You should not have seen this print! error?', kcom
2852   END SUBROUTINE mpp_comm_free
2853#endif
2854
2855   !!----------------------------------------------------------------------
2856   !!   All cases:         ctl_stop, ctl_warn, get_unit, ctl_opn   routines
2857   !!----------------------------------------------------------------------
2858
2859   SUBROUTINE ctl_stop( cd1, cd2, cd3, cd4, cd5 ,   &
2860      &                 cd6, cd7, cd8, cd9, cd10 )
2861      !!----------------------------------------------------------------------
2862      !!                  ***  ROUTINE  stop_opa  ***
2863      !!
2864      !! ** Purpose :   print in ocean.outpput file a error message and
2865      !!                increment the error number (nstop) by one.
2866      !!----------------------------------------------------------------------
2867      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd1, cd2, cd3, cd4, cd5
2868      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd6, cd7, cd8, cd9, cd10
2869      !!----------------------------------------------------------------------
2870      !
2871      nstop = nstop + 1 
2872      IF(lwp) THEN
2873         WRITE(numout,cform_err)
2874         IF( PRESENT(cd1 ) )   WRITE(numout,*) cd1
2875         IF( PRESENT(cd2 ) )   WRITE(numout,*) cd2
2876         IF( PRESENT(cd3 ) )   WRITE(numout,*) cd3
2877         IF( PRESENT(cd4 ) )   WRITE(numout,*) cd4
2878         IF( PRESENT(cd5 ) )   WRITE(numout,*) cd5
2879         IF( PRESENT(cd6 ) )   WRITE(numout,*) cd6
2880         IF( PRESENT(cd7 ) )   WRITE(numout,*) cd7
2881         IF( PRESENT(cd8 ) )   WRITE(numout,*) cd8
2882         IF( PRESENT(cd9 ) )   WRITE(numout,*) cd9
2883         IF( PRESENT(cd10) )   WRITE(numout,*) cd10
2884      ENDIF
2885                               CALL FLUSH(numout    )
2886      IF( numstp     /= -1 )   CALL FLUSH(numstp    )
2887      IF( numsol     /= -1 )   CALL FLUSH(numsol    )
2888      IF( numevo_ice /= -1 )   CALL FLUSH(numevo_ice)
2889      !
2890      IF( cd1 == 'STOP' ) THEN
2891         IF(lwp) WRITE(numout,*)  'huge E-R-R-O-R : immediate stop'
2892         CALL mppstop()
2893      ENDIF
2894      !
2895   END SUBROUTINE ctl_stop
2896
2897
2898   SUBROUTINE ctl_warn( cd1, cd2, cd3, cd4, cd5,   &
2899      &                 cd6, cd7, cd8, cd9, cd10 )
2900      !!----------------------------------------------------------------------
2901      !!                  ***  ROUTINE  stop_warn  ***
2902      !!
2903      !! ** Purpose :   print in ocean.outpput file a error message and
2904      !!                increment the warning number (nwarn) by one.
2905      !!----------------------------------------------------------------------
2906      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd1, cd2, cd3, cd4, cd5
2907      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd6, cd7, cd8, cd9, cd10
2908      !!----------------------------------------------------------------------
2909      !
2910      nwarn = nwarn + 1 
2911      IF(lwp) THEN
2912         WRITE(numout,cform_war)
2913         IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1
2914         IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2
2915         IF( PRESENT(cd3 ) ) WRITE(numout,*) cd3
2916         IF( PRESENT(cd4 ) ) WRITE(numout,*) cd4
2917         IF( PRESENT(cd5 ) ) WRITE(numout,*) cd5
2918         IF( PRESENT(cd6 ) ) WRITE(numout,*) cd6
2919         IF( PRESENT(cd7 ) ) WRITE(numout,*) cd7
2920         IF( PRESENT(cd8 ) ) WRITE(numout,*) cd8
2921         IF( PRESENT(cd9 ) ) WRITE(numout,*) cd9
2922         IF( PRESENT(cd10) ) WRITE(numout,*) cd10
2923      ENDIF
2924      CALL FLUSH(numout)
2925      !
2926   END SUBROUTINE ctl_warn
2927
2928
2929   SUBROUTINE ctl_opn( knum, cdfile, cdstat, cdform, cdacce, klengh, kout, ldwp, karea )
2930      !!----------------------------------------------------------------------
2931      !!                  ***  ROUTINE ctl_opn  ***
2932      !!
2933      !! ** Purpose :   Open file and check if required file is available.
2934      !!
2935      !! ** Method  :   Fortan open
2936      !!----------------------------------------------------------------------
2937      INTEGER          , INTENT(  out) ::   knum      ! logical unit to open
2938      CHARACTER(len=*) , INTENT(in   ) ::   cdfile    ! file name to open
2939      CHARACTER(len=*) , INTENT(in   ) ::   cdstat    ! disposition specifier
2940      CHARACTER(len=*) , INTENT(in   ) ::   cdform    ! formatting specifier
2941      CHARACTER(len=*) , INTENT(in   ) ::   cdacce    ! access specifier
2942      INTEGER          , INTENT(in   ) ::   klengh    ! record length
2943      INTEGER          , INTENT(in   ) ::   kout      ! number of logical units for write
2944      LOGICAL          , INTENT(in   ) ::   ldwp      ! boolean term for print
2945      INTEGER, OPTIONAL, INTENT(in   ) ::   karea     ! proc number
2946      !!
2947      CHARACTER(len=80) ::   clfile
2948      INTEGER           ::   iost
2949      !!----------------------------------------------------------------------
2950
2951      ! adapt filename
2952      ! ----------------
2953      clfile = TRIM(cdfile)
2954      IF( PRESENT( karea ) ) THEN
2955         IF( karea > 1 )   WRITE(clfile, "(a,'_',i4.4)") TRIM(clfile), karea-1
2956      ENDIF
2957#if defined key_agrif
2958      IF( .NOT. Agrif_Root() )   clfile = TRIM(Agrif_CFixed())//'_'//TRIM(clfile)
2959      knum=Agrif_Get_Unit()
2960#else
2961      knum=get_unit()
2962#endif
2963
2964      iost=0
2965      IF( cdacce(1:6) == 'DIRECT' )  THEN
2966         OPEN( UNIT=knum, FILE=clfile, FORM=cdform, ACCESS=cdacce, STATUS=cdstat, RECL=klengh, ERR=100, IOSTAT=iost )
2967      ELSE
2968         OPEN( UNIT=knum, FILE=clfile, FORM=cdform, ACCESS=cdacce, STATUS=cdstat             , ERR=100, IOSTAT=iost )
2969      ENDIF
2970      IF( iost == 0 ) THEN
2971         IF(ldwp) THEN
2972            WRITE(kout,*) '     file   : ', clfile,' open ok'
2973            WRITE(kout,*) '     unit   = ', knum
2974            WRITE(kout,*) '     status = ', cdstat
2975            WRITE(kout,*) '     form   = ', cdform
2976            WRITE(kout,*) '     access = ', cdacce
2977            WRITE(kout,*)
2978         ENDIF
2979      ENDIF
2980100   CONTINUE
2981      IF( iost /= 0 ) THEN
2982         IF(ldwp) THEN
2983            WRITE(kout,*)
2984            WRITE(kout,*) ' ===>>>> : bad opening file: ', clfile
2985            WRITE(kout,*) ' =======   ===  '
2986            WRITE(kout,*) '           unit   = ', knum
2987            WRITE(kout,*) '           status = ', cdstat
2988            WRITE(kout,*) '           form   = ', cdform
2989            WRITE(kout,*) '           access = ', cdacce
2990            WRITE(kout,*) '           iostat = ', iost
2991            WRITE(kout,*) '           we stop. verify the file '
2992            WRITE(kout,*)
2993         ENDIF
2994         STOP 'ctl_opn bad opening'
2995      ENDIF
2996     
2997   END SUBROUTINE ctl_opn
2998
2999
3000   INTEGER FUNCTION get_unit()
3001      !!----------------------------------------------------------------------
3002      !!                  ***  FUNCTION  get_unit  ***
3003      !!
3004      !! ** Purpose :   return the index of an unused logical unit
3005      !!----------------------------------------------------------------------
3006      LOGICAL :: llopn 
3007      !!----------------------------------------------------------------------
3008      !
3009      get_unit = 15   ! choose a unit that is big enough then it is not already used in NEMO
3010      llopn = .TRUE.
3011      DO WHILE( (get_unit < 998) .AND. llopn )
3012         get_unit = get_unit + 1
3013         INQUIRE( unit = get_unit, opened = llopn )
3014      END DO
3015      IF( (get_unit == 999) .AND. llopn ) THEN
3016         CALL ctl_stop( 'get_unit: All logical units until 999 are used...' )
3017         get_unit = -1
3018      ENDIF
3019      !
3020   END FUNCTION get_unit
3021
3022   !!----------------------------------------------------------------------
3023END MODULE lib_mpp
Note: See TracBrowser for help on using the repository browser.