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 branches/2012/dev_r3337_NOCS10_ICB/NEMOGCM/NEMO/OPA_SRC/LBC – NEMO

source: branches/2012/dev_r3337_NOCS10_ICB/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90 @ 3340

Last change on this file since 3340 was 3340, checked in by sga, 12 years ago

NEMO branch dev_r3337_NOCS10_ICB: add changes to ocean code to allow interface to iceberg code

  • Property svn:keywords set to Id
File size: 129.8 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   mppsend, mpprecv                          ! needed by ICB routines
70   PUBLIC   lib_mpp_alloc   ! Called in nemogcm.F90
71
72   !! * Interfaces
73   !! define generic interface for these routine as they are called sometimes
74   !! with scalar arguments instead of array arguments, which causes problems
75   !! for the compilation on AIX system as well as NEC and SGI. Ok on COMPACQ
76   INTERFACE mpp_min
77      MODULE PROCEDURE mppmin_a_int, mppmin_int, mppmin_a_real, mppmin_real
78   END INTERFACE
79   INTERFACE mpp_max
80      MODULE PROCEDURE mppmax_a_int, mppmax_int, mppmax_a_real, mppmax_real
81   END INTERFACE
82   INTERFACE mpp_sum
83# if defined key_mpp_rep
84      MODULE PROCEDURE mppsum_a_int, mppsum_int, mppsum_a_real, mppsum_real, &
85                       mppsum_realdd, mppsum_a_realdd
86# else
87      MODULE PROCEDURE mppsum_a_int, mppsum_int, mppsum_a_real, mppsum_real
88# endif
89   END INTERFACE
90   INTERFACE mpp_lbc_north
91      MODULE PROCEDURE mpp_lbc_north_3d, mpp_lbc_north_2d 
92   END INTERFACE
93   INTERFACE mpp_minloc
94      MODULE PROCEDURE mpp_minloc2d ,mpp_minloc3d
95   END INTERFACE
96   INTERFACE mpp_maxloc
97      MODULE PROCEDURE mpp_maxloc2d ,mpp_maxloc3d
98   END INTERFACE
99   
100   !! ========================= !!
101   !!  MPI  variable definition !!
102   !! ========================= !!
103!$AGRIF_DO_NOT_TREAT
104   INCLUDE 'mpif.h'
105!$AGRIF_END_DO_NOT_TREAT
106   
107   LOGICAL, PUBLIC, PARAMETER ::   lk_mpp = .TRUE.    !: mpp flag
108
109   INTEGER, PARAMETER         ::   nprocmax = 2**10   ! maximun dimension (required to be a power of 2)
110   
111   INTEGER ::   mppsize        ! number of process
112   INTEGER ::   mpprank        ! process number  [ 0 - size-1 ]
113!$AGRIF_DO_NOT_TREAT
114   INTEGER, PUBLIC ::   mpi_comm_opa   ! opa local communicator
115!$AGRIF_END_DO_NOT_TREAT
116
117# if defined key_mpp_rep
118   INTEGER :: MPI_SUMDD
119# endif
120
121   ! variables used in case of sea-ice
122   INTEGER, PUBLIC ::   ncomm_ice       !: communicator made by the processors with sea-ice
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         , PUBLIC ::   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
163   ! Arrays used in mpp_lbc_north_3d()
164   REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE, SAVE   ::   ztab, znorthloc
165   REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, SAVE   ::   znorthgloio
166   REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE, SAVE   ::   zfoldwk      ! Workspace for message transfers avoiding mpi_allgather
167
168   ! Arrays used in mpp_lbc_north_2d()
169   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   ztab_2d, znorthloc_2d
170   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE    ::   znorthgloio_2d
171   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   zfoldwk_2d    ! Workspace for message transfers avoiding mpi_allgather
172
173   ! Arrays used in mpp_lbc_north_e()
174   REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   ztab_e, znorthloc_e
175   REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE    ::   znorthgloio_e
176
177   ! North fold arrays used to minimise the use of allgather operations. Set in nemo_northcomms (nemogcm) so need to be public
178   INTEGER, PUBLIC,  PARAMETER :: jpmaxngh = 8                 ! Assumed maximum number of active neighbours
179   INTEGER, PUBLIC,  PARAMETER :: jptyps   = 5                 ! Number of different neighbour lists to be used for northfold exchanges
180   INTEGER, PUBLIC,  DIMENSION (jpmaxngh,jptyps)    ::   isendto
181   INTEGER, PUBLIC,  DIMENSION (jptyps)             ::   nsndto
182   LOGICAL, PUBLIC                                  ::   ln_nnogather     = .FALSE.  ! namelist control of northfold comms
183   LOGICAL, PUBLIC                                  ::   l_north_nogather = .FALSE.  ! internal control of northfold comms
184   INTEGER, PUBLIC                                  ::   ityp
185   !!----------------------------------------------------------------------
186   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
187   !! $Id$
188   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
189   !!----------------------------------------------------------------------
190CONTAINS
191
192   INTEGER FUNCTION lib_mpp_alloc( kumout )
193      !!----------------------------------------------------------------------
194      !!              ***  routine lib_mpp_alloc  ***
195      !!----------------------------------------------------------------------
196      INTEGER, INTENT(in) ::   kumout   ! ocean.output logical unit
197      !!----------------------------------------------------------------------
198      !
199      ALLOCATE( t4ns(jpi,jprecj,jpk,2,2) , t4sn(jpi,jprecj,jpk,2,2) ,                                            &
200         &      t4ew(jpj,jpreci,jpk,2,2) , t4we(jpj,jpreci,jpk,2,2) ,                                            &
201         &      t4p1(jpi,jprecj,jpk,2,2) , t4p2(jpi,jprecj,jpk,2,2) ,                                            &
202         &      t3ns(jpi,jprecj,jpk,2)   , t3sn(jpi,jprecj,jpk,2)   ,                                            &
203         &      t3ew(jpj,jpreci,jpk,2)   , t3we(jpj,jpreci,jpk,2)   ,                                            &
204         &      t3p1(jpi,jprecj,jpk,2)   , t3p2(jpi,jprecj,jpk,2)   ,                                            &
205         &      t2ns(jpi,jprecj    ,2)   , t2sn(jpi,jprecj    ,2)   ,                                            &
206         &      t2ew(jpj,jpreci    ,2)   , t2we(jpj,jpreci    ,2)   ,                                            &
207         &      t2p1(jpi,jprecj    ,2)   , t2p2(jpi,jprecj    ,2)   ,                                            &
208         !
209         &      ztab(jpiglo,4,jpk) , znorthloc(jpi,4,jpk) , znorthgloio(jpi,4,jpk,jpni) ,                        &
210         &      zfoldwk(jpi,4,jpk) ,                                                                             &
211         !
212         &      ztab_2d(jpiglo,4)  , znorthloc_2d(jpi,4)  , znorthgloio_2d(jpi,4,jpni)  ,                        &
213         &      zfoldwk_2d(jpi,4)  ,                                                                             &
214         !
215         &      ztab_e(jpiglo,4+2*jpr2dj) , znorthloc_e(jpi,4+2*jpr2dj) , znorthgloio_e(jpi,4+2*jpr2dj,jpni) ,   &
216         !
217         &      STAT=lib_mpp_alloc )
218         !
219      IF( lib_mpp_alloc /= 0 ) THEN
220         WRITE(kumout,cform_war)
221         WRITE(kumout,*) 'lib_mpp_alloc : failed to allocate arrays'
222      ENDIF
223      !
224   END FUNCTION lib_mpp_alloc
225
226
227   FUNCTION mynode( ldtxt, kumnam, kstop, localComm )
228      !!----------------------------------------------------------------------
229      !!                  ***  routine mynode  ***
230      !!                   
231      !! ** Purpose :   Find processor unit
232      !!----------------------------------------------------------------------
233      CHARACTER(len=*),DIMENSION(:), INTENT(  out) ::   ldtxt 
234      INTEGER                      , INTENT(in   ) ::   kumnam       ! namelist logical unit
235      INTEGER                      , INTENT(inout) ::   kstop        ! stop indicator
236      INTEGER, OPTIONAL            , INTENT(in   ) ::   localComm
237      !
238      INTEGER ::   mynode, ierr, code, ji, ii
239      LOGICAL ::   mpi_was_called
240      !
241      NAMELIST/nammpp/ cn_mpi_send, nn_buffer, jpni, jpnj, jpnij, ln_nnogather
242      !!----------------------------------------------------------------------
243      !
244      ii = 1
245      WRITE(ldtxt(ii),*)                                                                          ;   ii = ii + 1
246      WRITE(ldtxt(ii),*) 'mynode : mpi initialisation'                                            ;   ii = ii + 1
247      WRITE(ldtxt(ii),*) '~~~~~~ '                                                                ;   ii = ii + 1
248      !
249      jpni = -1; jpnj = -1; jpnij = -1
250      REWIND( kumnam )               ! Namelist namrun : parameters of the run
251      READ  ( kumnam, nammpp )
252      !                              ! control print
253      WRITE(ldtxt(ii),*) '   Namelist nammpp'                                                     ;   ii = ii + 1
254      WRITE(ldtxt(ii),*) '      mpi send type                      cn_mpi_send = ', cn_mpi_send   ;   ii = ii + 1
255      WRITE(ldtxt(ii),*) '      size in bytes of exported buffer   nn_buffer   = ', nn_buffer     ;   ii = ii + 1
256
257#if defined key_agrif
258      IF( .NOT. Agrif_Root() ) THEN
259         jpni  = Agrif_Parent(jpni ) 
260         jpnj  = Agrif_Parent(jpnj )
261         jpnij = Agrif_Parent(jpnij)
262      ENDIF
263#endif
264
265      IF(jpnij < 1)THEN
266         ! If jpnij is not specified in namelist then we calculate it - this
267         ! means there will be no land cutting out.
268         jpnij = jpni * jpnj
269      END IF
270
271      IF( (jpni < 1) .OR. (jpnj < 1) )THEN
272         WRITE(ldtxt(ii),*) '      jpni, jpnj and jpnij will be calculated automatically'; ii = ii + 1
273      ELSE
274         WRITE(ldtxt(ii),*) '      processor grid extent in i         jpni = ',jpni; ii = ii + 1
275         WRITE(ldtxt(ii),*) '      processor grid extent in j         jpnj = ',jpnj; ii = ii + 1
276         WRITE(ldtxt(ii),*) '      number of local domains           jpnij = ',jpnij; ii = ii +1
277      END IF
278
279      WRITE(ldtxt(ii),*) '      avoid use of mpi_allgather at the north fold  ln_nnogather = ', ln_nnogather  ; ii = ii + 1
280
281      CALL mpi_initialized ( mpi_was_called, code )
282      IF( code /= MPI_SUCCESS ) THEN
283         DO ji = 1, SIZE(ldtxt) 
284            IF( TRIM(ldtxt(ji)) /= '' )   WRITE(*,*) ldtxt(ji)      ! control print of mynode
285         END DO         
286         WRITE(*, cform_err)
287         WRITE(*, *) 'lib_mpp: Error in routine mpi_initialized'
288         CALL mpi_abort( mpi_comm_world, code, ierr )
289      ENDIF
290
291      IF( mpi_was_called ) THEN
292         !
293         SELECT CASE ( cn_mpi_send )
294         CASE ( 'S' )                ! Standard mpi send (blocking)
295            WRITE(ldtxt(ii),*) '           Standard blocking mpi send (send)'                     ;   ii = ii + 1
296         CASE ( 'B' )                ! Buffer mpi send (blocking)
297            WRITE(ldtxt(ii),*) '           Buffer blocking mpi send (bsend)'                      ;   ii = ii + 1
298            IF( Agrif_Root() )   CALL mpi_init_opa( ldtxt, ii, ierr ) 
299         CASE ( 'I' )                ! Immediate mpi send (non-blocking send)
300            WRITE(ldtxt(ii),*) '           Immediate non-blocking send (isend)'                   ;   ii = ii + 1
301            l_isend = .TRUE.
302         CASE DEFAULT
303            WRITE(ldtxt(ii),cform_err)                                                            ;   ii = ii + 1
304            WRITE(ldtxt(ii),*) '           bad value for cn_mpi_send = ', cn_mpi_send             ;   ii = ii + 1
305            kstop = kstop + 1
306         END SELECT
307      ELSE IF ( PRESENT(localComm) .and. .not. mpi_was_called ) THEN
308         WRITE(ldtxt(ii),*) ' lib_mpp: You cannot provide a local communicator '                  ;   ii = ii + 1
309         WRITE(ldtxt(ii),*) '          without calling MPI_Init before ! '                        ;   ii = ii + 1
310         kstop = kstop + 1
311      ELSE
312         SELECT CASE ( cn_mpi_send )
313         CASE ( 'S' )                ! Standard mpi send (blocking)
314            WRITE(ldtxt(ii),*) '           Standard blocking mpi send (send)'                     ;   ii = ii + 1
315            CALL mpi_init( ierr )
316         CASE ( 'B' )                ! Buffer mpi send (blocking)
317            WRITE(ldtxt(ii),*) '           Buffer blocking mpi send (bsend)'                      ;   ii = ii + 1
318            IF( Agrif_Root() )   CALL mpi_init_opa( ldtxt, ii, ierr )
319         CASE ( 'I' )                ! Immediate mpi send (non-blocking send)
320            WRITE(ldtxt(ii),*) '           Immediate non-blocking send (isend)'                   ;   ii = ii + 1
321            l_isend = .TRUE.
322            CALL mpi_init( ierr )
323         CASE DEFAULT
324            WRITE(ldtxt(ii),cform_err)                                                            ;   ii = ii + 1
325            WRITE(ldtxt(ii),*) '           bad value for cn_mpi_send = ', cn_mpi_send             ;   ii = ii + 1
326            kstop = kstop + 1
327         END SELECT
328         !
329      ENDIF
330
331      IF( PRESENT(localComm) ) THEN
332         IF( Agrif_Root() ) THEN
333            mpi_comm_opa = localComm
334         ENDIF
335      ELSE
336         CALL mpi_comm_dup( mpi_comm_world, mpi_comm_opa, code)
337         IF( code /= MPI_SUCCESS ) THEN
338            DO ji = 1, SIZE(ldtxt) 
339               IF( TRIM(ldtxt(ji)) /= '' )   WRITE(*,*) ldtxt(ji)      ! control print of mynode
340            END DO
341            WRITE(*, cform_err)
342            WRITE(*, *) ' lib_mpp: Error in routine mpi_comm_dup'
343            CALL mpi_abort( mpi_comm_world, code, ierr )
344         ENDIF
345      ENDIF
346
347      CALL mpi_comm_rank( mpi_comm_opa, mpprank, ierr )
348      CALL mpi_comm_size( mpi_comm_opa, mppsize, ierr )
349      mynode = mpprank
350      !
351#if defined key_mpp_rep
352      CALL MPI_OP_CREATE(DDPDD_MPI, .TRUE., MPI_SUMDD, ierr)
353#endif
354      !
355   END FUNCTION mynode
356
357
358   SUBROUTINE mpp_lnk_3d( ptab, cd_type, psgn, cd_mpp, pval )
359      !!----------------------------------------------------------------------
360      !!                  ***  routine mpp_lnk_3d  ***
361      !!
362      !! ** Purpose :   Message passing manadgement
363      !!
364      !! ** Method  :   Use mppsend and mpprecv function for passing mask
365      !!      between processors following neighboring subdomains.
366      !!            domain parameters
367      !!                    nlci   : first dimension of the local subdomain
368      !!                    nlcj   : second dimension of the local subdomain
369      !!                    nbondi : mark for "east-west local boundary"
370      !!                    nbondj : mark for "north-south local boundary"
371      !!                    noea   : number for local neighboring processors
372      !!                    nowe   : number for local neighboring processors
373      !!                    noso   : number for local neighboring processors
374      !!                    nono   : number for local neighboring processors
375      !!
376      !! ** Action  :   ptab with update value at its periphery
377      !!
378      !!----------------------------------------------------------------------
379      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptab     ! 3D array on which the boundary condition is applied
380      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type  ! define the nature of ptab array grid-points
381      !                                                             ! = T , U , V , F , W points
382      REAL(wp)                        , INTENT(in   ) ::   psgn     ! =-1 the sign change across the north fold boundary
383      !                                                             ! =  1. , the sign is kept
384      CHARACTER(len=3), OPTIONAL      , INTENT(in   ) ::   cd_mpp   ! fill the overlap area only
385      REAL(wp)        , OPTIONAL      , INTENT(in   ) ::   pval     ! background value (used at closed boundaries)
386      !!
387      INTEGER  ::   ji, jj, jk, jl             ! dummy loop indices
388      INTEGER  ::   imigr, iihom, ijhom        ! temporary integers
389      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
390      REAL(wp) ::   zland
391      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
392      !!----------------------------------------------------------------------
393
394      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value
395      ELSE                         ;   zland = 0.e0      ! zero by default
396      ENDIF
397
398      ! 1. standard boundary treatment
399      ! ------------------------------
400      IF( PRESENT( cd_mpp ) ) THEN      ! only fill added line/raw with existing values
401         !
402         ! WARNING ptab is defined only between nld and nle
403         DO jk = 1, jpk
404            DO jj = nlcj+1, jpj                 ! added line(s)   (inner only)
405               ptab(nldi  :nlei  , jj          ,jk) = ptab(nldi:nlei,     nlej,jk)   
406               ptab(1     :nldi-1, jj          ,jk) = ptab(nldi     ,     nlej,jk)
407               ptab(nlei+1:nlci  , jj          ,jk) = ptab(     nlei,     nlej,jk)
408            END DO
409            DO ji = nlci+1, jpi                 ! added column(s) (full)
410               ptab(ji           ,nldj  :nlej  ,jk) = ptab(     nlei,nldj:nlej,jk)
411               ptab(ji           ,1     :nldj-1,jk) = ptab(     nlei,nldj     ,jk)
412               ptab(ji           ,nlej+1:jpj   ,jk) = ptab(     nlei,     nlej,jk)
413            END DO
414         END DO
415         !
416      ELSE                              ! standard close or cyclic treatment
417         !
418         !                                   ! East-West boundaries
419         !                                        !* Cyclic east-west
420         IF( nbondi == 2 .AND. (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
421            ptab( 1 ,:,:) = ptab(jpim1,:,:)
422            ptab(jpi,:,:) = ptab(  2  ,:,:)
423         ELSE                                     !* closed
424            IF( .NOT. cd_type == 'F' )   ptab(     1       :jpreci,:,:) = zland    ! south except F-point
425                                         ptab(nlci-jpreci+1:jpi   ,:,:) = zland    ! north
426         ENDIF
427         !                                   ! North-South boundaries (always closed)
428         IF( .NOT. cd_type == 'F' )   ptab(:,     1       :jprecj,:) = zland       ! south except F-point
429                                      ptab(:,nlcj-jprecj+1:jpj   ,:) = zland       ! north
430         !
431      ENDIF
432
433      ! 2. East and west directions exchange
434      ! ------------------------------------
435      ! we play with the neigbours AND the row number because of the periodicity
436      !
437      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
438      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
439         iihom = nlci-nreci
440         DO jl = 1, jpreci
441            t3ew(:,jl,:,1) = ptab(jpreci+jl,:,:)
442            t3we(:,jl,:,1) = ptab(iihom +jl,:,:)
443         END DO
444      END SELECT 
445      !
446      !                           ! Migrations
447      imigr = jpreci * jpj * jpk
448      !
449      SELECT CASE ( nbondi ) 
450      CASE ( -1 )
451         CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req1 )
452         CALL mpprecv( 1, t3ew(1,1,1,2), imigr, noea )
453         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
454      CASE ( 0 )
455         CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 )
456         CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req2 )
457         CALL mpprecv( 1, t3ew(1,1,1,2), imigr, noea )
458         CALL mpprecv( 2, t3we(1,1,1,2), imigr, nowe )
459         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
460         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
461      CASE ( 1 )
462         CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 )
463         CALL mpprecv( 2, t3we(1,1,1,2), imigr, nowe )
464         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
465      END SELECT
466      !
467      !                           ! Write Dirichlet lateral conditions
468      iihom = nlci-jpreci
469      !
470      SELECT CASE ( nbondi )
471      CASE ( -1 )
472         DO jl = 1, jpreci
473            ptab(iihom+jl,:,:) = t3ew(:,jl,:,2)
474         END DO
475      CASE ( 0 ) 
476         DO jl = 1, jpreci
477            ptab(jl      ,:,:) = t3we(:,jl,:,2)
478            ptab(iihom+jl,:,:) = t3ew(:,jl,:,2)
479         END DO
480      CASE ( 1 )
481         DO jl = 1, jpreci
482            ptab(jl      ,:,:) = t3we(:,jl,:,2)
483         END DO
484      END SELECT
485
486
487      ! 3. North and south directions
488      ! -----------------------------
489      ! always closed : we play only with the neigbours
490      !
491      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
492         ijhom = nlcj-nrecj
493         DO jl = 1, jprecj
494            t3sn(:,jl,:,1) = ptab(:,ijhom +jl,:)
495            t3ns(:,jl,:,1) = ptab(:,jprecj+jl,:)
496         END DO
497      ENDIF
498      !
499      !                           ! Migrations
500      imigr = jprecj * jpi * jpk
501      !
502      SELECT CASE ( nbondj )     
503      CASE ( -1 )
504         CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req1 )
505         CALL mpprecv( 3, t3ns(1,1,1,2), imigr, nono )
506         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
507      CASE ( 0 )
508         CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 )
509         CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req2 )
510         CALL mpprecv( 3, t3ns(1,1,1,2), imigr, nono )
511         CALL mpprecv( 4, t3sn(1,1,1,2), imigr, noso )
512         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
513         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
514      CASE ( 1 ) 
515         CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 )
516         CALL mpprecv( 4, t3sn(1,1,1,2), imigr, noso )
517         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
518      END SELECT
519      !
520      !                           ! Write Dirichlet lateral conditions
521      ijhom = nlcj-jprecj
522      !
523      SELECT CASE ( nbondj )
524      CASE ( -1 )
525         DO jl = 1, jprecj
526            ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2)
527         END DO
528      CASE ( 0 ) 
529         DO jl = 1, jprecj
530            ptab(:,jl      ,:) = t3sn(:,jl,:,2)
531            ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2)
532         END DO
533      CASE ( 1 )
534         DO jl = 1, jprecj
535            ptab(:,jl,:) = t3sn(:,jl,:,2)
536         END DO
537      END SELECT
538
539
540      ! 4. north fold treatment
541      ! -----------------------
542      !
543      IF( npolj /= 0 .AND. .NOT. PRESENT(cd_mpp) ) THEN
544         !
545         SELECT CASE ( jpni )
546         CASE ( 1 )     ;   CALL lbc_nfd      ( ptab, cd_type, psgn )   ! only 1 northern proc, no mpp
547         CASE DEFAULT   ;   CALL mpp_lbc_north( ptab, cd_type, psgn )   ! for all northern procs.
548         END SELECT
549         !
550      ENDIF
551      !
552   END SUBROUTINE mpp_lnk_3d
553
554
555   SUBROUTINE mpp_lnk_2d( pt2d, cd_type, psgn, cd_mpp, pval )
556      !!----------------------------------------------------------------------
557      !!                  ***  routine mpp_lnk_2d  ***
558      !!                 
559      !! ** Purpose :   Message passing manadgement for 2d array
560      !!
561      !! ** Method  :   Use mppsend and mpprecv function for passing mask
562      !!      between processors following neighboring subdomains.
563      !!            domain parameters
564      !!                    nlci   : first dimension of the local subdomain
565      !!                    nlcj   : second dimension of the local subdomain
566      !!                    nbondi : mark for "east-west local boundary"
567      !!                    nbondj : mark for "north-south local boundary"
568      !!                    noea   : number for local neighboring processors
569      !!                    nowe   : number for local neighboring processors
570      !!                    noso   : number for local neighboring processors
571      !!                    nono   : number for local neighboring processors
572      !!
573      !!----------------------------------------------------------------------
574      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   pt2d     ! 2D array on which the boundary condition is applied
575      CHARACTER(len=1)            , INTENT(in   ) ::   cd_type  ! define the nature of ptab array grid-points
576      !                                                         ! = T , U , V , F , W and I points
577      REAL(wp)                    , INTENT(in   ) ::   psgn     ! =-1 the sign change across the north fold boundary
578      !                                                         ! =  1. , the sign is kept
579      CHARACTER(len=3), OPTIONAL  , INTENT(in   ) ::   cd_mpp   ! fill the overlap area only
580      REAL(wp)        , OPTIONAL  , INTENT(in   ) ::   pval     ! background value (used at closed boundaries)
581      !!
582      INTEGER  ::   ji, jj, jl   ! dummy loop indices
583      INTEGER  ::   imigr, iihom, ijhom        ! temporary integers
584      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
585      REAL(wp) ::   zland
586      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
587      !!----------------------------------------------------------------------
588
589      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value
590      ELSE                         ;   zland = 0.e0      ! zero by default
591      ENDIF
592
593      ! 1. standard boundary treatment
594      ! ------------------------------
595      !
596      IF( PRESENT( cd_mpp ) ) THEN      ! only fill added line/raw with existing values
597         !
598         ! WARNING pt2d is defined only between nld and nle
599         DO jj = nlcj+1, jpj                 ! added line(s)   (inner only)
600            pt2d(nldi  :nlei  , jj          ) = pt2d(nldi:nlei,     nlej)   
601            pt2d(1     :nldi-1, jj          ) = pt2d(nldi     ,     nlej)
602            pt2d(nlei+1:nlci  , jj          ) = pt2d(     nlei,     nlej)
603         END DO
604         DO ji = nlci+1, jpi                 ! added column(s) (full)
605            pt2d(ji           ,nldj  :nlej  ) = pt2d(     nlei,nldj:nlej)
606            pt2d(ji           ,1     :nldj-1) = pt2d(     nlei,nldj     )
607            pt2d(ji           ,nlej+1:jpj   ) = pt2d(     nlei,     nlej)
608         END DO
609         !
610      ELSE                              ! standard close or cyclic treatment
611         !
612         !                                   ! East-West boundaries
613         IF( nbondi == 2 .AND.   &                ! Cyclic east-west
614            &    (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
615            pt2d( 1 ,:) = pt2d(jpim1,:)                                    ! west
616            pt2d(jpi,:) = pt2d(  2  ,:)                                    ! east
617         ELSE                                     ! closed
618            IF( .NOT. cd_type == 'F' )   pt2d(     1       :jpreci,:) = zland    ! south except F-point
619                                         pt2d(nlci-jpreci+1:jpi   ,:) = zland    ! north
620         ENDIF
621         !                                   ! North-South boundaries (always closed)
622            IF( .NOT. cd_type == 'F' )   pt2d(:,     1       :jprecj) = zland    !south except F-point
623                                         pt2d(:,nlcj-jprecj+1:jpj   ) = zland    ! north
624         !
625      ENDIF
626
627      ! 2. East and west directions exchange
628      ! ------------------------------------
629      ! we play with the neigbours AND the row number because of the periodicity
630      !
631      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
632      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
633         iihom = nlci-nreci
634         DO jl = 1, jpreci
635            t2ew(:,jl,1) = pt2d(jpreci+jl,:)
636            t2we(:,jl,1) = pt2d(iihom +jl,:)
637         END DO
638      END SELECT
639      !
640      !                           ! Migrations
641      imigr = jpreci * jpj
642      !
643      SELECT CASE ( nbondi )
644      CASE ( -1 )
645         CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req1 )
646         CALL mpprecv( 1, t2ew(1,1,2), imigr, noea )
647         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
648      CASE ( 0 )
649         CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 )
650         CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req2 )
651         CALL mpprecv( 1, t2ew(1,1,2), imigr, noea )
652         CALL mpprecv( 2, t2we(1,1,2), imigr, nowe )
653         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
654         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
655      CASE ( 1 )
656         CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 )
657         CALL mpprecv( 2, t2we(1,1,2), imigr, nowe )
658         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
659      END SELECT
660      !
661      !                           ! Write Dirichlet lateral conditions
662      iihom = nlci - jpreci
663      !
664      SELECT CASE ( nbondi )
665      CASE ( -1 )
666         DO jl = 1, jpreci
667            pt2d(iihom+jl,:) = t2ew(:,jl,2)
668         END DO
669      CASE ( 0 )
670         DO jl = 1, jpreci
671            pt2d(jl      ,:) = t2we(:,jl,2)
672            pt2d(iihom+jl,:) = t2ew(:,jl,2)
673         END DO
674      CASE ( 1 )
675         DO jl = 1, jpreci
676            pt2d(jl      ,:) = t2we(:,jl,2)
677         END DO
678      END SELECT
679
680
681      ! 3. North and south directions
682      ! -----------------------------
683      ! always closed : we play only with the neigbours
684      !
685      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
686         ijhom = nlcj-nrecj
687         DO jl = 1, jprecj
688            t2sn(:,jl,1) = pt2d(:,ijhom +jl)
689            t2ns(:,jl,1) = pt2d(:,jprecj+jl)
690         END DO
691      ENDIF
692      !
693      !                           ! Migrations
694      imigr = jprecj * jpi
695      !
696      SELECT CASE ( nbondj )
697      CASE ( -1 )
698         CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req1 )
699         CALL mpprecv( 3, t2ns(1,1,2), imigr, nono )
700         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
701      CASE ( 0 )
702         CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 )
703         CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req2 )
704         CALL mpprecv( 3, t2ns(1,1,2), imigr, nono )
705         CALL mpprecv( 4, t2sn(1,1,2), imigr, noso )
706         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
707         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
708      CASE ( 1 )
709         CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 )
710         CALL mpprecv( 4, t2sn(1,1,2), imigr, noso )
711         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
712      END SELECT
713      !
714      !                           ! Write Dirichlet lateral conditions
715      ijhom = nlcj - jprecj
716      !
717      SELECT CASE ( nbondj )
718      CASE ( -1 )
719         DO jl = 1, jprecj
720            pt2d(:,ijhom+jl) = t2ns(:,jl,2)
721         END DO
722      CASE ( 0 )
723         DO jl = 1, jprecj
724            pt2d(:,jl      ) = t2sn(:,jl,2)
725            pt2d(:,ijhom+jl) = t2ns(:,jl,2)
726         END DO
727      CASE ( 1 ) 
728         DO jl = 1, jprecj
729            pt2d(:,jl      ) = t2sn(:,jl,2)
730         END DO
731      END SELECT
732
733
734      ! 4. north fold treatment
735      ! -----------------------
736      !
737      IF( npolj /= 0 .AND. .NOT. PRESENT(cd_mpp) ) THEN
738         !
739         SELECT CASE ( jpni )
740         CASE ( 1 )     ;   CALL lbc_nfd      ( pt2d, cd_type, psgn )   ! only 1 northern proc, no mpp
741         CASE DEFAULT   ;   CALL mpp_lbc_north( pt2d, cd_type, psgn )   ! for all northern procs.
742         END SELECT
743         !
744      ENDIF
745      !
746   END SUBROUTINE mpp_lnk_2d
747
748
749   SUBROUTINE mpp_lnk_3d_gather( ptab1, cd_type1, ptab2, cd_type2, psgn )
750      !!----------------------------------------------------------------------
751      !!                  ***  routine mpp_lnk_3d_gather  ***
752      !!
753      !! ** Purpose :   Message passing manadgement for two 3D arrays
754      !!
755      !! ** Method  :   Use mppsend and mpprecv function for passing mask
756      !!      between processors following neighboring subdomains.
757      !!            domain parameters
758      !!                    nlci   : first dimension of the local subdomain
759      !!                    nlcj   : second dimension of the local subdomain
760      !!                    nbondi : mark for "east-west local boundary"
761      !!                    nbondj : mark for "north-south local boundary"
762      !!                    noea   : number for local neighboring processors
763      !!                    nowe   : number for local neighboring processors
764      !!                    noso   : number for local neighboring processors
765      !!                    nono   : number for local neighboring processors
766      !!
767      !! ** Action  :   ptab1 and ptab2  with update value at its periphery
768      !!
769      !!----------------------------------------------------------------------
770      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptab1     ! first and second 3D array on which
771      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   ptab2     ! the boundary condition is applied
772      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type1  ! nature of ptab1 and ptab2 arrays
773      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type2  ! i.e. grid-points = T , U , V , F or W points
774      REAL(wp)                        , INTENT(in   ) ::   psgn      ! =-1 the sign change across the north fold boundary
775      !!                                                             ! =  1. , the sign is kept
776      INTEGER  ::   jl   ! dummy loop indices
777      INTEGER  ::   imigr, iihom, ijhom        ! temporary integers
778      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
779      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
780      !!----------------------------------------------------------------------
781
782      ! 1. standard boundary treatment
783      ! ------------------------------
784      !                                      ! East-West boundaries
785      !                                           !* Cyclic east-west
786      IF( nbondi == 2 .AND. (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
787         ptab1( 1 ,:,:) = ptab1(jpim1,:,:)
788         ptab1(jpi,:,:) = ptab1(  2  ,:,:)
789         ptab2( 1 ,:,:) = ptab2(jpim1,:,:)
790         ptab2(jpi,:,:) = ptab2(  2  ,:,:)
791      ELSE                                        !* closed
792         IF( .NOT. cd_type1 == 'F' )   ptab1(     1       :jpreci,:,:) = 0.e0    ! south except at F-point
793         IF( .NOT. cd_type2 == 'F' )   ptab2(     1       :jpreci,:,:) = 0.e0
794                                       ptab1(nlci-jpreci+1:jpi   ,:,:) = 0.e0    ! north
795                                       ptab2(nlci-jpreci+1:jpi   ,:,:) = 0.e0
796      ENDIF
797
798     
799      !                                      ! North-South boundaries
800      IF( .NOT. cd_type1 == 'F' )   ptab1(:,     1       :jprecj,:) = 0.e0    ! south except at F-point
801      IF( .NOT. cd_type2 == 'F' )   ptab2(:,     1       :jprecj,:) = 0.e0
802                                    ptab1(:,nlcj-jprecj+1:jpj   ,:) = 0.e0    ! north
803                                    ptab2(:,nlcj-jprecj+1:jpj   ,:) = 0.e0
804
805
806      ! 2. East and west directions exchange
807      ! ------------------------------------
808      ! we play with the neigbours AND the row number because of the periodicity
809      !
810      SELECT CASE ( nbondi )      ! Read Dirichlet lateral conditions
811      CASE ( -1, 0, 1 )                ! all exept 2 (i.e. close case)
812         iihom = nlci-nreci
813         DO jl = 1, jpreci
814            t4ew(:,jl,:,1,1) = ptab1(jpreci+jl,:,:)
815            t4we(:,jl,:,1,1) = ptab1(iihom +jl,:,:)
816            t4ew(:,jl,:,2,1) = ptab2(jpreci+jl,:,:)
817            t4we(:,jl,:,2,1) = ptab2(iihom +jl,:,:)
818         END DO
819      END SELECT
820      !
821      !                           ! Migrations
822      imigr = jpreci * jpj * jpk *2
823      !
824      SELECT CASE ( nbondi ) 
825      CASE ( -1 )
826         CALL mppsend( 2, t4we(1,1,1,1,1), imigr, noea, ml_req1 )
827         CALL mpprecv( 1, t4ew(1,1,1,1,2), imigr, noea )
828         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
829      CASE ( 0 )
830         CALL mppsend( 1, t4ew(1,1,1,1,1), imigr, nowe, ml_req1 )
831         CALL mppsend( 2, t4we(1,1,1,1,1), imigr, noea, ml_req2 )
832         CALL mpprecv( 1, t4ew(1,1,1,1,2), imigr, noea )
833         CALL mpprecv( 2, t4we(1,1,1,1,2), imigr, nowe )
834         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
835         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
836      CASE ( 1 )
837         CALL mppsend( 1, t4ew(1,1,1,1,1), imigr, nowe, ml_req1 )
838         CALL mpprecv( 2, t4we(1,1,1,1,2), imigr, nowe )
839         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
840      END SELECT
841      !
842      !                           ! Write Dirichlet lateral conditions
843      iihom = nlci - jpreci
844      !
845      SELECT CASE ( nbondi )
846      CASE ( -1 )
847         DO jl = 1, jpreci
848            ptab1(iihom+jl,:,:) = t4ew(:,jl,:,1,2)
849            ptab2(iihom+jl,:,:) = t4ew(:,jl,:,2,2)
850         END DO
851      CASE ( 0 ) 
852         DO jl = 1, jpreci
853            ptab1(jl      ,:,:) = t4we(:,jl,:,1,2)
854            ptab1(iihom+jl,:,:) = t4ew(:,jl,:,1,2)
855            ptab2(jl      ,:,:) = t4we(:,jl,:,2,2)
856            ptab2(iihom+jl,:,:) = t4ew(:,jl,:,2,2)
857         END DO
858      CASE ( 1 )
859         DO jl = 1, jpreci
860            ptab1(jl      ,:,:) = t4we(:,jl,:,1,2)
861            ptab2(jl      ,:,:) = t4we(:,jl,:,2,2)
862         END DO
863      END SELECT
864
865
866      ! 3. North and south directions
867      ! -----------------------------
868      ! always closed : we play only with the neigbours
869      !
870      IF( nbondj /= 2 ) THEN      ! Read Dirichlet lateral conditions
871         ijhom = nlcj - nrecj
872         DO jl = 1, jprecj
873            t4sn(:,jl,:,1,1) = ptab1(:,ijhom +jl,:)
874            t4ns(:,jl,:,1,1) = ptab1(:,jprecj+jl,:)
875            t4sn(:,jl,:,2,1) = ptab2(:,ijhom +jl,:)
876            t4ns(:,jl,:,2,1) = ptab2(:,jprecj+jl,:)
877         END DO
878      ENDIF
879      !
880      !                           ! Migrations
881      imigr = jprecj * jpi * jpk * 2
882      !
883      SELECT CASE ( nbondj )     
884      CASE ( -1 )
885         CALL mppsend( 4, t4sn(1,1,1,1,1), imigr, nono, ml_req1 )
886         CALL mpprecv( 3, t4ns(1,1,1,1,2), imigr, nono )
887         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
888      CASE ( 0 )
889         CALL mppsend( 3, t4ns(1,1,1,1,1), imigr, noso, ml_req1 )
890         CALL mppsend( 4, t4sn(1,1,1,1,1), imigr, nono, ml_req2 )
891         CALL mpprecv( 3, t4ns(1,1,1,1,2), imigr, nono )
892         CALL mpprecv( 4, t4sn(1,1,1,1,2), imigr, noso )
893         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
894         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
895      CASE ( 1 ) 
896         CALL mppsend( 3, t4ns(1,1,1,1,1), imigr, noso, ml_req1 )
897         CALL mpprecv( 4, t4sn(1,1,1,1,2), imigr, noso )
898         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
899      END SELECT
900      !
901      !                           ! Write Dirichlet lateral conditions
902      ijhom = nlcj - jprecj
903      !
904      SELECT CASE ( nbondj )
905      CASE ( -1 )
906         DO jl = 1, jprecj
907            ptab1(:,ijhom+jl,:) = t4ns(:,jl,:,1,2)
908            ptab2(:,ijhom+jl,:) = t4ns(:,jl,:,2,2)
909         END DO
910      CASE ( 0 ) 
911         DO jl = 1, jprecj
912            ptab1(:,jl      ,:) = t4sn(:,jl,:,1,2)
913            ptab1(:,ijhom+jl,:) = t4ns(:,jl,:,1,2)
914            ptab2(:,jl      ,:) = t4sn(:,jl,:,2,2)
915            ptab2(:,ijhom+jl,:) = t4ns(:,jl,:,2,2)
916         END DO
917      CASE ( 1 )
918         DO jl = 1, jprecj
919            ptab1(:,jl,:) = t4sn(:,jl,:,1,2)
920            ptab2(:,jl,:) = t4sn(:,jl,:,2,2)
921         END DO
922      END SELECT
923
924
925      ! 4. north fold treatment
926      ! -----------------------
927      IF( npolj /= 0 ) THEN
928         !
929         SELECT CASE ( jpni )
930         CASE ( 1 )                                           
931            CALL lbc_nfd      ( ptab1, cd_type1, psgn )   ! only for northern procs.
932            CALL lbc_nfd      ( ptab2, cd_type2, psgn )
933         CASE DEFAULT
934            CALL mpp_lbc_north( ptab1, cd_type1, psgn )   ! for all northern procs.
935            CALL mpp_lbc_north (ptab2, cd_type2, psgn)
936         END SELECT 
937         !
938      ENDIF
939      !
940   END SUBROUTINE mpp_lnk_3d_gather
941
942
943   SUBROUTINE mpp_lnk_2d_e( pt2d, cd_type, psgn, jpri, jprj )
944      !!----------------------------------------------------------------------
945      !!                  ***  routine mpp_lnk_2d_e  ***
946      !!                 
947      !! ** Purpose :   Message passing manadgement for 2d array (with halo)
948      !!
949      !! ** Method  :   Use mppsend and mpprecv function for passing mask
950      !!      between processors following neighboring subdomains.
951      !!            domain parameters
952      !!                    nlci   : first dimension of the local subdomain
953      !!                    nlcj   : second dimension of the local subdomain
954      !!                    jpri   : number of rows for extra outer halo
955      !!                    jprj   : number of columns for extra outer halo
956      !!                    nbondi : mark for "east-west local boundary"
957      !!                    nbondj : mark for "north-south local boundary"
958      !!                    noea   : number for local neighboring processors
959      !!                    nowe   : number for local neighboring processors
960      !!                    noso   : number for local neighboring processors
961      !!                    nono   : number for local neighboring processors
962      !!
963      !!----------------------------------------------------------------------
964      INTEGER                                             , INTENT(in   ) ::   jpri
965      INTEGER                                             , INTENT(in   ) ::   jprj
966      REAL(wp), DIMENSION(1-jpri:jpi+jpri,1-jprj:jpj+jprj), INTENT(inout) ::   pt2d     ! 2D array with extra halo
967      CHARACTER(len=1)                                    , INTENT(in   ) ::   cd_type  ! nature of ptab array grid-points
968      !                                                                                 ! = T , U , V , F , W and I points
969      REAL(wp)                                            , INTENT(in   ) ::   psgn     ! =-1 the sign change across the
970      !!                                                                                ! north boundary, =  1. otherwise
971      INTEGER  ::   jl   ! dummy loop indices
972      INTEGER  ::   imigr, iihom, ijhom        ! temporary integers
973      INTEGER  ::   ipreci, iprecj             ! temporary integers
974      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend
975      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend
976      !!
977      REAL(wp), DIMENSION(1-jpri:jpi+jpri,jprecj+jprj,2) :: r2dns
978      REAL(wp), DIMENSION(1-jpri:jpi+jpri,jprecj+jprj,2) :: r2dsn
979      REAL(wp), DIMENSION(1-jprj:jpj+jprj,jpreci+jpri,2) :: r2dwe
980      REAL(wp), DIMENSION(1-jprj:jpj+jprj,jpreci+jpri,2) :: r2dew
981      !!----------------------------------------------------------------------
982
983      ipreci = jpreci + jpri      ! take into account outer extra 2D overlap area
984      iprecj = jprecj + jprj
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-jprj   :  jprecj  ) = 0.e0    ! south except at F-point
993                                   pt2d(:,nlcj-jprecj+1:jpj+jprj) = 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-jpri:     1    ,:) = pt2d(jpim1-jpri:  jpim1 ,:)       ! east
999         pt2d(   jpi  :jpi+jpri,:) = pt2d(     2      :2+jpri,:)       ! west
1000         !
1001      ELSE                                        !* closed
1002         IF( .NOT. cd_type == 'F' )   pt2d(  1-jpri   :jpreci    ,:) = 0.e0    ! south except at F-point
1003                                      pt2d(nlci-jpreci+1:jpi+jpri,:) = 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+jprj), cd_type, psgn, pr2dj=jprj )
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-jpri
1025         DO jl = 1, ipreci
1026            r2dew(:,jl,1) = pt2d(jpreci+jl,:)
1027            r2dwe(:,jl,1) = pt2d(iihom +jl,:)
1028         END DO
1029      END SELECT
1030      !
1031      !                           ! Migrations
1032      imigr = ipreci * ( jpj + 2*jprj)
1033      !
1034      SELECT CASE ( nbondi )
1035      CASE ( -1 )
1036         CALL mppsend( 2, r2dwe(1-jprj,1,1), imigr, noea, ml_req1 )
1037         CALL mpprecv( 1, r2dew(1-jprj,1,2), imigr, noea )
1038         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1039      CASE ( 0 )
1040         CALL mppsend( 1, r2dew(1-jprj,1,1), imigr, nowe, ml_req1 )
1041         CALL mppsend( 2, r2dwe(1-jprj,1,1), imigr, noea, ml_req2 )
1042         CALL mpprecv( 1, r2dew(1-jprj,1,2), imigr, noea )
1043         CALL mpprecv( 2, r2dwe(1-jprj,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, r2dew(1-jprj,1,1), imigr, nowe, ml_req1 )
1048         CALL mpprecv( 2, r2dwe(1-jprj,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,:) = r2dew(:,jl,2)
1059         END DO
1060      CASE ( 0 )
1061         DO jl = 1, ipreci
1062            pt2d(jl-jpri,:) = r2dwe(:,jl,2)
1063            pt2d( iihom+jl,:) = r2dew(:,jl,2)
1064         END DO
1065      CASE ( 1 )
1066         DO jl = 1, ipreci
1067            pt2d(jl-jpri,:) = r2dwe(:,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-jprj
1078         DO jl = 1, iprecj
1079            r2dsn(:,jl,1) = pt2d(:,ijhom +jl)
1080            r2dns(:,jl,1) = pt2d(:,jprecj+jl)
1081         END DO
1082      ENDIF
1083      !
1084      !                           ! Migrations
1085      imigr = iprecj * ( jpi + 2*jpri )
1086      !
1087      SELECT CASE ( nbondj )
1088      CASE ( -1 )
1089         CALL mppsend( 4, r2dsn(1-jpri,1,1), imigr, nono, ml_req1 )
1090         CALL mpprecv( 3, r2dns(1-jpri,1,2), imigr, nono )
1091         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1092      CASE ( 0 )
1093         CALL mppsend( 3, r2dns(1-jpri,1,1), imigr, noso, ml_req1 )
1094         CALL mppsend( 4, r2dsn(1-jpri,1,1), imigr, nono, ml_req2 )
1095         CALL mpprecv( 3, r2dns(1-jpri,1,2), imigr, nono )
1096         CALL mpprecv( 4, r2dsn(1-jpri,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, r2dns(1-jpri,1,1), imigr, noso, ml_req1 )
1101         CALL mpprecv( 4, r2dsn(1-jpri,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) = r2dns(:,jl,2)
1112         END DO
1113      CASE ( 0 )
1114         DO jl = 1, iprecj
1115            pt2d(:,jl-jprj) = r2dsn(:,jl,2)
1116            pt2d(:,ijhom+jl ) = r2dns(:,jl,2)
1117         END DO
1118      CASE ( 1 ) 
1119         DO jl = 1, iprecj
1120            pt2d(:,jl-jprj) = r2dsn(:,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_world = 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_world, ierr )
2030
2031      ! Create the ice group from the world group
2032      CALL MPI_GROUP_INCL( ngrp_world, 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_world,n_ice_root,ierr)
2040      !
2041      DEALLOCATE(kice, zwork)
2042      !
2043   END SUBROUTINE mpp_ini_ice
2044
2045
2046   SUBROUTINE mpp_ini_znl( kumout )
2047      !!----------------------------------------------------------------------
2048      !!               ***  routine mpp_ini_znl  ***
2049      !!
2050      !! ** Purpose :   Initialize special communicator for computing zonal sum
2051      !!
2052      !! ** Method  : - Look for processors in the same row
2053      !!              - Put their number in nrank_znl
2054      !!              - Create group for the znl processors
2055      !!              - Create a communicator for znl processors
2056      !!              - Determine if processor should write znl files
2057      !!
2058      !! ** output
2059      !!      ndim_rank_znl = number of processors on the same row
2060      !!      ngrp_znl = group ID for the znl processors
2061      !!      ncomm_znl = communicator for the ice procs.
2062      !!      n_znl_root = number (in the world) of proc 0 in the ice comm.
2063      !!
2064      !!----------------------------------------------------------------------
2065      INTEGER, INTENT(in) ::   kumout   ! ocean.output logical units
2066      !
2067      INTEGER :: jproc      ! dummy loop integer
2068      INTEGER :: ierr, ii   ! local integer
2069      INTEGER, ALLOCATABLE, DIMENSION(:) ::   kwork
2070      !!----------------------------------------------------------------------
2071      !-$$     WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - ngrp_world     : ', ngrp_world
2072      !-$$     WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - mpi_comm_world : ', mpi_comm_world
2073      !-$$     WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - mpi_comm_opa   : ', mpi_comm_opa
2074      !
2075      ALLOCATE( kwork(jpnij), STAT=ierr )
2076      IF( ierr /= 0 ) THEN
2077         WRITE(kumout, cform_err)
2078         WRITE(kumout,*) 'mpp_ini_znl : failed to allocate 1D array of length jpnij'
2079         CALL mppstop
2080      ENDIF
2081
2082      IF( jpnj == 1 ) THEN
2083         ngrp_znl  = ngrp_world
2084         ncomm_znl = mpi_comm_opa
2085      ELSE
2086         !
2087         CALL MPI_ALLGATHER ( njmpp, 1, mpi_integer, kwork, 1, mpi_integer, mpi_comm_opa, ierr )
2088         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - kwork pour njmpp : ', kwork
2089         !-$$        CALL flush(numout)
2090         !
2091         ! Count number of processors on the same row
2092         ndim_rank_znl = 0
2093         DO jproc=1,jpnij
2094            IF ( kwork(jproc) == njmpp ) THEN
2095               ndim_rank_znl = ndim_rank_znl + 1
2096            ENDIF
2097         END DO
2098         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - ndim_rank_znl : ', ndim_rank_znl
2099         !-$$        CALL flush(numout)
2100         ! Allocate the right size to nrank_znl
2101         IF (ALLOCATED (nrank_znl)) DEALLOCATE(nrank_znl)
2102         ALLOCATE(nrank_znl(ndim_rank_znl))
2103         ii = 0     
2104         nrank_znl (:) = 0
2105         DO jproc=1,jpnij
2106            IF ( kwork(jproc) == njmpp) THEN
2107               ii = ii + 1
2108               nrank_znl(ii) = jproc -1 
2109            ENDIF
2110         END DO
2111         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - nrank_znl : ', nrank_znl
2112         !-$$        CALL flush(numout)
2113
2114         ! Create the opa group
2115         CALL MPI_COMM_GROUP(mpi_comm_opa,ngrp_opa,ierr)
2116         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - ngrp_opa : ', ngrp_opa
2117         !-$$        CALL flush(numout)
2118
2119         ! Create the znl group from the opa group
2120         CALL MPI_GROUP_INCL  ( ngrp_opa, ndim_rank_znl, nrank_znl, ngrp_znl, ierr )
2121         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - ngrp_znl ', ngrp_znl
2122         !-$$        CALL flush(numout)
2123
2124         ! Create the znl communicator from the opa communicator, ie the pool of procs in the same row
2125         CALL MPI_COMM_CREATE ( mpi_comm_opa, ngrp_znl, ncomm_znl, ierr )
2126         !-$$        WRITE (numout,*) 'mpp_ini_znl ', nproc, ' - ncomm_znl ', ncomm_znl
2127         !-$$        CALL flush(numout)
2128         !
2129      END IF
2130
2131      ! Determines if processor if the first (starting from i=1) on the row
2132      IF ( jpni == 1 ) THEN
2133         l_znl_root = .TRUE.
2134      ELSE
2135         l_znl_root = .FALSE.
2136         kwork (1) = nimpp
2137         CALL mpp_min ( kwork(1), kcom = ncomm_znl)
2138         IF ( nimpp == kwork(1)) l_znl_root = .TRUE.
2139      END IF
2140
2141      DEALLOCATE(kwork)
2142
2143   END SUBROUTINE mpp_ini_znl
2144
2145
2146   SUBROUTINE mpp_ini_north
2147      !!----------------------------------------------------------------------
2148      !!               ***  routine mpp_ini_north  ***
2149      !!
2150      !! ** Purpose :   Initialize special communicator for north folding
2151      !!      condition together with global variables needed in the mpp folding
2152      !!
2153      !! ** Method  : - Look for northern processors
2154      !!              - Put their number in nrank_north
2155      !!              - Create groups for the world processors and the north processors
2156      !!              - Create a communicator for northern processors
2157      !!
2158      !! ** output
2159      !!      njmppmax = njmpp for northern procs
2160      !!      ndim_rank_north = number of processors in the northern line
2161      !!      nrank_north (ndim_rank_north) = number  of the northern procs.
2162      !!      ngrp_world = group ID for the world processors
2163      !!      ngrp_north = group ID for the northern processors
2164      !!      ncomm_north = communicator for the northern procs.
2165      !!      north_root = number (in the world) of proc 0 in the northern comm.
2166      !!
2167      !!----------------------------------------------------------------------
2168      INTEGER ::   ierr
2169      INTEGER ::   jjproc
2170      INTEGER ::   ii, ji
2171      !!----------------------------------------------------------------------
2172      !
2173      njmppmax = MAXVAL( njmppt )
2174      !
2175      ! Look for how many procs on the northern boundary
2176      ndim_rank_north = 0
2177      DO jjproc = 1, jpnij
2178         IF( njmppt(jjproc) == njmppmax )   ndim_rank_north = ndim_rank_north + 1
2179      END DO
2180      !
2181      ! Allocate the right size to nrank_north
2182      IF (ALLOCATED (nrank_north)) DEALLOCATE(nrank_north)
2183      ALLOCATE( nrank_north(ndim_rank_north) )
2184
2185      ! Fill the nrank_north array with proc. number of northern procs.
2186      ! Note : the rank start at 0 in MPI
2187      ii = 0
2188      DO ji = 1, jpnij
2189         IF ( njmppt(ji) == njmppmax   ) THEN
2190            ii=ii+1
2191            nrank_north(ii)=ji-1
2192         END IF
2193      END DO
2194      !
2195      ! create the world group
2196      CALL MPI_COMM_GROUP( mpi_comm_opa, ngrp_world, ierr )
2197      !
2198      ! Create the North group from the world group
2199      CALL MPI_GROUP_INCL( ngrp_world, ndim_rank_north, nrank_north, ngrp_north, ierr )
2200      !
2201      ! Create the North communicator , ie the pool of procs in the north group
2202      CALL MPI_COMM_CREATE( mpi_comm_opa, ngrp_north, ncomm_north, ierr )
2203      !
2204   END SUBROUTINE mpp_ini_north
2205
2206
2207   SUBROUTINE mpp_lbc_north_3d( pt3d, cd_type, psgn )
2208      !!---------------------------------------------------------------------
2209      !!                   ***  routine mpp_lbc_north_3d  ***
2210      !!
2211      !! ** Purpose :   Ensure proper north fold horizontal bondary condition
2212      !!              in mpp configuration in case of jpn1 > 1
2213      !!
2214      !! ** Method  :   North fold condition and mpp with more than one proc
2215      !!              in i-direction require a specific treatment. We gather
2216      !!              the 4 northern lines of the global domain on 1 processor
2217      !!              and apply lbc north-fold on this sub array. Then we
2218      !!              scatter the north fold array back to the processors.
2219      !!
2220      !!----------------------------------------------------------------------
2221      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) ::   pt3d      ! 3D array on which the b.c. is applied
2222      CHARACTER(len=1)                , INTENT(in   ) ::   cd_type   ! nature of pt3d grid-points
2223      !                                                              !   = T ,  U , V , F or W  gridpoints
2224      REAL(wp)                        , INTENT(in   ) ::   psgn      ! = -1. the sign change across the north fold
2225      !!                                                             ! =  1. , the sign is kept
2226      INTEGER ::   ji, jj, jr
2227      INTEGER ::   ierr, itaille, ildi, ilei, iilb
2228      INTEGER ::   ijpj, ijpjm1, ij, iproc
2229      INTEGER, DIMENSION (jpmaxngh)          ::   ml_req_nf          ! for mpi_isend when avoiding mpi_allgather
2230      INTEGER                                ::   ml_err             ! for mpi_isend when avoiding mpi_allgather
2231      INTEGER, DIMENSION(MPI_STATUS_SIZE)    ::   ml_stat            ! for mpi_isend when avoiding mpi_allgather
2232      !!----------------------------------------------------------------------
2233      !   
2234      ijpj   = 4
2235      ityp = -1
2236      ijpjm1 = 3
2237      ztab(:,:,:) = 0.e0
2238      !
2239      DO jj = nlcj - ijpj +1, nlcj          ! put in znorthloc the last 4 jlines of pt3d
2240         ij = jj - nlcj + ijpj
2241         znorthloc(:,ij,:) = pt3d(:,jj,:)
2242      END DO
2243      !
2244      !                                     ! Build in procs of ncomm_north the znorthgloio
2245      itaille = jpi * jpk * ijpj
2246      IF ( l_north_nogather ) THEN
2247         !
2248         ! Avoid the use of mpi_allgather by exchanging only with the processes already identified
2249         ! (in nemo_northcomms) as being  involved in this process' northern boundary exchange
2250         !
2251         DO jj = nlcj-ijpj+1, nlcj          ! First put local values into the global array
2252            ij = jj - nlcj + ijpj
2253            DO ji = 1, nlci
2254               ztab(ji+nimpp-1,ij,:) = pt3d(ji,jj,:)
2255            END DO
2256         END DO
2257
2258         !
2259         ! Set the exchange type in order to access the correct list of active neighbours
2260         !
2261         SELECT CASE ( cd_type )
2262            CASE ( 'T' , 'W' )
2263               ityp = 1
2264            CASE ( 'U' )
2265               ityp = 2
2266            CASE ( 'V' )
2267               ityp = 3
2268            CASE ( 'F' )
2269               ityp = 4
2270            CASE ( 'I' )
2271               ityp = 5
2272            CASE DEFAULT
2273               ityp = -1                    ! Set a default value for unsupported types which
2274                                            ! will cause a fallback to the mpi_allgather method
2275         END SELECT
2276         IF ( ityp .gt. 0 ) THEN
2277
2278            DO jr = 1,nsndto(ityp)
2279               CALL mppsend(5, znorthloc, itaille, isendto(jr,ityp), ml_req_nf(jr) )
2280            END DO
2281            DO jr = 1,nsndto(ityp)
2282               CALL mpprecv(5, zfoldwk, itaille, isendto(jr,ityp))
2283               iproc = isendto(jr,ityp) + 1
2284               ildi = nldit (iproc)
2285               ilei = nleit (iproc)
2286               iilb = nimppt(iproc)
2287               DO jj = 1, ijpj
2288                  DO ji = ildi, ilei
2289                     ztab(ji+iilb-1,jj,:) = zfoldwk(ji,jj,:)
2290                  END DO
2291               END DO
2292            END DO
2293            IF (l_isend) THEN
2294               DO jr = 1,nsndto(ityp)
2295                  CALL mpi_wait(ml_req_nf(jr), ml_stat, ml_err)
2296               END DO
2297            ENDIF
2298
2299         ENDIF
2300
2301      ENDIF
2302
2303      IF ( ityp .lt. 0 ) THEN
2304         CALL MPI_ALLGATHER( znorthloc  , itaille, MPI_DOUBLE_PRECISION,                &
2305            &                znorthgloio, itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr )
2306         !
2307         DO jr = 1, ndim_rank_north         ! recover the global north array
2308            iproc = nrank_north(jr) + 1
2309            ildi  = nldit (iproc)
2310            ilei  = nleit (iproc)
2311            iilb  = nimppt(iproc)
2312            DO jj = 1, ijpj
2313               DO ji = ildi, ilei
2314                  ztab(ji+iilb-1,jj,:) = znorthgloio(ji,jj,:,jr)
2315               END DO
2316            END DO
2317         END DO
2318      ENDIF
2319      !
2320      ! The ztab array has been either:
2321      !  a. Fully populated by the mpi_allgather operation or
2322      !  b. Had the active points for this domain and northern neighbours populated
2323      !     by peer to peer exchanges
2324      ! Either way the array may be folded by lbc_nfd and the result for the span of
2325      ! this domain will be identical.
2326      !
2327      CALL lbc_nfd( ztab, cd_type, psgn )   ! North fold boundary condition
2328      !
2329      DO jj = nlcj-ijpj+1, nlcj             ! Scatter back to pt3d
2330         ij = jj - nlcj + ijpj
2331         DO ji= 1, nlci
2332            pt3d(ji,jj,:) = ztab(ji+nimpp-1,ij,:)
2333         END DO
2334      END DO
2335      !
2336   END SUBROUTINE mpp_lbc_north_3d
2337
2338
2339   SUBROUTINE mpp_lbc_north_2d( pt2d, cd_type, psgn)
2340      !!---------------------------------------------------------------------
2341      !!                   ***  routine mpp_lbc_north_2d  ***
2342      !!
2343      !! ** Purpose :   Ensure proper north fold horizontal bondary condition
2344      !!              in mpp configuration in case of jpn1 > 1 (for 2d array )
2345      !!
2346      !! ** Method  :   North fold condition and mpp with more than one proc
2347      !!              in i-direction require a specific treatment. We gather
2348      !!              the 4 northern lines of the global domain on 1 processor
2349      !!              and apply lbc north-fold on this sub array. Then we
2350      !!              scatter the north fold array back to the processors.
2351      !!
2352      !!----------------------------------------------------------------------
2353      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   pt2d      ! 3D array on which the b.c. is applied
2354      CHARACTER(len=1)            , INTENT(in   ) ::   cd_type   ! nature of pt3d grid-points
2355      !                                                          !   = T ,  U , V , F or W  gridpoints
2356      REAL(wp)                    , INTENT(in   ) ::   psgn      ! = -1. the sign change across the north fold
2357      !!                                                             ! =  1. , the sign is kept
2358      INTEGER ::   ji, jj, jr
2359      INTEGER ::   ierr, itaille, ildi, ilei, iilb
2360      INTEGER ::   ijpj, ijpjm1, ij, iproc
2361      INTEGER, DIMENSION (jpmaxngh)      ::   ml_req_nf          ! for mpi_isend when avoiding mpi_allgather
2362      INTEGER                            ::   ml_err             ! for mpi_isend when avoiding mpi_allgather
2363      INTEGER, DIMENSION(MPI_STATUS_SIZE)::   ml_stat            ! for mpi_isend when avoiding mpi_allgather
2364      !!----------------------------------------------------------------------
2365      !
2366      ijpj   = 4
2367      ityp = -1
2368      ijpjm1 = 3
2369      ztab_2d(:,:) = 0.e0
2370      !
2371      DO jj = nlcj-ijpj+1, nlcj             ! put in znorthloc_2d the last 4 jlines of pt2d
2372         ij = jj - nlcj + ijpj
2373         znorthloc_2d(:,ij) = pt2d(:,jj)
2374      END DO
2375
2376      !                                     ! Build in procs of ncomm_north the znorthgloio_2d
2377      itaille = jpi * ijpj
2378      IF ( l_north_nogather ) THEN
2379         !
2380         ! Avoid the use of mpi_allgather by exchanging only with the processes already identified
2381         ! (in nemo_northcomms) as being  involved in this process' northern boundary exchange
2382         !
2383         DO jj = nlcj-ijpj+1, nlcj          ! First put local values into the global array
2384            ij = jj - nlcj + ijpj
2385            DO ji = 1, nlci
2386               ztab_2d(ji+nimpp-1,ij) = pt2d(ji,jj)
2387            END DO
2388         END DO
2389
2390         !
2391         ! Set the exchange type in order to access the correct list of active neighbours
2392         !
2393         SELECT CASE ( cd_type )
2394            CASE ( 'T' , 'W' )
2395               ityp = 1
2396            CASE ( 'U' )
2397               ityp = 2
2398            CASE ( 'V' )
2399               ityp = 3
2400            CASE ( 'F' )
2401               ityp = 4
2402            CASE ( 'I' )
2403               ityp = 5
2404            CASE DEFAULT
2405               ityp = -1                    ! Set a default value for unsupported types which
2406                                            ! will cause a fallback to the mpi_allgather method
2407         END SELECT
2408
2409         IF ( ityp .gt. 0 ) THEN
2410
2411            DO jr = 1,nsndto(ityp)
2412               CALL mppsend(5, znorthloc_2d, itaille, isendto(jr,ityp), ml_req_nf(jr) )
2413            END DO
2414            DO jr = 1,nsndto(ityp)
2415               CALL mpprecv(5, zfoldwk_2d, itaille, isendto(jr,ityp))
2416               iproc = isendto(jr,ityp) + 1
2417               ildi = nldit (iproc)
2418               ilei = nleit (iproc)
2419               iilb = nimppt(iproc)
2420               DO jj = 1, ijpj
2421                  DO ji = ildi, ilei
2422                     ztab_2d(ji+iilb-1,jj) = zfoldwk_2d(ji,jj)
2423                  END DO
2424               END DO
2425            END DO
2426            IF (l_isend) THEN
2427               DO jr = 1,nsndto(ityp)
2428                  CALL mpi_wait(ml_req_nf(jr), ml_stat, ml_err)
2429               END DO
2430            ENDIF
2431
2432         ENDIF
2433
2434      ENDIF
2435
2436      IF ( ityp .lt. 0 ) THEN
2437         CALL MPI_ALLGATHER( znorthloc_2d  , itaille, MPI_DOUBLE_PRECISION,        &
2438            &                znorthgloio_2d, itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr )
2439         !
2440         DO jr = 1, ndim_rank_north            ! recover the global north array
2441            iproc = nrank_north(jr) + 1
2442            ildi = nldit (iproc)
2443            ilei = nleit (iproc)
2444            iilb = nimppt(iproc)
2445            DO jj = 1, ijpj
2446               DO ji = ildi, ilei
2447                  ztab_2d(ji+iilb-1,jj) = znorthgloio_2d(ji,jj,jr)
2448               END DO
2449            END DO
2450         END DO
2451      ENDIF
2452      !
2453      ! The ztab array has been either:
2454      !  a. Fully populated by the mpi_allgather operation or
2455      !  b. Had the active points for this domain and northern neighbours populated
2456      !     by peer to peer exchanges
2457      ! Either way the array may be folded by lbc_nfd and the result for the span of
2458      ! this domain will be identical.
2459      !
2460      CALL lbc_nfd( ztab_2d, cd_type, psgn )   ! North fold boundary condition
2461      !
2462      !
2463      DO jj = nlcj-ijpj+1, nlcj             ! Scatter back to pt2d
2464         ij = jj - nlcj + ijpj
2465         DO ji = 1, nlci
2466            pt2d(ji,jj) = ztab_2d(ji+nimpp-1,ij)
2467         END DO
2468      END DO
2469      !
2470   END SUBROUTINE mpp_lbc_north_2d
2471
2472
2473   SUBROUTINE mpp_lbc_north_e( pt2d, cd_type, psgn)
2474      !!---------------------------------------------------------------------
2475      !!                   ***  routine mpp_lbc_north_2d  ***
2476      !!
2477      !! ** Purpose :   Ensure proper north fold horizontal bondary condition
2478      !!              in mpp configuration in case of jpn1 > 1 and for 2d
2479      !!              array with outer extra halo
2480      !!
2481      !! ** Method  :   North fold condition and mpp with more than one proc
2482      !!              in i-direction require a specific treatment. We gather
2483      !!              the 4+2*jpr2dj northern lines of the global domain on 1
2484      !!              processor and apply lbc north-fold on this sub array.
2485      !!              Then we scatter the north fold array back to the processors.
2486      !!
2487      !!----------------------------------------------------------------------
2488      REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj), INTENT(inout) ::   pt2d     ! 2D array with extra halo
2489      CHARACTER(len=1)                                            , INTENT(in   ) ::   cd_type  ! nature of pt3d grid-points
2490      !                                                                                         !   = T ,  U , V , F or W -points
2491      REAL(wp)                                                    , INTENT(in   ) ::   psgn     ! = -1. the sign change across the 
2492      !!                                                                                        ! north fold, =  1. otherwise
2493      INTEGER ::   ji, jj, jr
2494      INTEGER ::   ierr, itaille, ildi, ilei, iilb
2495      INTEGER ::   ijpj, ij, iproc
2496      !!----------------------------------------------------------------------
2497      !
2498      ijpj=4
2499      ztab_e(:,:) = 0.e0
2500
2501      ij=0
2502      ! put in znorthloc_e the last 4 jlines of pt2d
2503      DO jj = nlcj - ijpj + 1 - jpr2dj, nlcj +jpr2dj
2504         ij = ij + 1
2505         DO ji = 1, jpi
2506            znorthloc_e(ji,ij)=pt2d(ji,jj)
2507         END DO
2508      END DO
2509      !
2510      itaille = jpi * ( ijpj + 2 * jpr2dj )
2511      CALL MPI_ALLGATHER( znorthloc_e(1,1)  , itaille, MPI_DOUBLE_PRECISION,    &
2512         &                znorthgloio_e(1,1,1), itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr )
2513      !
2514      DO jr = 1, ndim_rank_north            ! recover the global north array
2515         iproc = nrank_north(jr) + 1
2516         ildi = nldit (iproc)
2517         ilei = nleit (iproc)
2518         iilb = nimppt(iproc)
2519         DO jj = 1, ijpj+2*jpr2dj
2520            DO ji = ildi, ilei
2521               ztab_e(ji+iilb-1,jj) = znorthgloio_e(ji,jj,jr)
2522            END DO
2523         END DO
2524      END DO
2525
2526
2527      ! 2. North-Fold boundary conditions
2528      ! ----------------------------------
2529      CALL lbc_nfd( ztab_e(:,:), cd_type, psgn, pr2dj = jpr2dj )
2530
2531      ij = jpr2dj
2532      !! Scatter back to pt2d
2533      DO jj = nlcj - ijpj + 1 , nlcj +jpr2dj
2534      ij  = ij +1 
2535         DO ji= 1, nlci
2536            pt2d(ji,jj) = ztab_e(ji+nimpp-1,ij)
2537         END DO
2538      END DO
2539      !
2540   END SUBROUTINE mpp_lbc_north_e
2541
2542
2543   SUBROUTINE mpi_init_opa( ldtxt, ksft, code )
2544      !!---------------------------------------------------------------------
2545      !!                   ***  routine mpp_init.opa  ***
2546      !!
2547      !! ** Purpose :: export and attach a MPI buffer for bsend
2548      !!
2549      !! ** Method  :: define buffer size in namelist, if 0 no buffer attachment
2550      !!            but classical mpi_init
2551      !!
2552      !! History :: 01/11 :: IDRIS initial version for IBM only 
2553      !!            08/04 :: R. Benshila, generalisation
2554      !!---------------------------------------------------------------------
2555      CHARACTER(len=*),DIMENSION(:), INTENT(  out) ::   ldtxt 
2556      INTEGER                      , INTENT(inout) ::   ksft
2557      INTEGER                      , INTENT(  out) ::   code
2558      INTEGER                                      ::   ierr, ji
2559      LOGICAL                                      ::   mpi_was_called
2560      !!---------------------------------------------------------------------
2561      !
2562      CALL mpi_initialized( mpi_was_called, code )      ! MPI initialization
2563      IF ( code /= MPI_SUCCESS ) THEN
2564         DO ji = 1, SIZE(ldtxt) 
2565            IF( TRIM(ldtxt(ji)) /= '' )   WRITE(*,*) ldtxt(ji)      ! control print of mynode
2566         END DO         
2567         WRITE(*, cform_err)
2568         WRITE(*, *) ' lib_mpp: Error in routine mpi_initialized'
2569         CALL mpi_abort( mpi_comm_world, code, ierr )
2570      ENDIF
2571      !
2572      IF( .NOT. mpi_was_called ) THEN
2573         CALL mpi_init( code )
2574         CALL mpi_comm_dup( mpi_comm_world, mpi_comm_opa, code )
2575         IF ( code /= MPI_SUCCESS ) THEN
2576            DO ji = 1, SIZE(ldtxt) 
2577               IF( TRIM(ldtxt(ji)) /= '' )   WRITE(*,*) ldtxt(ji)      ! control print of mynode
2578            END DO
2579            WRITE(*, cform_err)
2580            WRITE(*, *) ' lib_mpp: Error in routine mpi_comm_dup'
2581            CALL mpi_abort( mpi_comm_world, code, ierr )
2582         ENDIF
2583      ENDIF
2584      !
2585      IF( nn_buffer > 0 ) THEN
2586         WRITE(ldtxt(ksft),*) 'mpi_bsend, buffer allocation of  : ', nn_buffer   ;   ksft = ksft + 1
2587         ! Buffer allocation and attachment
2588         ALLOCATE( tampon(nn_buffer), stat = ierr )
2589         IF( ierr /= 0 ) THEN
2590            DO ji = 1, SIZE(ldtxt) 
2591               IF( TRIM(ldtxt(ji)) /= '' )   WRITE(*,*) ldtxt(ji)      ! control print of mynode
2592            END DO
2593            WRITE(*, cform_err)
2594            WRITE(*, *) ' lib_mpp: Error in ALLOCATE', ierr
2595            CALL mpi_abort( mpi_comm_world, code, ierr )
2596         END IF
2597         CALL mpi_buffer_attach( tampon, nn_buffer, code )
2598      ENDIF
2599      !
2600   END SUBROUTINE mpi_init_opa
2601
2602#if defined key_mpp_rep
2603   SUBROUTINE DDPDD_MPI (ydda, yddb, ilen, itype)
2604      !!---------------------------------------------------------------------
2605      !!   Routine DDPDD_MPI: used by reduction operator MPI_SUMDD
2606      !!
2607      !!   Modification of original codes written by David H. Bailey
2608      !!   This subroutine computes yddb(i) = ydda(i)+yddb(i)
2609      !!---------------------------------------------------------------------
2610      INTEGER, INTENT(in)                         :: ilen, itype
2611      COMPLEX(wp), DIMENSION(ilen), INTENT(in)     :: ydda
2612      COMPLEX(wp), DIMENSION(ilen), INTENT(inout)  :: yddb
2613      !
2614      REAL(wp) :: zerr, zt1, zt2    ! local work variables
2615      INTEGER :: ji, ztmp           ! local scalar
2616
2617      ztmp = itype   ! avoid compilation warning
2618
2619      DO ji=1,ilen
2620      ! Compute ydda + yddb using Knuth's trick.
2621         zt1  = real(ydda(ji)) + real(yddb(ji))
2622         zerr = zt1 - real(ydda(ji))
2623         zt2  = ((real(yddb(ji)) - zerr) + (real(ydda(ji)) - (zt1 - zerr))) &
2624                + aimag(ydda(ji)) + aimag(yddb(ji))
2625
2626         ! The result is zt1 + zt2, after normalization.
2627         yddb(ji) = cmplx ( zt1 + zt2, zt2 - ((zt1 + zt2) - zt1),wp )
2628      END DO
2629
2630   END SUBROUTINE DDPDD_MPI
2631#endif
2632
2633#else
2634   !!----------------------------------------------------------------------
2635   !!   Default case:            Dummy module        share memory computing
2636   !!----------------------------------------------------------------------
2637   USE in_out_manager
2638
2639   INTERFACE mpp_sum
2640      MODULE PROCEDURE mpp_sum_a2s, mpp_sum_as, mpp_sum_ai, mpp_sum_s, mpp_sum_i, mppsum_realdd, mppsum_a_realdd
2641   END INTERFACE
2642   INTERFACE mpp_max
2643      MODULE PROCEDURE mppmax_a_int, mppmax_int, mppmax_a_real, mppmax_real
2644   END INTERFACE
2645   INTERFACE mpp_min
2646      MODULE PROCEDURE mppmin_a_int, mppmin_int, mppmin_a_real, mppmin_real
2647   END INTERFACE
2648   INTERFACE mppobc
2649      MODULE PROCEDURE mppobc_1d, mppobc_2d, mppobc_3d, mppobc_4d
2650   END INTERFACE
2651   INTERFACE mpp_minloc
2652      MODULE PROCEDURE mpp_minloc2d ,mpp_minloc3d
2653   END INTERFACE
2654   INTERFACE mpp_maxloc
2655      MODULE PROCEDURE mpp_maxloc2d ,mpp_maxloc3d
2656   END INTERFACE
2657
2658   LOGICAL, PUBLIC, PARAMETER ::   lk_mpp = .FALSE.      !: mpp flag
2659   LOGICAL, PUBLIC            ::   ln_nnogather  = .FALSE.  !: namelist control of northfold comms (needed here in case "key_mpp_mpi" is not used)
2660   INTEGER :: ncomm_ice
2661   !!----------------------------------------------------------------------
2662CONTAINS
2663
2664   INTEGER FUNCTION lib_mpp_alloc(kumout)          ! Dummy function
2665      INTEGER, INTENT(in) ::   kumout
2666      lib_mpp_alloc = 0
2667   END FUNCTION lib_mpp_alloc
2668
2669   FUNCTION mynode( ldtxt, kumnam, kstop, localComm ) RESULT (function_value)
2670      INTEGER, OPTIONAL            , INTENT(in   ) ::   localComm
2671      CHARACTER(len=*),DIMENSION(:) ::   ldtxt 
2672      INTEGER ::   kumnam, kstop
2673      IF( PRESENT( localComm ) .OR. .NOT.PRESENT( localComm ) )   function_value = 0
2674      IF( .FALSE. )   ldtxt(:) = 'never done'
2675   END FUNCTION mynode
2676
2677   SUBROUTINE mppsync                       ! Dummy routine
2678   END SUBROUTINE mppsync
2679
2680   SUBROUTINE mpp_sum_as( parr, kdim, kcom )      ! Dummy routine
2681      REAL   , DIMENSION(:) :: parr
2682      INTEGER               :: kdim
2683      INTEGER, OPTIONAL     :: kcom 
2684      WRITE(*,*) 'mpp_sum_as: You should not have seen this print! error?', kdim, parr(1), kcom
2685   END SUBROUTINE mpp_sum_as
2686
2687   SUBROUTINE mpp_sum_a2s( parr, kdim, kcom )      ! Dummy routine
2688      REAL   , DIMENSION(:,:) :: parr
2689      INTEGER               :: kdim
2690      INTEGER, OPTIONAL     :: kcom 
2691      WRITE(*,*) 'mpp_sum_a2s: You should not have seen this print! error?', kdim, parr(1,1), kcom
2692   END SUBROUTINE mpp_sum_a2s
2693
2694   SUBROUTINE mpp_sum_ai( karr, kdim, kcom )      ! Dummy routine
2695      INTEGER, DIMENSION(:) :: karr
2696      INTEGER               :: kdim
2697      INTEGER, OPTIONAL     :: kcom 
2698      WRITE(*,*) 'mpp_sum_ai: You should not have seen this print! error?', kdim, karr(1), kcom
2699   END SUBROUTINE mpp_sum_ai
2700
2701   SUBROUTINE mpp_sum_s( psca, kcom )            ! Dummy routine
2702      REAL                  :: psca
2703      INTEGER, OPTIONAL     :: kcom 
2704      WRITE(*,*) 'mpp_sum_s: You should not have seen this print! error?', psca, kcom
2705   END SUBROUTINE mpp_sum_s
2706
2707   SUBROUTINE mpp_sum_i( kint, kcom )            ! Dummy routine
2708      integer               :: kint
2709      INTEGER, OPTIONAL     :: kcom 
2710      WRITE(*,*) 'mpp_sum_i: You should not have seen this print! error?', kint, kcom
2711   END SUBROUTINE mpp_sum_i
2712
2713   SUBROUTINE mppsum_realdd( ytab, kcom )
2714      COMPLEX(wp), INTENT(inout)         :: ytab    ! input scalar
2715      INTEGER , INTENT( in  ), OPTIONAL :: kcom
2716      WRITE(*,*) 'mppsum_realdd: You should not have seen this print! error?', ytab
2717   END SUBROUTINE mppsum_realdd
2718 
2719   SUBROUTINE mppsum_a_realdd( ytab, kdim, kcom )
2720      INTEGER , INTENT( in )                        ::   kdim      ! size of ytab
2721      COMPLEX(wp), DIMENSION(kdim), INTENT( inout ) ::   ytab      ! input array
2722      INTEGER , INTENT( in  ), OPTIONAL :: kcom
2723      WRITE(*,*) 'mppsum_a_realdd: You should not have seen this print! error?', kdim, ytab(1), kcom
2724   END SUBROUTINE mppsum_a_realdd
2725
2726   SUBROUTINE mppmax_a_real( parr, kdim, kcom )
2727      REAL   , DIMENSION(:) :: parr
2728      INTEGER               :: kdim
2729      INTEGER, OPTIONAL     :: kcom 
2730      WRITE(*,*) 'mppmax_a_real: You should not have seen this print! error?', kdim, parr(1), kcom
2731   END SUBROUTINE mppmax_a_real
2732
2733   SUBROUTINE mppmax_real( psca, kcom )
2734      REAL                  :: psca
2735      INTEGER, OPTIONAL     :: kcom 
2736      WRITE(*,*) 'mppmax_real: You should not have seen this print! error?', psca, kcom
2737   END SUBROUTINE mppmax_real
2738
2739   SUBROUTINE mppmin_a_real( parr, kdim, kcom )
2740      REAL   , DIMENSION(:) :: parr
2741      INTEGER               :: kdim
2742      INTEGER, OPTIONAL     :: kcom 
2743      WRITE(*,*) 'mppmin_a_real: You should not have seen this print! error?', kdim, parr(1), kcom
2744   END SUBROUTINE mppmin_a_real
2745
2746   SUBROUTINE mppmin_real( psca, kcom )
2747      REAL                  :: psca
2748      INTEGER, OPTIONAL     :: kcom 
2749      WRITE(*,*) 'mppmin_real: You should not have seen this print! error?', psca, kcom
2750   END SUBROUTINE mppmin_real
2751
2752   SUBROUTINE mppmax_a_int( karr, kdim ,kcom)
2753      INTEGER, DIMENSION(:) :: karr
2754      INTEGER               :: kdim
2755      INTEGER, OPTIONAL     :: kcom 
2756      WRITE(*,*) 'mppmax_a_int: You should not have seen this print! error?', kdim, karr(1), kcom
2757   END SUBROUTINE mppmax_a_int
2758
2759   SUBROUTINE mppmax_int( kint, kcom)
2760      INTEGER               :: kint
2761      INTEGER, OPTIONAL     :: kcom 
2762      WRITE(*,*) 'mppmax_int: You should not have seen this print! error?', kint, kcom
2763   END SUBROUTINE mppmax_int
2764
2765   SUBROUTINE mppmin_a_int( karr, kdim, kcom )
2766      INTEGER, DIMENSION(:) :: karr
2767      INTEGER               :: kdim
2768      INTEGER, OPTIONAL     :: kcom 
2769      WRITE(*,*) 'mppmin_a_int: You should not have seen this print! error?', kdim, karr(1), kcom
2770   END SUBROUTINE mppmin_a_int
2771
2772   SUBROUTINE mppmin_int( kint, kcom )
2773      INTEGER               :: kint
2774      INTEGER, OPTIONAL     :: kcom 
2775      WRITE(*,*) 'mppmin_int: You should not have seen this print! error?', kint, kcom
2776   END SUBROUTINE mppmin_int
2777
2778   SUBROUTINE mppobc_1d( parr, kd1, kd2, kl, kk, ktype, kij, knum )
2779      INTEGER  ::   kd1, kd2, kl , kk, ktype, kij, knum
2780      REAL, DIMENSION(:) ::   parr           ! variable array
2781      WRITE(*,*) 'mppobc: You should not have seen this print! error?', parr(1), kd1, kd2, kl, kk, ktype, kij, knum
2782   END SUBROUTINE mppobc_1d
2783
2784   SUBROUTINE mppobc_2d( parr, kd1, kd2, kl, kk, ktype, kij, knum )
2785      INTEGER  ::   kd1, kd2, kl , kk, ktype, kij, knum
2786      REAL, DIMENSION(:,:) ::   parr           ! variable array
2787      WRITE(*,*) 'mppobc: You should not have seen this print! error?', parr(1,1), kd1, kd2, kl, kk, ktype, kij, knum
2788   END SUBROUTINE mppobc_2d
2789
2790   SUBROUTINE mppobc_3d( parr, kd1, kd2, kl, kk, ktype, kij, knum )
2791      INTEGER  ::   kd1, kd2, kl , kk, ktype, kij, knum
2792      REAL, DIMENSION(:,:,:) ::   parr           ! variable array
2793      WRITE(*,*) 'mppobc: You should not have seen this print! error?', parr(1,1,1), kd1, kd2, kl, kk, ktype, kij, knum
2794   END SUBROUTINE mppobc_3d
2795
2796   SUBROUTINE mppobc_4d( parr, kd1, kd2, kl, kk, ktype, kij, knum )
2797      INTEGER  ::   kd1, kd2, kl , kk, ktype, kij, knum
2798      REAL, DIMENSION(:,:,:,:) ::   parr           ! variable array
2799      WRITE(*,*) 'mppobc: You should not have seen this print! error?', parr(1,1,1,1), kd1, kd2, kl, kk, ktype, kij, knum
2800   END SUBROUTINE mppobc_4d
2801
2802   SUBROUTINE mpp_minloc2d( ptab, pmask, pmin, ki, kj )
2803      REAL                   :: pmin
2804      REAL , DIMENSION (:,:) :: ptab, pmask
2805      INTEGER :: ki, kj
2806      WRITE(*,*) 'mpp_minloc2d: You should not have seen this print! error?', pmin, ki, kj, ptab(1,1), pmask(1,1)
2807   END SUBROUTINE mpp_minloc2d
2808
2809   SUBROUTINE mpp_minloc3d( ptab, pmask, pmin, ki, kj, kk )
2810      REAL                     :: pmin
2811      REAL , DIMENSION (:,:,:) :: ptab, pmask
2812      INTEGER :: ki, kj, kk
2813      WRITE(*,*) 'mpp_minloc3d: You should not have seen this print! error?', pmin, ki, kj, kk, ptab(1,1,1), pmask(1,1,1)
2814   END SUBROUTINE mpp_minloc3d
2815
2816   SUBROUTINE mpp_maxloc2d( ptab, pmask, pmax, ki, kj )
2817      REAL                   :: pmax
2818      REAL , DIMENSION (:,:) :: ptab, pmask
2819      INTEGER :: ki, kj
2820      WRITE(*,*) 'mpp_maxloc2d: You should not have seen this print! error?', pmax, ki, kj, ptab(1,1), pmask(1,1)
2821   END SUBROUTINE mpp_maxloc2d
2822
2823   SUBROUTINE mpp_maxloc3d( ptab, pmask, pmax, ki, kj, kk )
2824      REAL                     :: pmax
2825      REAL , DIMENSION (:,:,:) :: ptab, pmask
2826      INTEGER :: ki, kj, kk
2827      WRITE(*,*) 'mpp_maxloc3d: You should not have seen this print! error?', pmax, ki, kj, kk, ptab(1,1,1), pmask(1,1,1)
2828   END SUBROUTINE mpp_maxloc3d
2829
2830   SUBROUTINE mppstop
2831      WRITE(*,*) 'mppstop: You should not have seen this print if running in mpp mode! error?...'
2832      WRITE(*,*) 'mppstop: ..otherwise this is a stop condition raised by ctl_stop in single processor mode'
2833      STOP
2834   END SUBROUTINE mppstop
2835
2836   SUBROUTINE mpp_ini_ice( kcom, knum )
2837      INTEGER :: kcom, knum
2838      WRITE(*,*) 'mpp_ini_ice: You should not have seen this print! error?', kcom, knum
2839   END SUBROUTINE mpp_ini_ice
2840
2841   SUBROUTINE mpp_ini_znl( knum )
2842      INTEGER :: knum
2843      WRITE(*,*) 'mpp_ini_znl: You should not have seen this print! error?', knum
2844   END SUBROUTINE mpp_ini_znl
2845
2846   SUBROUTINE mpp_comm_free( kcom )
2847      INTEGER :: kcom
2848      WRITE(*,*) 'mpp_comm_free: You should not have seen this print! error?', kcom
2849   END SUBROUTINE mpp_comm_free
2850#endif
2851
2852   !!----------------------------------------------------------------------
2853   !!   All cases:         ctl_stop, ctl_warn, get_unit, ctl_opn   routines
2854   !!----------------------------------------------------------------------
2855
2856   SUBROUTINE ctl_stop( cd1, cd2, cd3, cd4, cd5 ,   &
2857      &                 cd6, cd7, cd8, cd9, cd10 )
2858      !!----------------------------------------------------------------------
2859      !!                  ***  ROUTINE  stop_opa  ***
2860      !!
2861      !! ** Purpose :   print in ocean.outpput file a error message and
2862      !!                increment the error number (nstop) by one.
2863      !!----------------------------------------------------------------------
2864      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd1, cd2, cd3, cd4, cd5
2865      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd6, cd7, cd8, cd9, cd10
2866      !!----------------------------------------------------------------------
2867      !
2868      nstop = nstop + 1 
2869      IF(lwp) THEN
2870         WRITE(numout,cform_err)
2871         IF( PRESENT(cd1 ) )   WRITE(numout,*) cd1
2872         IF( PRESENT(cd2 ) )   WRITE(numout,*) cd2
2873         IF( PRESENT(cd3 ) )   WRITE(numout,*) cd3
2874         IF( PRESENT(cd4 ) )   WRITE(numout,*) cd4
2875         IF( PRESENT(cd5 ) )   WRITE(numout,*) cd5
2876         IF( PRESENT(cd6 ) )   WRITE(numout,*) cd6
2877         IF( PRESENT(cd7 ) )   WRITE(numout,*) cd7
2878         IF( PRESENT(cd8 ) )   WRITE(numout,*) cd8
2879         IF( PRESENT(cd9 ) )   WRITE(numout,*) cd9
2880         IF( PRESENT(cd10) )   WRITE(numout,*) cd10
2881      ENDIF
2882                               CALL FLUSH(numout    )
2883      IF( numstp     /= -1 )   CALL FLUSH(numstp    )
2884      IF( numsol     /= -1 )   CALL FLUSH(numsol    )
2885      IF( numevo_ice /= -1 )   CALL FLUSH(numevo_ice)
2886      !
2887      IF( cd1 == 'STOP' ) THEN
2888         IF(lwp) WRITE(numout,*)  'huge E-R-R-O-R : immediate stop'
2889         CALL mppstop()
2890      ENDIF
2891      !
2892   END SUBROUTINE ctl_stop
2893
2894
2895   SUBROUTINE ctl_warn( cd1, cd2, cd3, cd4, cd5,   &
2896      &                 cd6, cd7, cd8, cd9, cd10 )
2897      !!----------------------------------------------------------------------
2898      !!                  ***  ROUTINE  stop_warn  ***
2899      !!
2900      !! ** Purpose :   print in ocean.outpput file a error message and
2901      !!                increment the warning number (nwarn) by one.
2902      !!----------------------------------------------------------------------
2903      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd1, cd2, cd3, cd4, cd5
2904      CHARACTER(len=*), INTENT(in), OPTIONAL ::  cd6, cd7, cd8, cd9, cd10
2905      !!----------------------------------------------------------------------
2906      !
2907      nwarn = nwarn + 1 
2908      IF(lwp) THEN
2909         WRITE(numout,cform_war)
2910         IF( PRESENT(cd1 ) ) WRITE(numout,*) cd1
2911         IF( PRESENT(cd2 ) ) WRITE(numout,*) cd2
2912         IF( PRESENT(cd3 ) ) WRITE(numout,*) cd3
2913         IF( PRESENT(cd4 ) ) WRITE(numout,*) cd4
2914         IF( PRESENT(cd5 ) ) WRITE(numout,*) cd5
2915         IF( PRESENT(cd6 ) ) WRITE(numout,*) cd6
2916         IF( PRESENT(cd7 ) ) WRITE(numout,*) cd7
2917         IF( PRESENT(cd8 ) ) WRITE(numout,*) cd8
2918         IF( PRESENT(cd9 ) ) WRITE(numout,*) cd9
2919         IF( PRESENT(cd10) ) WRITE(numout,*) cd10
2920      ENDIF
2921      CALL FLUSH(numout)
2922      !
2923   END SUBROUTINE ctl_warn
2924
2925
2926   SUBROUTINE ctl_opn( knum, cdfile, cdstat, cdform, cdacce, klengh, kout, ldwp, karea )
2927      !!----------------------------------------------------------------------
2928      !!                  ***  ROUTINE ctl_opn  ***
2929      !!
2930      !! ** Purpose :   Open file and check if required file is available.
2931      !!
2932      !! ** Method  :   Fortan open
2933      !!----------------------------------------------------------------------
2934      INTEGER          , INTENT(  out) ::   knum      ! logical unit to open
2935      CHARACTER(len=*) , INTENT(in   ) ::   cdfile    ! file name to open
2936      CHARACTER(len=*) , INTENT(in   ) ::   cdstat    ! disposition specifier
2937      CHARACTER(len=*) , INTENT(in   ) ::   cdform    ! formatting specifier
2938      CHARACTER(len=*) , INTENT(in   ) ::   cdacce    ! access specifier
2939      INTEGER          , INTENT(in   ) ::   klengh    ! record length
2940      INTEGER          , INTENT(in   ) ::   kout      ! number of logical units for write
2941      LOGICAL          , INTENT(in   ) ::   ldwp      ! boolean term for print
2942      INTEGER, OPTIONAL, INTENT(in   ) ::   karea     ! proc number
2943      !!
2944      CHARACTER(len=80) ::   clfile
2945      INTEGER           ::   iost
2946      !!----------------------------------------------------------------------
2947
2948      ! adapt filename
2949      ! ----------------
2950      clfile = TRIM(cdfile)
2951      IF( PRESENT( karea ) ) THEN
2952         IF( karea > 1 )   WRITE(clfile, "(a,'_',i4.4)") TRIM(clfile), karea-1
2953      ENDIF
2954#if defined key_agrif
2955      IF( .NOT. Agrif_Root() )   clfile = TRIM(Agrif_CFixed())//'_'//TRIM(clfile)
2956      knum=Agrif_Get_Unit()
2957#else
2958      knum=get_unit()
2959#endif
2960
2961      iost=0
2962      IF( cdacce(1:6) == 'DIRECT' )  THEN
2963         OPEN( UNIT=knum, FILE=clfile, FORM=cdform, ACCESS=cdacce, STATUS=cdstat, RECL=klengh, ERR=100, IOSTAT=iost )
2964      ELSE
2965         OPEN( UNIT=knum, FILE=clfile, FORM=cdform, ACCESS=cdacce, STATUS=cdstat             , ERR=100, IOSTAT=iost )
2966      ENDIF
2967      IF( iost == 0 ) THEN
2968         IF(ldwp) THEN
2969            WRITE(kout,*) '     file   : ', clfile,' open ok'
2970            WRITE(kout,*) '     unit   = ', knum
2971            WRITE(kout,*) '     status = ', cdstat
2972            WRITE(kout,*) '     form   = ', cdform
2973            WRITE(kout,*) '     access = ', cdacce
2974            WRITE(kout,*)
2975         ENDIF
2976      ENDIF
2977100   CONTINUE
2978      IF( iost /= 0 ) THEN
2979         IF(ldwp) THEN
2980            WRITE(kout,*)
2981            WRITE(kout,*) ' ===>>>> : bad opening file: ', clfile
2982            WRITE(kout,*) ' =======   ===  '
2983            WRITE(kout,*) '           unit   = ', knum
2984            WRITE(kout,*) '           status = ', cdstat
2985            WRITE(kout,*) '           form   = ', cdform
2986            WRITE(kout,*) '           access = ', cdacce
2987            WRITE(kout,*) '           iostat = ', iost
2988            WRITE(kout,*) '           we stop. verify the file '
2989            WRITE(kout,*)
2990         ENDIF
2991         STOP 'ctl_opn bad opening'
2992      ENDIF
2993     
2994   END SUBROUTINE ctl_opn
2995
2996
2997   INTEGER FUNCTION get_unit()
2998      !!----------------------------------------------------------------------
2999      !!                  ***  FUNCTION  get_unit  ***
3000      !!
3001      !! ** Purpose :   return the index of an unused logical unit
3002      !!----------------------------------------------------------------------
3003      LOGICAL :: llopn 
3004      !!----------------------------------------------------------------------
3005      !
3006      get_unit = 15   ! choose a unit that is big enough then it is not already used in NEMO
3007      llopn = .TRUE.
3008      DO WHILE( (get_unit < 998) .AND. llopn )
3009         get_unit = get_unit + 1
3010         INQUIRE( unit = get_unit, opened = llopn )
3011      END DO
3012      IF( (get_unit == 999) .AND. llopn ) THEN
3013         CALL ctl_stop( 'get_unit: All logical units until 999 are used...' )
3014         get_unit = -1
3015      ENDIF
3016      !
3017   END FUNCTION get_unit
3018
3019   !!----------------------------------------------------------------------
3020END MODULE lib_mpp
Note: See TracBrowser for help on using the repository browser.