New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
lib_mpp.F90 in trunk/NEMO/OPA_SRC – NEMO

source: trunk/NEMO/OPA_SRC/lib_mpp.F90 @ 633

Last change on this file since 633 was 629, checked in by opalod, 17 years ago

nemo_v2_bugfix_018 : CT : change variables name "size" & "rank" into "mppsize" & "mpprank" to avoid conflicts when they become PUBLIC when using key_oasis[3-4] cpp keys

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 177.2 KB
Line 
1MODULE lib_mpp
2   !!======================================================================
3   !!                       ***  MODULE  lib_mpp  ***
4   !! Ocean numerics:  massively parallel processing librairy
5   !!=====================================================================
6#if   defined key_mpp_mpi   ||   defined key_mpp_shmem
7   !!----------------------------------------------------------------------
8   !!   'key_mpp_mpi'     OR      MPI massively parallel processing library
9   !!   'key_mpp_shmem'         SHMEM massively parallel processing library
10   !!----------------------------------------------------------------------
11   !!   mynode
12   !!   mpparent
13   !!   mppshmem
14   !!   mpp_lnk     : generic interface (defined in lbclnk) for :
15   !!                 mpp_lnk_2d, mpp_lnk_3d
16   !!   mpp_lnk_3d_gather :  Message passing manadgement for two 3D arrays
17   !!   mpp_lnk_e   : interface defined in lbclnk
18   !!   mpplnks
19   !!   mpprecv
20   !!   mppsend
21   !!   mppscatter
22   !!   mppgather
23   !!   mpp_isl    : generic inteface  for :
24   !!                mppisl_int , mppisl_a_int , mppisl_real, mppisl_a_real
25   !!   mpp_min    : generic interface for :
26   !!                mppmin_int , mppmin_a_int , mppmin_real, mppmin_a_real
27   !!   mpp_max    : generic interface for :
28   !!                mppmax_real, mppmax_a_real
29   !!   mpp_sum    : generic interface for :
30   !!                mppsum_int , mppsum_a_int , mppsum_real, mppsum_a_real
31   !!   mpp_minloc
32   !!   mpp_maxloc
33   !!   mppsync
34   !!   mppstop
35   !!   mppobc     : variant of mpp_lnk for open boundaries
36   !!   mpp_ini_north
37   !!   mpp_lbc_north
38   !!   mpp_lbc_north_e : variant of mpp_lbc_north for extra outer halo (nsolv=4)
39   !!----------------------------------------------------------------------
40   !! History :
41   !!        !  94 (M. Guyon, J. Escobar, M. Imbard)  Original code
42   !!        !  97  (A.M. Treguier)  SHMEM additions
43   !!        !  98  (M. Imbard, J. Escobar, L. Colombet ) SHMEM and MPI
44   !!   9.0  !  03  (J.-M. Molines, G. Madec)  F90, free form
45   !!        !  04  (R. Bourdalle Badie)  isend option in mpi
46   !!        !  05  (G. Madec, S. Masson)  npolj=5,6 F-point & ice cases
47   !!        !  05  (R. Redler) Replacement of MPI_COMM_WORLD except for MPI_Abort
48   !!----------------------------------------------------------------------
49   !!  OPA 9.0 , LOCEAN-IPSL (2005)
50   !! $Header$
51   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
52   !!---------------------------------------------------------------------
53   !! * Modules used
54   USE dom_oce                    ! ocean space and time domain
55   USE in_out_manager             ! I/O manager
56
57   IMPLICIT NONE
58
59   PRIVATE
60   PUBLIC  mynode, mpparent, mpp_isl, mpp_min, mpp_max, mpp_sum,  mpp_lbc_north
61   PUBLIC  mpp_lbc_north_e, mpp_minloc, mpp_maxloc, mpp_lnk_3d, mpp_lnk_2d, mpp_lnk_3d_gather, mpp_lnk_2d_e, mpplnks
62   PUBLIC  mpprecv, mppsend, mppscatter, mppgather, mppobc, mpp_ini_north, mppstop, mppsync
63#if defined key_oasis3 || defined key_oasis4
64   PUBLIC  mppsize, mpprank
65#endif
66
67   !! * Interfaces
68   !! define generic interface for these routine as they are called sometimes
69   !!        with scalar arguments instead of array arguments, which causes problems
70   !!        for the compilation on AIX system as well as NEC and SGI. Ok on COMPACQ
71
72   INTERFACE mpp_isl
73      MODULE PROCEDURE mppisl_a_int, mppisl_int, mppisl_a_real, mppisl_real
74   END INTERFACE
75   INTERFACE mpp_min
76      MODULE PROCEDURE mppmin_a_int, mppmin_int, mppmin_a_real, mppmin_real
77   END INTERFACE
78   INTERFACE mpp_max
79      MODULE PROCEDURE mppmax_a_real, mppmax_real
80   END INTERFACE
81   INTERFACE mpp_sum
82      MODULE PROCEDURE mppsum_a_int, mppsum_int, mppsum_a_real, mppsum_real
83   END INTERFACE
84   INTERFACE mpp_lbc_north
85      MODULE PROCEDURE mpp_lbc_north_3d, mpp_lbc_north_2d 
86   END INTERFACE
87  INTERFACE mpp_minloc
88     MODULE PROCEDURE mpp_minloc2d ,mpp_minloc3d
89  END INTERFACE
90  INTERFACE mpp_maxloc
91     MODULE PROCEDURE mpp_maxloc2d ,mpp_maxloc3d
92  END INTERFACE
93
94
95   !! * Share module variables
96   LOGICAL, PUBLIC, PARAMETER ::   lk_mpp = .TRUE.       !: mpp flag
97
98   !! The processor number is a required power of two : 1, 2, 4, 8, 16, 32, 64, 128, 256, 512, 1024,...
99   INTEGER, PARAMETER ::   &
100      nprocmax = 2**10,    &  ! maximun dimension
101      ndim_mpp = jpnij        ! dimension for this simulation
102
103#if defined key_mpp_mpi
104   !! ========================= !!
105   !!  MPI  variable definition !!
106   !! ========================= !!
107!$AGRIF_DO_NOT_TREAT
108#  include <mpif.h>
109!$AGRIF_END_DO_NOT_TREAT
110
111   INTEGER ::   &
112      mppsize,  &  ! number of process
113      mpprank,  &  ! process number  [ 0 - size-1 ]
114      mpi_comm_opa ! opa local communicator
115
116   ! variables used in case of north fold condition in mpp_mpi with jpni > 1
117   INTEGER ::      &       !
118      ngrp_world,  &       ! group ID for the world processors
119      ngrp_north,  &       ! group ID for the northern processors (to be fold)
120      ncomm_north, &       ! communicator made by the processors belonging to ngrp_north
121      ndim_rank_north, &   ! number of 'sea' processor in the northern line (can be /= jpni !)
122      njmppmax             ! value of njmpp for the processors of the northern line
123   INTEGER ::      &       !
124      north_root           ! number (in the comm_opa) of proc 0 in the northern comm
125   INTEGER, DIMENSION(:), ALLOCATABLE ::   &
126      nrank_north          ! dimension ndim_rank_north, number of the procs belonging to ncomm_north
127   CHARACTER (len=1) ::  &
128      c_mpi_send = 'S'     ! type od mpi send/recieve (S=standard, B=bsend, I=isend)
129   LOGICAL  ::           &
130      l_isend = .FALSE.    ! isend use indicator (T if c_mpi_send='I')
131
132
133#elif defined key_mpp_shmem
134   !! ========================= !!
135   !! SHMEM variable definition !!
136   !! ========================= !!
137#  include  <fpvm3.h>
138#  include <mpp/shmem.fh>
139
140   CHARACTER (len=80), PARAMETER ::   simfile    = 'pvm3_ndim'   ! file name
141   CHARACTER (len=47), PARAMETER ::   executable = 'opa'         ! executable name
142   CHARACTER, PARAMETER ::            opaall     = ""            ! group name (old def opaall*(*))
143
144   INTEGER, PARAMETER ::   & !! SHMEM control print
145      mynode_print   = 0,  &  ! flag for print, mynode   routine
146      mpprecv_print  = 0,  &  ! flag for print, mpprecv  routine
147      mppsend_print  = 0,  &  ! flag for print, mppsend  routine
148      mppsync_print  = 0,  &  ! flag for print, mppsync  routine
149      mppsum_print   = 0,  &  ! flag for print, mpp_sum  routine
150      mppisl_print   = 0,  &  ! flag for print, mpp_isl  routine
151      mppmin_print   = 0,  &  ! flag for print, mpp_min  routine
152      mppmax_print   = 0,  &  ! flag for print, mpp_max  routine
153      mpparent_print = 0      ! flag for print, mpparent routine
154
155   INTEGER, PARAMETER ::   & !! Variable definition
156      jpvmint = 21            ! ???
157
158   INTEGER, PARAMETER ::   & !! Maximum  dimension of array to sum on the processors
159      jpmsec   = 50000,    &  ! ???
160      jpmpplat =    30,    &  ! ???
161      jpmppsum = MAX( jpisl*jpisl, jpmpplat*jpk, jpmsec )   ! ???
162
163   INTEGER ::   &
164      npvm_ipas ,  &  ! pvm initialization flag
165      npvm_mytid,  &  ! pvm tid
166      npvm_me   ,  &  ! node number [ 0 - nproc-1 ]
167      npvm_nproc,  &  ! real number of nodes
168      npvm_inum       ! ???
169   INTEGER, DIMENSION(0:nprocmax-1) ::   &
170      npvm_tids       ! tids array [ 0 - nproc-1 ]
171
172   INTEGER ::   &
173      nt3d_ipas ,  &  ! pvm initialization flag
174      nt3d_mytid,  &  ! pvm tid
175      nt3d_me   ,  &  ! node number [ 0 - nproc-1 ]
176      nt3d_nproc      ! real number of nodes
177   INTEGER, DIMENSION(0:nprocmax-1) ::   &
178      nt3d_tids       ! tids array [ 0 - nproc-1 ]
179
180   !! real sum reduction
181   INTEGER, DIMENSION(SHMEM_REDUCE_SYNC_SIZE) ::   &
182       nrs1sync_shmem,   &  !
183       nrs2sync_shmem
184   REAL(wp), DIMENSION( MAX( SHMEM_REDUCE_MIN_WRKDATA_SIZE, jpmppsum/2+1 ) ) ::   &
185       wrs1wrk_shmem,    &  !
186       wrs2wrk_shmem        !
187   REAL(wp), DIMENSION(jpmppsum) ::   &
188       wrstab_shmem         !
189
190   !! minimum and maximum reduction
191   INTEGER, DIMENSION(SHMEM_REDUCE_SYNC_SIZE) ::   &
192       ni1sync_shmem,    &  !
193       ni2sync_shmem        !
194   REAL(wp), DIMENSION( MAX( SHMEM_REDUCE_MIN_WRKDATA_SIZE, jpmppsum/2+1 ) ) ::   &
195       wi1wrk_shmem,     &  !
196       wi2wrk_shmem
197   REAL(wp), DIMENSION(jpmppsum) ::   &
198       wintab_shmem,     &  !
199       wi1tab_shmem,     &  !
200       wi2tab_shmem         !
201       
202       !! value not equal zero for barotropic stream function around islands
203   INTEGER, DIMENSION(SHMEM_REDUCE_SYNC_SIZE) ::   &
204       ni11sync_shmem,   &  !
205       ni12sync_shmem,   &  !
206       ni21sync_shmem,   &  !
207       ni22sync_shmem       !
208   REAL(wp), DIMENSION( MAX( SHMEM_REDUCE_MIN_WRKDATA_SIZE, jpmppsum/2+1 ) ) ::   &
209       wi11wrk_shmem,    &  !
210       wi12wrk_shmem,    &  !
211       wi21wrk_shmem,    &  !
212       wi22wrk_shmem        !
213   REAL(wp), DIMENSION(jpmppsum) ::   &
214       wiltab_shmem ,    &  !
215       wi11tab_shmem,    &  !
216       wi12tab_shmem,    &  !
217       wi21tab_shmem,    &  !
218       wi22tab_shmem
219
220   INTEGER, DIMENSION( MAX( SHMEM_REDUCE_MIN_WRKDATA_SIZE, jpmppsum/2+1 ) ) ::   &
221       ni11wrk_shmem,    &  !
222       ni12wrk_shmem,    &  !
223       ni21wrk_shmem,    &  !
224       ni22wrk_shmem        !
225   INTEGER, DIMENSION(jpmppsum) ::   &
226       niitab_shmem ,    &  !
227       ni11tab_shmem,    &  !
228       ni12tab_shmem        !
229   INTEGER, DIMENSION(SHMEM_REDUCE_SYNC_SIZE) ::   &
230       nis1sync_shmem,   &  !
231       nis2sync_shmem       !
232   INTEGER, DIMENSION( MAX( SHMEM_REDUCE_MIN_WRKDATA_SIZE, jpmppsum/2+1 ) ) ::   &
233       nis1wrk_shmem,    &  !
234       nis2wrk_shmem        !
235   INTEGER, DIMENSION(jpmppsum) ::   &
236       nistab_shmem
237
238   !! integer sum reduction
239   INTEGER, DIMENSION(SHMEM_REDUCE_SYNC_SIZE) ::   &
240       nil1sync_shmem,   &  !
241       nil2sync_shmem       !
242   INTEGER, DIMENSION( MAX( SHMEM_REDUCE_MIN_WRKDATA_SIZE, jpmppsum/2+1 ) ) ::   &
243       nil1wrk_shmem,    &  !
244       nil2wrk_shmem        !
245   INTEGER, DIMENSION(jpmppsum) ::   &
246       niltab_shmem
247#endif
248
249   REAL(wp), DIMENSION(jpi,jprecj,jpk,2,2) ::   &
250       t4ns, t4sn  ! 3d message passing arrays north-south & south-north
251   REAL(wp), DIMENSION(jpj,jpreci,jpk,2,2) ::   &
252       t4ew, t4we  ! 3d message passing arrays east-west & west-east
253   REAL(wp), DIMENSION(jpi,jprecj,jpk,2,2) ::   &
254       t4p1, t4p2  ! 3d message passing arrays north fold
255   REAL(wp), DIMENSION(jpi,jprecj,jpk,2) ::   &
256       t3ns, t3sn  ! 3d message passing arrays north-south & south-north
257   REAL(wp), DIMENSION(jpj,jpreci,jpk,2) ::   &
258       t3ew, t3we  ! 3d message passing arrays east-west & west-east
259   REAL(wp), DIMENSION(jpi,jprecj,jpk,2) ::   &
260       t3p1, t3p2  ! 3d message passing arrays north fold
261   REAL(wp), DIMENSION(jpi,jprecj,2) ::   &
262       t2ns, t2sn  ! 2d message passing arrays north-south & south-north
263   REAL(wp), DIMENSION(jpj,jpreci,2) ::   &
264       t2ew, t2we  ! 2d message passing arrays east-west & west-east
265   REAL(wp), DIMENSION(jpi,jprecj,2) ::   &
266       t2p1, t2p2  ! 2d message passing arrays north fold
267   REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,jprecj+jpr2dj,2) ::   &
268       tr2ns, tr2sn  ! 2d message passing arrays north-south & south-north including extra outer halo
269   REAL(wp), DIMENSION(1-jpr2dj:jpj+jpr2dj,jpreci+jpr2di,2) ::   &
270       tr2ew, tr2we  ! 2d message passing arrays east-west & west-east including extra outer halo
271   !!----------------------------------------------------------------------
272   !!  OPA 9.0 , LOCEAN-IPSL (2005)
273   !! $Header$
274   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
275   !!---------------------------------------------------------------------
276
277CONTAINS
278
279   FUNCTION mynode(localComm)
280      !!----------------------------------------------------------------------
281      !!                  ***  routine mynode  ***
282      !!                   
283      !! ** Purpose :   Find processor unit
284      !!
285      !!----------------------------------------------------------------------
286#if defined key_mpp_mpi
287      !! * Local variables   (MPI version)
288      INTEGER ::   mynode, ierr, code
289      LOGICAL ::   mpi_was_called
290      INTEGER,OPTIONAL ::   localComm
291      NAMELIST/nam_mpp/ c_mpi_send
292      !!----------------------------------------------------------------------
293
294      WRITE(numout,*)
295      WRITE(numout,*) 'mynode : mpi initialisation'
296      WRITE(numout,*) '~~~~~~ '
297      WRITE(numout,*)
298
299      ! Namelist namrun : parameters of the run
300      REWIND( numnam )
301      READ  ( numnam, nam_mpp )
302
303      WRITE(numout,*) '        Namelist nam_mpp'
304      WRITE(numout,*) '           mpi send type            c_mpi_send = ', c_mpi_send
305
306#if defined key_agrif
307      IF( Agrif_Root() ) THEN
308#endif
309!!bug RB : should be clean to use Agrif in coupled mode
310#if ! defined key_agrif
311         CALL mpi_initialized ( mpi_was_called, code )
312         IF( code /= MPI_SUCCESS ) THEN
313            CALL ctl_stop( ' lib_mpp: Error in routine mpi_initialized' )
314            CALL mpi_abort( mpi_comm_world, code, ierr )
315         ENDIF
316
317         IF( PRESENT(localComm) .and. mpi_was_called ) THEN
318            mpi_comm_opa = localComm
319            SELECT CASE ( c_mpi_send )
320            CASE ( 'S' )                ! Standard mpi send (blocking)
321               WRITE(numout,*) '           Standard blocking mpi send (send)'
322            CASE ( 'B' )                ! Buffer mpi send (blocking)
323               WRITE(numout,*) '           Buffer blocking mpi send (bsend)'
324               CALL mpi_init_opa( ierr )
325            CASE ( 'I' )                ! Immediate mpi send (non-blocking send)
326               WRITE(numout,*) '           Immediate non-blocking send (isend)'
327               l_isend = .TRUE.
328            CASE DEFAULT
329               WRITE(numout,cform_err)
330               WRITE(numout,*) '           bad value for c_mpi_send = ', c_mpi_send
331               nstop = nstop + 1
332            END SELECT
333         ELSE IF ( PRESENT(localComm) .and. .not. mpi_was_called ) THEN
334            WRITE(numout,*) ' lib_mpp: You cannot provide a local communicator '
335            WRITE(numout,*) '          without calling MPI_Init before ! '
336         ELSE
337#endif
338            SELECT CASE ( c_mpi_send )
339            CASE ( 'S' )                ! Standard mpi send (blocking)
340               WRITE(numout,*) '           Standard blocking mpi send (send)'
341               CALL mpi_init( ierr )
342            CASE ( 'B' )                ! Buffer mpi send (blocking)
343               WRITE(numout,*) '           Buffer blocking mpi send (bsend)'
344               CALL mpi_init_opa( ierr )
345            CASE ( 'I' )                ! Immediate mpi send (non-blocking send)
346               WRITE(numout,*) '           Immediate non-blocking send (isend)'
347               l_isend = .TRUE.
348               CALL mpi_init( ierr )
349            CASE DEFAULT
350               WRITE(ctmp1,*) '           bad value for c_mpi_send = ', c_mpi_send
351               CALL ctl_stop( ctmp1 )
352            END SELECT
353
354#if ! defined key_agrif
355            CALL mpi_comm_dup( mpi_comm_world, mpi_comm_opa, code)
356            IF( code /= MPI_SUCCESS ) THEN
357               CALL ctl_stop( ' lib_mpp: Error in routine mpi_comm_dup' )
358               CALL mpi_abort( mpi_comm_world, code, ierr )
359            ENDIF
360            !
361         ENDIF
362#endif
363#if defined key_agrif
364      ELSE
365         SELECT CASE ( c_mpi_send )
366         CASE ( 'S' )                ! Standard mpi send (blocking)
367            WRITE(numout,*) '           Standard blocking mpi send (send)'
368         CASE ( 'B' )                ! Buffer mpi send (blocking)
369            WRITE(numout,*) '           Buffer blocking mpi send (bsend)'
370         CASE ( 'I' )                ! Immediate mpi send (non-blocking send)
371            WRITE(numout,*) '           Immediate non-blocking send (isend)'
372            l_isend = .TRUE.
373         CASE DEFAULT
374            WRITE(numout,cform_err)
375            WRITE(numout,*) '           bad value for c_mpi_send = ', c_mpi_send
376            nstop = nstop + 1
377         END SELECT
378      ENDIF
379
380      mpi_comm_opa = mpi_comm_world
381#endif
382        CALL mpi_comm_rank( mpi_comm_opa, mpprank, ierr )
383        CALL mpi_comm_size( mpi_comm_opa, mppsize, ierr )
384      mynode = mpprank
385#else
386      !! * Local variables   (SHMEM version)
387      INTEGER ::   mynode
388      INTEGER ::   &
389           imypid, imyhost, ji, info, iparent_tid
390      !!----------------------------------------------------------------------
391
392      IF( npvm_ipas /= nprocmax ) THEN
393         !         ---   first passage in mynode
394         !         -------------
395         !         enroll in pvm
396         !         -------------
397         CALL pvmfmytid( npvm_mytid )
398         IF( mynode_print /= 0 ) THEN
399            WRITE(numout,*) 'mynode, npvm_ipas =', npvm_ipas, ' nprocmax=', nprocmax
400            WRITE(numout,*) 'mynode, npvm_mytid=', npvm_mytid, ' after pvmfmytid'
401         ENDIF
402
403         !         ---------------------------------------------------------------
404         !         find out IF i am parent or child spawned processes have parents
405         !         ---------------------------------------------------------------
406         CALL mpparent( iparent_tid )
407         IF( mynode_print /= 0 ) THEN
408            WRITE(numout,*) 'mynode, npvm_mytid=', npvm_mytid,   &
409               &            ' after mpparent, npvm_tids(0) = ',   &
410               &            npvm_tids(0), ' iparent_tid=', iparent_tid
411         ENDIF
412         IF( iparent_tid < 0 )  THEN
413            WRITE(numout,*) 'mynode, npvm_mytid=', npvm_mytid,   &
414               &            ' after mpparent, npvm_tids(0) = ',   &
415               &            npvm_tids(0), ' iparent_tid=', iparent_tid
416            npvm_tids(0) = npvm_mytid
417            npvm_me = 0
418            IF( ndim_mpp > nprocmax ) THEN
419               WRITE(ctmp1,*) 'npvm_mytid=', npvm_mytid, ' too great'
420               CALL ctl_stop( ctmp1 )
421
422            ELSE
423               npvm_nproc = ndim_mpp
424            ENDIF
425
426            ! -------------------------
427            ! start up copies of myself
428            ! -------------------------
429            IF( npvm_nproc > 1 ) THEN
430               DO ji = 1, npvm_nproc-1
431                  npvm_tids(ji) = nt3d_tids(ji)
432               END DO
433               info=npvm_nproc-1
434 
435               IF( mynode_print /= 0 ) THEN
436                  WRITE(numout,*) 'mynode, npvm_mytid=',npvm_mytid,   &
437                     &            ' maitre=',executable,' info=', info   &
438                     &            ,' npvm_nproc=',npvm_nproc
439                  WRITE(numout,*) 'mynode, npvm_mytid=',npvm_mytid,   &
440                     &            ' npvm_tids ',(npvm_tids(ji),ji=0,npvm_nproc-1)
441               ENDIF
442
443               ! ---------------------------
444               ! multicast tids array to children
445               ! ---------------------------
446               CALL pvmfinitsend( pvmdefault, info )
447               CALL pvmfpack ( jpvmint, npvm_nproc, 1         , 1, info )
448               CALL pvmfpack ( jpvmint, npvm_tids , npvm_nproc, 1, info )
449               CALL pvmfmcast( npvm_nproc-1, npvm_tids(1), 10, info )
450            ENDIF
451         ELSE
452
453            ! ---------------------------------
454            ! receive the tids array and set me
455            ! ---------------------------------
456            IF( mynode_print /= 0 )   WRITE(numout,*) 'mynode, npvm_mytid=',npvm_mytid, ' pvmfrecv'
457            CALL pvmfrecv( iparent_tid, 10, info )
458            IF( mynode_print /= 0 )   WRITE(numout,*) 'mynode, npvm_mytid=',npvm_mytid, " fin pvmfrecv"
459            CALL pvmfunpack( jpvmint, npvm_nproc, 1         , 1, info )
460            CALL pvmfunpack( jpvmint, npvm_tids , npvm_nproc, 1, info )
461            IF( mynode_print /= 0 ) THEN
462               WRITE(numout,*) 'mynode, npvm_mytid=',npvm_mytid,   &
463                  &            ' esclave=', executable,' info=', info,' npvm_nproc=',npvm_nproc
464               WRITE(numout,*) 'mynode, npvm_mytid=', npvm_mytid,   &
465                  &            'npvm_tids', ( npvm_tids(ji), ji = 0, npvm_nproc-1 )
466            ENDIF
467            DO ji = 0, npvm_nproc-1
468               IF( npvm_mytid == npvm_tids(ji) ) npvm_me = ji
469            END DO
470         ENDIF
471
472         ! ------------------------------------------------------------
473         ! all nproc tasks are equal now
474         ! and can address each other by tids(0) thru tids(nproc-1)
475         ! for each process me => process number [0-(nproc-1)]
476         ! ------------------------------------------------------------
477         CALL pvmfjoingroup ( "bidon", info )
478         CALL pvmfbarrier   ( "bidon", npvm_nproc, info )
479         DO ji = 0, npvm_nproc-1
480            IF( ji == npvm_me ) THEN
481               CALL pvmfjoingroup ( opaall, npvm_inum )
482               IF( npvm_inum /= npvm_me )   WRITE(numout,*) 'mynode not arrived in the good order for opaall'
483            ENDIF
484            CALL pvmfbarrier( "bidon", npvm_nproc, info )
485         END DO
486         CALL pvmfbarrier( opaall, npvm_nproc, info )
487 
488      ELSE
489         ! ---   other passage in mynode
490      ENDIF
491 
492      npvm_ipas = nprocmax
493      mynode    = npvm_me
494      imypid    = npvm_mytid
495      imyhost   = npvm_tids(0)
496      IF( mynode_print /= 0 ) THEN
497         WRITE(numout,*)'mynode: npvm_mytid=', npvm_mytid, ' npvm_me=', npvm_me,   &
498            &           ' npvm_nproc=', npvm_nproc , ' npvm_ipas=', npvm_ipas
499      ENDIF
500#endif
501   END FUNCTION mynode
502
503
504   SUBROUTINE mpparent( kparent_tid )
505      !!----------------------------------------------------------------------
506      !!                  ***  routine mpparent  ***
507      !!
508      !! ** Purpose :   use an pvmfparent routine for T3E (key_mpp_shmem)
509      !!              or  only return -1 (key_mpp_mpi)
510      !!----------------------------------------------------------------------
511      !! * Arguments
512      INTEGER, INTENT(inout) ::   kparent_tid      ! ???
513 
514#if defined key_mpp_mpi
515      ! MPI version : retour -1
516
517      kparent_tid = -1
518
519#else
520      !! * Local variables   (SHMEN onto T3E version)
521      INTEGER ::   &
522           it3d_my_pe, LEADZ, ji, info
523 
524      CALL pvmfmytid( nt3d_mytid )
525      CALL pvmfgetpe( nt3d_mytid, it3d_my_pe )
526      IF( mpparent_print /= 0 ) THEN
527         WRITE(numout,*) 'mpparent: nt3d_mytid= ', nt3d_mytid ,' it3d_my_pe=',it3d_my_pe
528      ENDIF
529      IF( it3d_my_pe == 0 ) THEN
530         !-----------------------------------------------------------------!
531         !     process = 0 => receive other tids                           !
532         !-----------------------------------------------------------------!
533         kparent_tid = -1
534         IF(mpparent_print /= 0 ) THEN
535            WRITE(numout,*) 'mpparent, nt3d_mytid=',nt3d_mytid ,' kparent_tid=',kparent_tid
536         ENDIF
537         !          --- END receive dimension ---
538         IF( ndim_mpp > nprocmax ) THEN
539            WRITE(ctmp1,*) 'mytid=',nt3d_mytid,' too great'
540            CALL ctl_stop( ctmp1 )
541         ELSE
542            nt3d_nproc =  ndim_mpp
543         ENDIF
544         IF( mpparent_print /= 0 ) THEN
545            WRITE(numout,*) 'mpparent, nt3d_mytid=', nt3d_mytid , ' nt3d_nproc=', nt3d_nproc
546         ENDIF
547         !-------- receive tids from others process --------
548         DO ji = 1, nt3d_nproc-1
549            CALL pvmfrecv( ji , 100, info )
550            CALL pvmfunpack( jpvmint, nt3d_tids(ji), 1, 1, info )
551            IF( mpparent_print /= 0 ) THEN
552               WRITE(numout,*) 'mpparent, nt3d_mytid=', nt3d_mytid , ' receive=', nt3d_tids(ji), ' from = ', ji
553            ENDIF
554         END DO
555         nt3d_tids(0) = nt3d_mytid
556         IF( mpparent_print /= 0 ) THEN
557            WRITE(numout,*) 'mpparent, nt3d_mytid=', nt3d_mytid , ' nt3d_tids(ji) =', (nt3d_tids(ji),   &
558                 ji = 0, nt3d_nproc-1 )
559            WRITE(numout,*) 'mpparent, nt3d_mytid=', nt3d_mytid , ' kparent_tid=', kparent_tid
560         ENDIF
561
562      ELSE
563         !!----------------------------------------------------------------!
564         !     process <> 0 => send  other tids                            !
565         !!----------------------------------------------------------------!
566         kparent_tid = 0
567         CALL pvmfinitsend( pvmdataraw, info )
568         CALL pvmfpack( jpvmint, nt3d_mytid, 1, 1, info )
569         CALL pvmfsend( kparent_tid, 100, info )
570      ENDIF
571#endif
572
573   END SUBROUTINE mpparent
574
575#if defined key_mpp_shmem
576
577   SUBROUTINE mppshmem
578      !!----------------------------------------------------------------------
579      !!                  ***  routine mppshmem  ***
580      !!
581      !! ** Purpose :   SHMEM ROUTINE
582      !!
583      !!----------------------------------------------------------------------
584      nrs1sync_shmem = SHMEM_SYNC_VALUE
585      nrs2sync_shmem = SHMEM_SYNC_VALUE
586      nis1sync_shmem = SHMEM_SYNC_VALUE
587      nis2sync_shmem = SHMEM_SYNC_VALUE
588      nil1sync_shmem = SHMEM_SYNC_VALUE
589      nil2sync_shmem = SHMEM_SYNC_VALUE
590      ni11sync_shmem = SHMEM_SYNC_VALUE
591      ni12sync_shmem = SHMEM_SYNC_VALUE
592      ni21sync_shmem = SHMEM_SYNC_VALUE
593      ni22sync_shmem = SHMEM_SYNC_VALUE
594      CALL barrier()
595 
596   END SUBROUTINE mppshmem
597
598#endif
599
600   SUBROUTINE mpp_lnk_3d( ptab, cd_type, psgn, cd_mpp )
601      !!----------------------------------------------------------------------
602      !!                  ***  routine mpp_lnk_3d  ***
603      !!
604      !! ** Purpose :   Message passing manadgement
605      !!
606      !! ** Method  :   Use mppsend and mpprecv function for passing mask
607      !!      between processors following neighboring subdomains.
608      !!            domain parameters
609      !!                    nlci   : first dimension of the local subdomain
610      !!                    nlcj   : second dimension of the local subdomain
611      !!                    nbondi : mark for "east-west local boundary"
612      !!                    nbondj : mark for "north-south local boundary"
613      !!                    noea   : number for local neighboring processors
614      !!                    nowe   : number for local neighboring processors
615      !!                    noso   : number for local neighboring processors
616      !!                    nono   : number for local neighboring processors
617      !!
618      !! ** Action  :   ptab with update value at its periphery
619      !!
620      !!----------------------------------------------------------------------
621      !! * Arguments
622      CHARACTER(len=1) , INTENT( in ) ::   &
623         cd_type       ! define the nature of ptab array grid-points
624         !             ! = T , U , V , F , W points
625         !             ! = S : T-point, north fold treatment ???
626         !             ! = G : F-point, north fold treatment ???
627      REAL(wp), INTENT( in ) ::   &
628         psgn          ! control of the sign change
629         !             !   = -1. , the sign is changed if north fold boundary
630         !             !   =  1. , the sign is kept  if north fold boundary
631      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   &
632         ptab          ! 3D array on which the boundary condition is applied
633      CHARACTER(len=3), INTENT( in ), OPTIONAL ::    &
634         cd_mpp        ! fill the overlap area only
635
636      !! * Local variables
637      INTEGER ::   ji, jj, jk, jl                        ! dummy loop indices
638      INTEGER ::   imigr, iihom, ijhom, iloc, ijt, iju   ! temporary integers
639      INTEGER ::   ml_req1, ml_req2, ml_err     ! for key_mpi_isend
640      INTEGER ::   ml_stat(MPI_STATUS_SIZE)     ! for key_mpi_isend
641      !!----------------------------------------------------------------------
642
643      ! 1. standard boundary treatment
644      ! ------------------------------
645
646      IF( PRESENT( cd_mpp ) ) THEN
647         DO jj = nlcj+1, jpj   ! only fill extra allows last line
648            ptab(1:nlci, jj, :) = ptab(1:nlci, nlej, :)
649         END DO
650         DO ji = nlci+1, jpi   ! only fill extra allows last column
651            ptab(ji    , : , :) = ptab(nlei  , :   , :)
652         END DO
653      ELSE     
654
655         !                                        ! East-West boundaries
656         !                                        ! ====================
657         IF( nbondi == 2 .AND.   &      ! Cyclic east-west
658            &   (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
659            ptab( 1 ,:,:) = ptab(jpim1,:,:)
660            ptab(jpi,:,:) = ptab(  2  ,:,:)
661
662         ELSE                           ! closed
663            SELECT CASE ( cd_type )
664            CASE ( 'T', 'U', 'V', 'W' )
665               ptab(     1       :jpreci,:,:) = 0.e0
666               ptab(nlci-jpreci+1:jpi   ,:,:) = 0.e0
667            CASE ( 'F' )
668               ptab(nlci-jpreci+1:jpi   ,:,:) = 0.e0
669            END SELECT
670         ENDIF
671
672         !                                        ! North-South boundaries
673         !                                        ! ======================
674         SELECT CASE ( cd_type )
675         CASE ( 'T', 'U', 'V', 'W' )
676            ptab(:,     1       :jprecj,:) = 0.e0
677            ptab(:,nlcj-jprecj+1:jpj   ,:) = 0.e0
678         CASE ( 'F' )
679            ptab(:,nlcj-jprecj+1:jpj   ,:) = 0.e0
680         END SELECT
681     
682      ENDIF
683
684      ! 2. East and west directions exchange
685      ! ------------------------------------
686
687      ! 2.1 Read Dirichlet lateral conditions
688
689      SELECT CASE ( nbondi )
690      CASE ( -1, 0, 1 )    ! all exept 2
691         iihom = nlci-nreci
692         DO jl = 1, jpreci
693            t3ew(:,jl,:,1) = ptab(jpreci+jl,:,:)
694            t3we(:,jl,:,1) = ptab(iihom +jl,:,:)
695         END DO
696      END SELECT
697
698      ! 2.2 Migrations
699
700#if defined key_mpp_shmem
701      !! * SHMEM version
702
703      imigr = jpreci * jpj * jpk
704
705      SELECT CASE ( nbondi )
706      CASE ( -1 )
707         CALL shmem_put( t3we(1,1,1,2), t3we(1,1,1,1), imigr, noea )
708      CASE ( 0 )
709         CALL shmem_put( t3ew(1,1,1,2), t3ew(1,1,1,1), imigr, nowe )
710         CALL shmem_put( t3we(1,1,1,2), t3we(1,1,1,1), imigr, noea )
711      CASE ( 1 )
712         CALL shmem_put( t3ew(1,1,1,2), t3ew(1,1,1,1), imigr, nowe )
713      END SELECT
714
715      CALL barrier()
716      CALL shmem_udcflush()
717
718#elif defined key_mpp_mpi
719      !! * Local variables   (MPI version)
720
721      imigr = jpreci * jpj * jpk
722
723      SELECT CASE ( nbondi ) 
724      CASE ( -1 )
725         CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req1 )
726         CALL mpprecv( 1, t3ew(1,1,1,2), imigr )
727         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
728      CASE ( 0 )
729         CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 )
730         CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req2 )
731         CALL mpprecv( 1, t3ew(1,1,1,2), imigr )
732         CALL mpprecv( 2, t3we(1,1,1,2), imigr )
733         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
734         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
735      CASE ( 1 )
736         CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 )
737         CALL mpprecv( 2, t3we(1,1,1,2), imigr )
738         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
739      END SELECT
740#endif
741
742      ! 2.3 Write Dirichlet lateral conditions
743
744      iihom = nlci-jpreci
745
746      SELECT CASE ( nbondi )
747      CASE ( -1 )
748         DO jl = 1, jpreci
749            ptab(iihom+jl,:,:) = t3ew(:,jl,:,2)
750         END DO
751      CASE ( 0 ) 
752         DO jl = 1, jpreci
753            ptab(jl      ,:,:) = t3we(:,jl,:,2)
754            ptab(iihom+jl,:,:) = t3ew(:,jl,:,2)
755         END DO
756      CASE ( 1 )
757         DO jl = 1, jpreci
758            ptab(jl      ,:,:) = t3we(:,jl,:,2)
759         END DO
760      END SELECT
761
762
763      ! 3. North and south directions
764      ! -----------------------------
765
766      ! 3.1 Read Dirichlet lateral conditions
767
768      IF( nbondj /= 2 ) THEN
769         ijhom = nlcj-nrecj
770         DO jl = 1, jprecj
771            t3sn(:,jl,:,1) = ptab(:,ijhom +jl,:)
772            t3ns(:,jl,:,1) = ptab(:,jprecj+jl,:)
773         END DO
774      ENDIF
775
776      ! 3.2 Migrations
777
778#if defined key_mpp_shmem
779      !! * SHMEM version
780
781      imigr = jprecj * jpi * jpk
782
783      SELECT CASE ( nbondj )
784      CASE ( -1 )
785         CALL shmem_put( t3sn(1,1,1,2), t3sn(1,1,1,1), imigr, nono )
786      CASE ( 0 )
787         CALL shmem_put( t3ns(1,1,1,2), t3ns(1,1,1,1), imigr, noso )
788         CALL shmem_put( t3sn(1,1,1,2), t3sn(1,1,1,1), imigr, nono )
789      CASE ( 1 )
790         CALL shmem_put( t3ns(1,1,1,2), t3ns(1,1,1,1), imigr, noso )
791      END SELECT
792
793      CALL barrier()
794      CALL shmem_udcflush()
795
796#elif defined key_mpp_mpi
797      !! * Local variables   (MPI version)
798 
799      imigr=jprecj*jpi*jpk
800
801      SELECT CASE ( nbondj )     
802      CASE ( -1 )
803         CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req1 )
804         CALL mpprecv( 3, t3ns(1,1,1,2), imigr )
805         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
806      CASE ( 0 )
807         CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 )
808         CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req2 )
809         CALL mpprecv( 3, t3ns(1,1,1,2), imigr )
810         CALL mpprecv( 4, t3sn(1,1,1,2), imigr )
811         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
812         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
813      CASE ( 1 ) 
814         CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 )
815         CALL mpprecv( 4, t3sn(1,1,1,2), imigr )
816         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
817      END SELECT
818
819#endif
820
821      ! 3.3 Write Dirichlet lateral conditions
822
823      ijhom = nlcj-jprecj
824
825      SELECT CASE ( nbondj )
826      CASE ( -1 )
827         DO jl = 1, jprecj
828            ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2)
829         END DO
830      CASE ( 0 ) 
831         DO jl = 1, jprecj
832            ptab(:,jl      ,:) = t3sn(:,jl,:,2)
833            ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2)
834         END DO
835      CASE ( 1 )
836         DO jl = 1, jprecj
837            ptab(:,jl,:) = t3sn(:,jl,:,2)
838         END DO
839      END SELECT
840
841
842      ! 4. north fold treatment
843      ! -----------------------
844
845      IF (PRESENT(cd_mpp)) THEN
846         ! No north fold treatment (it is assumed to be already OK)
847     
848      ELSE     
849
850      ! 4.1 treatment without exchange (jpni odd)
851      !     T-point pivot 
852
853      SELECT CASE ( jpni )
854
855      CASE ( 1 )  ! only one proc along I, no mpp exchange
856
857         SELECT CASE ( npolj )
858 
859         CASE ( 3 , 4 )    ! T pivot
860            iloc = jpiglo - 2 * ( nimpp - 1 )
861
862            SELECT CASE ( cd_type )
863
864            CASE ( 'T' , 'S', 'W' )
865               DO jk = 1, jpk
866                  DO ji = 2, nlci
867                     ijt=iloc-ji+2
868                     ptab(ji,nlcj,jk) = psgn * ptab(ijt,nlcj-2,jk)
869                  END DO
870                  DO ji = nlci/2+1, nlci
871                     ijt=iloc-ji+2
872                     ptab(ji,nlcj-1,jk) = psgn * ptab(ijt,nlcj-1,jk)
873                  END DO
874               END DO
875         
876            CASE ( 'U' )
877               DO jk = 1, jpk
878                  DO ji = 1, nlci-1
879                     iju=iloc-ji+1
880                     ptab(ji,nlcj,jk) = psgn * ptab(iju,nlcj-2,jk)
881                  END DO
882                  DO ji = nlci/2, nlci-1
883                     iju=iloc-ji+1
884                     ptab(ji,nlcj-1,jk) = psgn * ptab(iju,nlcj-1,jk)
885                  END DO
886               END DO
887
888            CASE ( 'V' )
889               DO jk = 1, jpk
890                  DO ji = 2, nlci
891                     ijt=iloc-ji+2
892                     ptab(ji,nlcj-1,jk) = psgn * ptab(ijt,nlcj-2,jk)
893                     ptab(ji,nlcj  ,jk) = psgn * ptab(ijt,nlcj-3,jk)
894                  END DO
895               END DO
896
897            CASE ( 'F', 'G' )
898               DO jk = 1, jpk
899                  DO ji = 1, nlci-1
900                     iju=iloc-ji+1
901                     ptab(ji,nlcj-1,jk) = psgn * ptab(iju,nlcj-2,jk)
902                     ptab(ji,nlcj  ,jk) = psgn * ptab(iju,nlcj-3,jk)
903                  END DO
904               END DO
905 
906          END SELECT
907       
908         CASE ( 5 , 6 ) ! F pivot
909            iloc=jpiglo-2*(nimpp-1)
910 
911            SELECT CASE ( cd_type )
912
913            CASE ( 'T' , 'S', 'W' )
914               DO jk = 1, jpk
915                  DO ji = 1, nlci
916                     ijt=iloc-ji+1
917                     ptab(ji,nlcj,jk) = psgn * ptab(ijt,nlcj-1,jk)
918                  END DO
919               END DO
920
921            CASE ( 'U' )
922               DO jk = 1, jpk
923                  DO ji = 1, nlci-1
924                     iju=iloc-ji
925                     ptab(ji,nlcj,jk) = psgn * ptab(iju,nlcj-1,jk)
926                  END DO
927               END DO
928
929            CASE ( 'V' )
930               DO jk = 1, jpk
931                  DO ji = 1, nlci
932                     ijt=iloc-ji+1
933                     ptab(ji,nlcj  ,jk) = psgn * ptab(ijt,nlcj-2,jk)
934                  END DO
935                  DO ji = nlci/2+1, nlci
936                     ijt=iloc-ji+1
937                     ptab(ji,nlcj-1,jk) = psgn * ptab(ijt,nlcj-1,jk)
938                  END DO
939               END DO
940
941            CASE ( 'F', 'G' )
942               DO jk = 1, jpk
943                  DO ji = 1, nlci-1
944                     iju=iloc-ji
945                     ptab(ji,nlcj,jk) = psgn * ptab(iju,nlcj-2,jk)
946                  END DO
947                  DO ji = nlci/2+1, nlci-1
948                     iju=iloc-ji
949                     ptab(ji,nlcj-1,jk) = psgn * ptab(iju,nlcj-1,jk)
950                  END DO
951               END DO
952            END SELECT  ! cd_type
953
954         END SELECT     !  npolj
955 
956      CASE DEFAULT ! more than 1 proc along I
957         IF ( npolj /= 0 ) CALL mpp_lbc_north (ptab, cd_type, psgn)  ! only for northern procs.
958
959      END SELECT ! jpni
960
961      ENDIF
962     
963
964      ! 5. East and west directions exchange
965      ! ------------------------------------
966
967      SELECT CASE ( npolj )
968
969      CASE ( 3, 4, 5, 6 )
970
971         ! 5.1 Read Dirichlet lateral conditions
972
973         SELECT CASE ( nbondi )
974
975         CASE ( -1, 0, 1 )
976            iihom = nlci-nreci
977            DO jl = 1, jpreci
978               t3ew(:,jl,:,1) = ptab(jpreci+jl,:,:)
979               t3we(:,jl,:,1) = ptab(iihom +jl,:,:)
980            END DO
981
982         END SELECT
983
984         ! 5.2 Migrations
985
986#if defined key_mpp_shmem
987         !! SHMEM version
988
989         imigr = jpreci * jpj * jpk
990
991         SELECT CASE ( nbondi )
992         CASE ( -1 )
993            CALL shmem_put( t3we(1,1,1,2), t3we(1,1,1,1), imigr, noea )
994         CASE ( 0 )
995            CALL shmem_put( t3ew(1,1,1,2), t3ew(1,1,1,1), imigr, nowe )
996            CALL shmem_put( t3we(1,1,1,2), t3we(1,1,1,1), imigr, noea )
997         CASE ( 1 )
998            CALL shmem_put( t3ew(1,1,1,2), t3ew(1,1,1,1), imigr, nowe )
999         END SELECT
1000
1001         CALL barrier()
1002         CALL shmem_udcflush()
1003
1004#elif defined key_mpp_mpi
1005         !! MPI version
1006
1007         imigr=jpreci*jpj*jpk
1008 
1009         SELECT CASE ( nbondi )
1010         CASE ( -1 )
1011            CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req1 )
1012            CALL mpprecv( 1, t3ew(1,1,1,2), imigr )
1013            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1014         CASE ( 0 )
1015            CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 )
1016            CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req2 )
1017            CALL mpprecv( 1, t3ew(1,1,1,2), imigr )
1018            CALL mpprecv( 2, t3we(1,1,1,2), imigr )
1019            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1020            IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
1021         CASE ( 1 )
1022            CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 )
1023            CALL mpprecv( 2, t3we(1,1,1,2), imigr )
1024            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1025         END SELECT
1026#endif
1027
1028         ! 5.3 Write Dirichlet lateral conditions
1029
1030         iihom = nlci-jpreci
1031
1032         SELECT CASE ( nbondi)
1033         CASE ( -1 )
1034            DO jl = 1, jpreci
1035               ptab(iihom+jl,:,:) = t3ew(:,jl,:,2)
1036            END DO
1037         CASE ( 0 ) 
1038            DO jl = 1, jpreci
1039               ptab(jl      ,:,:) = t3we(:,jl,:,2)
1040               ptab(iihom+jl,:,:) = t3ew(:,jl,:,2)
1041            END DO
1042         CASE ( 1 )
1043            DO jl = 1, jpreci
1044               ptab(jl      ,:,:) = t3we(:,jl,:,2)
1045            END DO
1046         END SELECT
1047
1048      END SELECT    ! npolj
1049
1050   END SUBROUTINE mpp_lnk_3d
1051
1052
1053   SUBROUTINE mpp_lnk_2d( pt2d, cd_type, psgn, cd_mpp )
1054      !!----------------------------------------------------------------------
1055      !!                  ***  routine mpp_lnk_2d  ***
1056      !!                 
1057      !! ** Purpose :   Message passing manadgement for 2d array
1058      !!
1059      !! ** Method  :   Use mppsend and mpprecv function for passing mask
1060      !!      between processors following neighboring subdomains.
1061      !!            domain parameters
1062      !!                    nlci   : first dimension of the local subdomain
1063      !!                    nlcj   : second dimension of the local subdomain
1064      !!                    nbondi : mark for "east-west local boundary"
1065      !!                    nbondj : mark for "north-south local boundary"
1066      !!                    noea   : number for local neighboring processors
1067      !!                    nowe   : number for local neighboring processors
1068      !!                    noso   : number for local neighboring processors
1069      !!                    nono   : number for local neighboring processors
1070      !!
1071      !!----------------------------------------------------------------------
1072      !! * Arguments
1073      CHARACTER(len=1) , INTENT( in ) ::   &
1074         cd_type       ! define the nature of pt2d array grid-points
1075         !             !  = T , U , V , F , W
1076         !             !  = S : T-point, north fold treatment
1077         !             !  = G : F-point, north fold treatment
1078         !             !  = I : sea-ice velocity at F-point with index shift
1079      REAL(wp), INTENT( in ) ::   &
1080         psgn          ! control of the sign change
1081         !             !   = -1. , the sign is changed if north fold boundary
1082         !             !   =  1. , the sign is kept  if north fold boundary
1083      REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) ::   &
1084         pt2d          ! 2D array on which the boundary condition is applied
1085      CHARACTER(len=3), INTENT( in ), OPTIONAL ::    &
1086         cd_mpp        ! fill the overlap area only
1087
1088      !! * Local variables
1089      INTEGER  ::   ji, jj, jl      ! dummy loop indices
1090      INTEGER  ::   &
1091         imigr, iihom, ijhom,    &  ! temporary integers
1092         iloc, ijt, iju             !    "          "
1093      INTEGER  ::   ml_req1, ml_req2, ml_err     ! for key_mpi_isend
1094      INTEGER  ::   ml_stat(MPI_STATUS_SIZE)     ! for key_mpi_isend
1095      !!----------------------------------------------------------------------
1096
1097      ! 1. standard boundary treatment
1098      ! ------------------------------
1099      IF (PRESENT(cd_mpp)) THEN
1100         DO jj = nlcj+1, jpj   ! only fill extra allows last line
1101            pt2d(1:nlci, jj) = pt2d(1:nlci, nlej)
1102         END DO
1103         DO ji = nlci+1, jpi   ! only fill extra allows last column
1104            pt2d(ji    , : ) = pt2d(nlei  , :   )
1105         END DO     
1106      ELSE     
1107
1108         !                                        ! East-West boundaries
1109         !                                        ! ====================
1110         IF( nbondi == 2 .AND.   &      ! Cyclic east-west
1111            &    (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
1112            pt2d( 1 ,:) = pt2d(jpim1,:)
1113            pt2d(jpi,:) = pt2d(  2  ,:)
1114
1115         ELSE                           ! ... closed
1116            SELECT CASE ( cd_type )
1117            CASE ( 'T', 'U', 'V', 'W' , 'I' )
1118               pt2d(     1       :jpreci,:) = 0.e0
1119               pt2d(nlci-jpreci+1:jpi   ,:) = 0.e0
1120            CASE ( 'F' )
1121               pt2d(nlci-jpreci+1:jpi   ,:) = 0.e0
1122            END SELECT
1123         ENDIF
1124
1125         !                                        ! North-South boundaries
1126         !                                        ! ======================
1127         SELECT CASE ( cd_type )
1128         CASE ( 'T', 'U', 'V', 'W' , 'I' )
1129            pt2d(:,     1       :jprecj) = 0.e0
1130            pt2d(:,nlcj-jprecj+1:jpj   ) = 0.e0
1131         CASE ( 'F' )
1132            pt2d(:,nlcj-jprecj+1:jpj   ) = 0.e0
1133         END SELECT
1134
1135      ENDIF
1136
1137
1138      ! 2. East and west directions
1139      ! ---------------------------
1140
1141      ! 2.1 Read Dirichlet lateral conditions
1142
1143      SELECT CASE ( nbondi )
1144      CASE ( -1, 0, 1 )    ! all except 2
1145         iihom = nlci-nreci
1146         DO jl = 1, jpreci
1147            t2ew(:,jl,1) = pt2d(jpreci+jl,:)
1148            t2we(:,jl,1) = pt2d(iihom +jl,:)
1149         END DO
1150      END SELECT
1151
1152      ! 2.2 Migrations
1153
1154#if defined key_mpp_shmem
1155      !! * SHMEM version
1156
1157      imigr = jpreci * jpj
1158
1159      SELECT CASE ( nbondi )
1160      CASE ( -1 )
1161         CALL shmem_put( t2we(1,1,2), t2we(1,1,1), imigr, noea )
1162      CASE ( 0 )
1163         CALL shmem_put( t2ew(1,1,2), t2ew(1,1,1), imigr, nowe )
1164         CALL shmem_put( t2we(1,1,2), t2we(1,1,1), imigr, noea )
1165      CASE ( 1 )
1166         CALL shmem_put( t2ew(1,1,2), t2ew(1,1,1), imigr, nowe )
1167      END SELECT
1168
1169      CALL barrier()
1170      CALL shmem_udcflush()
1171
1172#elif defined key_mpp_mpi
1173      !! * MPI version
1174
1175      imigr = jpreci * jpj
1176
1177      SELECT CASE ( nbondi )
1178      CASE ( -1 )
1179         CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req1 )
1180         CALL mpprecv( 1, t2ew(1,1,2), imigr )
1181         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1182      CASE ( 0 )
1183         CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 )
1184         CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req2 )
1185         CALL mpprecv( 1, t2ew(1,1,2), imigr )
1186         CALL mpprecv( 2, t2we(1,1,2), imigr )
1187         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1188         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
1189      CASE ( 1 )
1190         CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 )
1191         CALL mpprecv( 2, t2we(1,1,2), imigr )
1192         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1193      END SELECT
1194
1195#endif
1196
1197      ! 2.3 Write Dirichlet lateral conditions
1198
1199      iihom = nlci - jpreci
1200      SELECT CASE ( nbondi )
1201      CASE ( -1 )
1202         DO jl = 1, jpreci
1203            pt2d(iihom+jl,:) = t2ew(:,jl,2)
1204         END DO
1205      CASE ( 0 )
1206         DO jl = 1, jpreci
1207            pt2d(jl      ,:) = t2we(:,jl,2)
1208            pt2d(iihom+jl,:) = t2ew(:,jl,2)
1209         END DO
1210      CASE ( 1 )
1211         DO jl = 1, jpreci
1212            pt2d(jl      ,:) = t2we(:,jl,2)
1213         END DO
1214      END SELECT
1215
1216
1217      ! 3. North and south directions
1218      ! -----------------------------
1219
1220      ! 3.1 Read Dirichlet lateral conditions
1221
1222      IF( nbondj /= 2 ) THEN
1223         ijhom = nlcj-nrecj
1224         DO jl = 1, jprecj
1225            t2sn(:,jl,1) = pt2d(:,ijhom +jl)
1226            t2ns(:,jl,1) = pt2d(:,jprecj+jl)
1227         END DO
1228      ENDIF
1229
1230      ! 3.2 Migrations
1231
1232#if defined key_mpp_shmem
1233      !! * SHMEM version
1234
1235      imigr = jprecj * jpi
1236
1237      SELECT CASE ( nbondj )
1238      CASE ( -1 )
1239         CALL shmem_put( t2sn(1,1,2), t2sn(1,1,1), imigr, nono )
1240      CASE ( 0 )
1241         CALL shmem_put( t2ns(1,1,2), t2ns(1,1,1), imigr, noso )
1242         CALL shmem_put( t2sn(1,1,2), t2sn(1,1,1), imigr, nono )
1243      CASE ( 1 )
1244         CALL shmem_put( t2ns(1,1,2), t2ns(1,1,1), imigr, noso )
1245      END SELECT
1246      CALL barrier()
1247      CALL shmem_udcflush()
1248
1249#elif defined key_mpp_mpi
1250      !! * MPI version
1251
1252      imigr = jprecj * jpi
1253
1254      SELECT CASE ( nbondj )
1255      CASE ( -1 )
1256         CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req1 )
1257         CALL mpprecv( 3, t2ns(1,1,2), imigr )
1258         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1259      CASE ( 0 )
1260         CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 )
1261         CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req2 )
1262         CALL mpprecv( 3, t2ns(1,1,2), imigr )
1263         CALL mpprecv( 4, t2sn(1,1,2), imigr )
1264         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1265         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
1266      CASE ( 1 )
1267         CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 )
1268         CALL mpprecv( 4, t2sn(1,1,2), imigr )
1269         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1270      END SELECT
1271 
1272#endif
1273
1274      ! 3.3 Write Dirichlet lateral conditions
1275
1276      ijhom = nlcj - jprecj
1277
1278      SELECT CASE ( nbondj )
1279      CASE ( -1 )
1280         DO jl = 1, jprecj
1281            pt2d(:,ijhom+jl) = t2ns(:,jl,2)
1282         END DO
1283      CASE ( 0 )
1284         DO jl = 1, jprecj
1285            pt2d(:,jl      ) = t2sn(:,jl,2)
1286            pt2d(:,ijhom+jl) = t2ns(:,jl,2)
1287         END DO
1288      CASE ( 1 ) 
1289         DO jl = 1, jprecj
1290            pt2d(:,jl      ) = t2sn(:,jl,2)
1291         END DO
1292      END SELECT 
1293 
1294
1295      ! 4. north fold treatment
1296      ! -----------------------
1297 
1298      IF (PRESENT(cd_mpp)) THEN
1299         ! No north fold treatment (it is assumed to be already OK)
1300     
1301      ELSE     
1302
1303      ! 4.1 treatment without exchange (jpni odd)
1304     
1305      SELECT CASE ( jpni )
1306 
1307      CASE ( 1 ) ! only one proc along I, no mpp exchange
1308 
1309         SELECT CASE ( npolj )
1310 
1311         CASE ( 3 , 4 )   !  T pivot
1312            iloc = jpiglo - 2 * ( nimpp - 1 )
1313 
1314            SELECT CASE ( cd_type )
1315 
1316            CASE ( 'T' , 'S', 'W' )
1317               DO ji = 2, nlci
1318                  ijt=iloc-ji+2
1319                  pt2d(ji,nlcj) = psgn * pt2d(ijt,nlcj-2)
1320               END DO
1321               DO ji = nlci/2+1, nlci
1322                  ijt=iloc-ji+2
1323                  pt2d(ji,nlcj-1) = psgn * pt2d(ijt,nlcj-1)
1324               END DO
1325 
1326            CASE ( 'U' )
1327               DO ji = 1, nlci-1
1328                  iju=iloc-ji+1
1329                  pt2d(ji,nlcj) = psgn * pt2d(iju,nlcj-2)
1330               END DO
1331               DO ji = nlci/2, nlci-1
1332                  iju=iloc-ji+1
1333                  pt2d(ji,nlcj-1) = psgn * pt2d(iju,nlcj-1)
1334               END DO
1335 
1336            CASE ( 'V' )
1337               DO ji = 2, nlci
1338                  ijt=iloc-ji+2
1339                  pt2d(ji,nlcj-1) = psgn * pt2d(ijt,nlcj-2)
1340                  pt2d(ji,nlcj  ) = psgn * pt2d(ijt,nlcj-3)
1341               END DO
1342 
1343            CASE ( 'F', 'G' )
1344               DO ji = 1, nlci-1
1345                  iju=iloc-ji+1
1346                  pt2d(ji,nlcj-1) = psgn * pt2d(iju,nlcj-2)
1347                  pt2d(ji,nlcj  ) = psgn * pt2d(iju,nlcj-3)
1348               END DO
1349 
1350            CASE ( 'I' )                                  ! ice U-V point
1351               pt2d(2,nlcj) = psgn * pt2d(3,nlcj-1)
1352               DO ji = 3, nlci
1353                  iju = iloc - ji + 3
1354                  pt2d(ji,nlcj) = psgn * pt2d(iju,nlcj-1)
1355               END DO
1356 
1357            END SELECT
1358 
1359         CASE ( 5 , 6 )                 ! F pivot
1360            iloc=jpiglo-2*(nimpp-1)
1361 
1362            SELECT CASE (cd_type )
1363 
1364            CASE ( 'T', 'S', 'W' )
1365               DO ji = 1, nlci
1366                  ijt=iloc-ji+1
1367                  pt2d(ji,nlcj) = psgn * pt2d(ijt,nlcj-1)
1368               END DO
1369 
1370            CASE ( 'U' )
1371               DO ji = 1, nlci-1
1372                  iju=iloc-ji
1373                  pt2d(ji,nlcj) = psgn * pt2d(iju,nlcj-1)
1374               END DO
1375
1376            CASE ( 'V' )
1377               DO ji = 1, nlci
1378                  ijt=iloc-ji+1
1379                  pt2d(ji,nlcj  ) = psgn * pt2d(ijt,nlcj-2)
1380               END DO
1381               DO ji = nlci/2+1, nlci
1382                  ijt=iloc-ji+1
1383                  pt2d(ji,nlcj-1) = psgn * pt2d(ijt,nlcj-1)
1384               END DO
1385 
1386            CASE ( 'F', 'G' )
1387               DO ji = 1, nlci-1
1388                  iju=iloc-ji
1389                  pt2d(ji,nlcj) = psgn * pt2d(iju,nlcj-2)
1390               END DO
1391               DO ji = nlci/2+1, nlci-1
1392                  iju=iloc-ji
1393                  pt2d(ji,nlcj-1) = psgn * pt2d(iju,nlcj-1)
1394               END DO
1395 
1396            CASE ( 'I' )                                  ! ice U-V point
1397               pt2d( 2 ,nlcj) = 0.e0
1398               DO ji = 2 , nlci-1
1399                  ijt = iloc - ji + 2
1400                  pt2d(ji,nlcj)= 0.5 * ( pt2d(ji,nlcj-1) + psgn * pt2d(ijt,nlcj-1) )
1401               END DO
1402 
1403            END SELECT   ! cd_type
1404 
1405         END SELECT   ! npolj
1406
1407      CASE DEFAULT   ! more than 1 proc along I
1408         IF( npolj /= 0 )   CALL mpp_lbc_north( pt2d, cd_type, psgn )   ! only for northern procs.
1409
1410      END SELECT   ! jpni
1411
1412      ENDIF
1413
1414      ! 5. East and west directions
1415      ! ---------------------------
1416
1417      SELECT CASE ( npolj )
1418
1419      CASE ( 3, 4, 5, 6 )
1420
1421         ! 5.1 Read Dirichlet lateral conditions
1422
1423         SELECT CASE ( nbondi )
1424         CASE ( -1, 0, 1 )
1425            iihom = nlci-nreci
1426            DO jl = 1, jpreci
1427               DO jj = 1, jpj
1428                  t2ew(jj,jl,1) = pt2d(jpreci+jl,jj)
1429                  t2we(jj,jl,1) = pt2d(iihom +jl,jj)
1430               END DO
1431            END DO
1432         END SELECT
1433
1434         ! 5.2 Migrations
1435
1436#if defined key_mpp_shmem
1437         !! * SHMEM version
1438
1439         imigr=jpreci*jpj
1440
1441         SELECT CASE ( nbondi )
1442         CASE ( -1 )
1443            CALL shmem_put( t2we(1,1,2), t2we(1,1,1), imigr, noea )
1444         CASE ( 0 )
1445            CALL shmem_put( t2ew(1,1,2), t2ew(1,1,1), imigr, nowe )
1446            CALL shmem_put( t2we(1,1,2), t2we(1,1,1), imigr, noea )
1447         CASE ( 1 )
1448            CALL shmem_put( t2ew(1,1,2), t2ew(1,1,1), imigr, nowe )
1449         END SELECT
1450
1451         CALL barrier()
1452         CALL shmem_udcflush()
1453 
1454#elif defined key_mpp_mpi
1455         !! * MPI version
1456 
1457         imigr=jpreci*jpj
1458 
1459         SELECT CASE ( nbondi )
1460         CASE ( -1 )
1461            CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req1 )
1462            CALL mpprecv( 1, t2ew(1,1,2), imigr )
1463            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1464         CASE ( 0 )
1465            CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 )
1466            CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req2 )
1467            CALL mpprecv( 1, t2ew(1,1,2), imigr )
1468            CALL mpprecv( 2, t2we(1,1,2), imigr )
1469            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1470            IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
1471         CASE ( 1 )
1472            CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 )
1473            CALL mpprecv( 2, t2we(1,1,2), imigr )
1474            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
1475         END SELECT 
1476#endif
1477
1478         ! 5.3 Write Dirichlet lateral conditions
1479 
1480         iihom = nlci - jpreci
1481 
1482         SELECT CASE ( nbondi )
1483         CASE ( -1 )
1484            DO jl = 1, jpreci
1485               pt2d(iihom+jl,:) = t2ew(:,jl,2)
1486            END DO
1487         CASE ( 0 )
1488            DO jl = 1, jpreci
1489               pt2d(jl      ,:) = t2we(:,jl,2)
1490               pt2d(iihom+jl,:) = t2ew(:,jl,2)
1491            END DO
1492         CASE ( 1 )
1493            DO jl = 1, jpreci
1494               pt2d(jl,:) = t2we(:,jl,2)
1495            END DO
1496         END SELECT
1497 
1498      END SELECT   ! npolj
1499 
1500   END SUBROUTINE mpp_lnk_2d
1501
1502
1503   SUBROUTINE mpp_lnk_3d_gather( ptab1, cd_type1, ptab2, cd_type2, psgn )
1504      !!----------------------------------------------------------------------
1505      !!                  ***  routine mpp_lnk_3d_gather  ***
1506      !!
1507      !! ** Purpose :   Message passing manadgement for two 3D arrays
1508      !!
1509      !! ** Method  :   Use mppsend and mpprecv function for passing mask
1510      !!      between processors following neighboring subdomains.
1511      !!            domain parameters
1512      !!                    nlci   : first dimension of the local subdomain
1513      !!                    nlcj   : second dimension of the local subdomain
1514      !!                    nbondi : mark for "east-west local boundary"
1515      !!                    nbondj : mark for "north-south local boundary"
1516      !!                    noea   : number for local neighboring processors
1517      !!                    nowe   : number for local neighboring processors
1518      !!                    noso   : number for local neighboring processors
1519      !!                    nono   : number for local neighboring processors
1520      !!
1521      !! ** Action  :   ptab1 and ptab2  with update value at its periphery
1522      !!
1523      !!----------------------------------------------------------------------
1524      !! * Arguments
1525      CHARACTER(len=1) , INTENT( in ) ::   &
1526         cd_type1, cd_type2       ! define the nature of ptab array grid-points
1527         !                        ! = T , U , V , F , W points
1528         !                        ! = S : T-point, north fold treatment ???
1529         !                        ! = G : F-point, north fold treatment ???
1530      REAL(wp), INTENT( in ) ::   &
1531         psgn          ! control of the sign change
1532         !             !   = -1. , the sign is changed if north fold boundary
1533         !             !   =  1. , the sign is kept  if north fold boundary
1534      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   &
1535         ptab1, ptab2             ! 3D array on which the boundary condition is applied
1536
1537      !! * Local variables
1538      INTEGER ::   ji, jk, jl   ! dummy loop indices
1539      INTEGER ::   imigr, iihom, ijhom, iloc, ijt, iju   ! temporary integers
1540      INTEGER ::   ml_req1, ml_req2, ml_err     ! for key_mpi_isend
1541      INTEGER ::   ml_stat(MPI_STATUS_SIZE)     ! for key_mpi_isend
1542      !!----------------------------------------------------------------------
1543
1544      ! 1. standard boundary treatment
1545      ! ------------------------------
1546      !                                        ! East-West boundaries
1547      !                                        ! ====================
1548      IF( nbondi == 2 .AND.   &      ! Cyclic east-west
1549         &   (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
1550         ptab1( 1 ,:,:) = ptab1(jpim1,:,:)
1551         ptab1(jpi,:,:) = ptab1(  2  ,:,:)
1552         ptab2( 1 ,:,:) = ptab2(jpim1,:,:)
1553         ptab2(jpi,:,:) = ptab2(  2  ,:,:)
1554
1555      ELSE                           ! closed
1556         SELECT CASE ( cd_type1 )
1557         CASE ( 'T', 'U', 'V', 'W' )
1558            ptab1(     1       :jpreci,:,:) = 0.e0
1559            ptab1(nlci-jpreci+1:jpi   ,:,:) = 0.e0
1560         CASE ( 'F' )
1561            ptab1(nlci-jpreci+1:jpi   ,:,:) = 0.e0
1562         END SELECT
1563         SELECT CASE ( cd_type2 )
1564         CASE ( 'T', 'U', 'V', 'W' )
1565            ptab2(     1       :jpreci,:,:) = 0.e0
1566            ptab2(nlci-jpreci+1:jpi   ,:,:) = 0.e0
1567         CASE ( 'F' )
1568            ptab2(nlci-jpreci+1:jpi   ,:,:) = 0.e0
1569         END SELECT
1570      ENDIF
1571
1572      !                                        ! North-South boundaries
1573      !                                        ! ======================
1574      SELECT CASE ( cd_type1 )
1575      CASE ( 'T', 'U', 'V', 'W' )
1576         ptab1(:,     1       :jprecj,:) = 0.e0
1577         ptab1(:,nlcj-jprecj+1:jpj   ,:) = 0.e0
1578      CASE ( 'F' )
1579         ptab1(:,nlcj-jprecj+1:jpj   ,:) = 0.e0
1580      END SELECT
1581
1582      SELECT CASE ( cd_type2 )
1583      CASE ( 'T', 'U', 'V', 'W' )
1584         ptab2(:,     1       :jprecj,:) = 0.e0
1585         ptab2(:,nlcj-jprecj+1:jpj   ,:) = 0.e0
1586      CASE ( 'F' )
1587         ptab2(:,nlcj-jprecj+1:jpj   ,:) = 0.e0
1588      END SELECT
1589
1590
1591      ! 2. East and west directions exchange
1592      ! ------------------------------------
1593
1594      ! 2.1 Read Dirichlet lateral conditions
1595
1596      SELECT CASE ( nbondi )
1597      CASE ( -1, 0, 1 )    ! all exept 2
1598         iihom = nlci-nreci
1599         DO jl = 1, jpreci
1600            t4ew(:,jl,:,1,1) = ptab1(jpreci+jl,:,:)
1601            t4we(:,jl,:,1,1) = ptab1(iihom +jl,:,:)
1602            t4ew(:,jl,:,2,1) = ptab2(jpreci+jl,:,:)
1603            t4we(:,jl,:,2,1) = ptab2(iihom +jl,:,:)
1604         END DO
1605      END SELECT
1606
1607      ! 2.2 Migrations
1608
1609#if defined key_mpp_shmem
1610      !! * SHMEM version
1611
1612      imigr = jpreci * jpj * jpk *2
1613
1614      SELECT CASE ( nbondi )
1615      CASE ( -1 )
1616         CALL shmem_put( t4we(1,1,1,1,2), t4we(1,1,1,1,1), imigr, noea )
1617      CASE ( 0 )
1618         CALL shmem_put( t4ew(1,1,1,1,2), t4ew(1,1,1,1,1), imigr, nowe )
1619         CALL shmem_put( t4we(1,1,1,1,2), t4we(1,1,1,1,1), imigr, noea )
1620      CASE ( 1 )
1621         CALL shmem_put( t4ew(1,1,1,1,2), t4ew(1,1,1,1,1), imigr, nowe )
1622      END SELECT
1623
1624      CALL barrier()
1625      CALL shmem_udcflush()
1626
1627#elif defined key_mpp_mpi
1628      !! * Local variables   (MPI version)
1629
1630      imigr = jpreci * jpj * jpk *2
1631
1632      SELECT CASE ( nbondi ) 
1633      CASE ( -1 )
1634         CALL mppsend( 2, t4we(1,1,1,1,1), imigr, noea, ml_req1 )
1635         CALL mpprecv( 1, t4ew(1,1,1,1,2), imigr )
1636         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
1637      CASE ( 0 )
1638         CALL mppsend( 1, t4ew(1,1,1,1,1), imigr, nowe, ml_req1 )
1639         CALL mppsend( 2, t4we(1,1,1,1,1), imigr, noea, ml_req2 )
1640         CALL mpprecv( 1, t4ew(1,1,1,1,2), imigr )
1641         CALL mpprecv( 2, t4we(1,1,1,1,2), imigr )
1642         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
1643         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
1644      CASE ( 1 )
1645         CALL mppsend( 1, t4ew(1,1,1,1,1), imigr, nowe, ml_req1 )
1646         CALL mpprecv( 2, t4we(1,1,1,1,2), imigr )
1647         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
1648      END SELECT
1649#endif
1650
1651      ! 2.3 Write Dirichlet lateral conditions
1652
1653      iihom = nlci-jpreci
1654
1655      SELECT CASE ( nbondi )
1656      CASE ( -1 )
1657         DO jl = 1, jpreci
1658            ptab1(iihom+jl,:,:) = t4ew(:,jl,:,1,2)
1659            ptab2(iihom+jl,:,:) = t4ew(:,jl,:,2,2)
1660         END DO
1661      CASE ( 0 ) 
1662         DO jl = 1, jpreci
1663            ptab1(jl      ,:,:) = t4we(:,jl,:,1,2)
1664            ptab1(iihom+jl,:,:) = t4ew(:,jl,:,1,2)
1665            ptab2(jl      ,:,:) = t4we(:,jl,:,2,2)
1666            ptab2(iihom+jl,:,:) = t4ew(:,jl,:,2,2)
1667         END DO
1668      CASE ( 1 )
1669         DO jl = 1, jpreci
1670            ptab1(jl      ,:,:) = t4we(:,jl,:,1,2)
1671            ptab2(jl      ,:,:) = t4we(:,jl,:,2,2)
1672         END DO
1673      END SELECT
1674
1675
1676      ! 3. North and south directions
1677      ! -----------------------------
1678
1679      ! 3.1 Read Dirichlet lateral conditions
1680
1681      IF( nbondj /= 2 ) THEN
1682         ijhom = nlcj-nrecj
1683         DO jl = 1, jprecj
1684            t4sn(:,jl,:,1,1) = ptab1(:,ijhom +jl,:)
1685            t4ns(:,jl,:,1,1) = ptab1(:,jprecj+jl,:)
1686            t4sn(:,jl,:,2,1) = ptab2(:,ijhom +jl,:)
1687            t4ns(:,jl,:,2,1) = ptab2(:,jprecj+jl,:)
1688         END DO
1689      ENDIF
1690
1691      ! 3.2 Migrations
1692
1693#if defined key_mpp_shmem
1694      !! * SHMEM version
1695
1696      imigr = jprecj * jpi * jpk * 2
1697
1698      SELECT CASE ( nbondj )
1699      CASE ( -1 )
1700         CALL shmem_put( t4sn(1,1,1,1,2), t4sn(1,1,1,1,1), imigr, nono )
1701      CASE ( 0 )
1702         CALL shmem_put( t4ns(1,1,1,1,2), t4ns(1,1,1,1,1), imigr, noso )
1703         CALL shmem_put( t4sn(1,1,1,1,2), t4sn(1,1,1,1,1), imigr, nono )
1704      CASE ( 1 )
1705         CALL shmem_put( t4ns(1,1,1,1,2), t4ns(1,1,1,1;,1), imigr, noso )
1706      END SELECT
1707
1708      CALL barrier()
1709      CALL shmem_udcflush()
1710
1711#elif defined key_mpp_mpi
1712      !! * Local variables   (MPI version)
1713 
1714      imigr=jprecj * jpi * jpk * 2
1715
1716      SELECT CASE ( nbondj )     
1717      CASE ( -1 )
1718         CALL mppsend( 4, t4sn(1,1,1,1,1), imigr, nono, ml_req1 )
1719         CALL mpprecv( 3, t4ns(1,1,1,1,2), imigr )
1720         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
1721      CASE ( 0 )
1722         CALL mppsend( 3, t4ns(1,1,1,1,1), imigr, noso, ml_req1 )
1723         CALL mppsend( 4, t4sn(1,1,1,1,1), imigr, nono, ml_req2 )
1724         CALL mpprecv( 3, t4ns(1,1,1,1,2), imigr )
1725         CALL mpprecv( 4, t4sn(1,1,1,1,2), imigr )
1726         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
1727         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err)
1728      CASE ( 1 ) 
1729         CALL mppsend( 3, t4ns(1,1,1,1,1), imigr, noso, ml_req1 )
1730         CALL mpprecv( 4, t4sn(1,1,1,1,2), imigr )
1731         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err)
1732      END SELECT
1733
1734#endif
1735
1736      ! 3.3 Write Dirichlet lateral conditions
1737
1738      ijhom = nlcj-jprecj
1739
1740      SELECT CASE ( nbondj )
1741      CASE ( -1 )
1742         DO jl = 1, jprecj
1743            ptab1(:,ijhom+jl,:) = t4ns(:,jl,:,1,2)
1744            ptab2(:,ijhom+jl,:) = t4ns(:,jl,:,2,2)
1745         END DO
1746      CASE ( 0 ) 
1747         DO jl = 1, jprecj
1748            ptab1(:,jl      ,:) = t4sn(:,jl,:,1,2)
1749            ptab1(:,ijhom+jl,:) = t4ns(:,jl,:,1,2)
1750            ptab2(:,jl      ,:) = t4sn(:,jl,:,2,2)
1751            ptab2(:,ijhom+jl,:) = t4ns(:,jl,:,2,2)
1752         END DO
1753      CASE ( 1 )
1754         DO jl = 1, jprecj
1755            ptab1(:,jl,:) = t4sn(:,jl,:,1,2)
1756            ptab2(:,jl,:) = t4sn(:,jl,:,2,2)
1757         END DO
1758      END SELECT
1759
1760
1761      ! 4. north fold treatment
1762      ! -----------------------
1763
1764      ! 4.1 treatment without exchange (jpni odd)
1765      !     T-point pivot 
1766
1767      SELECT CASE ( jpni )
1768
1769      CASE ( 1 )  ! only one proc along I, no mpp exchange
1770
1771      SELECT CASE ( npolj )
1772 
1773         CASE ( 3 , 4 )    ! T pivot
1774            iloc = jpiglo - 2 * ( nimpp - 1 )
1775
1776            SELECT CASE ( cd_type1 )
1777
1778            CASE ( 'T' , 'S', 'W' )
1779               DO jk = 1, jpk
1780                  DO ji = 2, nlci
1781                     ijt=iloc-ji+2
1782                     ptab1(ji,nlcj,jk) = psgn * ptab1(ijt,nlcj-2,jk)
1783                  END DO
1784                  DO ji = nlci/2+1, nlci
1785                     ijt=iloc-ji+2
1786                     ptab1(ji,nlcj-1,jk) = psgn * ptab1(ijt,nlcj-1,jk)
1787                  END DO
1788               END DO
1789         
1790            CASE ( 'U' )
1791               DO jk = 1, jpk
1792                  DO ji = 1, nlci-1
1793                     iju=iloc-ji+1
1794                     ptab1(ji,nlcj,jk) = psgn * ptab1(iju,nlcj-2,jk)
1795                  END DO
1796                  DO ji = nlci/2, nlci-1
1797                     iju=iloc-ji+1
1798                     ptab1(ji,nlcj-1,jk) = psgn * ptab1(iju,nlcj-1,jk)
1799                  END DO
1800               END DO
1801
1802            CASE ( 'V' )
1803               DO jk = 1, jpk
1804                  DO ji = 2, nlci
1805                     ijt=iloc-ji+2
1806                     ptab1(ji,nlcj-1,jk) = psgn * ptab1(ijt,nlcj-2,jk)
1807                     ptab1(ji,nlcj  ,jk) = psgn * ptab1(ijt,nlcj-3,jk)
1808                  END DO
1809               END DO
1810
1811            CASE ( 'F', 'G' )
1812               DO jk = 1, jpk
1813                  DO ji = 1, nlci-1
1814                     iju=iloc-ji+1
1815                     ptab1(ji,nlcj-1,jk) = psgn * ptab1(iju,nlcj-2,jk)
1816                     ptab1(ji,nlcj  ,jk) = psgn * ptab1(iju,nlcj-3,jk)
1817                  END DO
1818               END DO
1819 
1820            END SELECT
1821           
1822            SELECT CASE ( cd_type2 )
1823
1824            CASE ( 'T' , 'S', 'W' )
1825               DO jk = 1, jpk
1826                  DO ji = 2, nlci
1827                     ijt=iloc-ji+2
1828                     ptab2(ji,nlcj,jk) = psgn * ptab2(ijt,nlcj-2,jk)
1829                  END DO
1830                  DO ji = nlci/2+1, nlci
1831                     ijt=iloc-ji+2
1832                     ptab2(ji,nlcj-1,jk) = psgn * ptab2(ijt,nlcj-1,jk)
1833                  END DO
1834               END DO
1835         
1836            CASE ( 'U' )
1837               DO jk = 1, jpk
1838                  DO ji = 1, nlci-1
1839                     iju=iloc-ji+1
1840                     ptab2(ji,nlcj,jk) = psgn * ptab2(iju,nlcj-2,jk)
1841                  END DO
1842                  DO ji = nlci/2, nlci-1
1843                     iju=iloc-ji+1
1844                     ptab2(ji,nlcj-1,jk) = psgn * ptab2(iju,nlcj-1,jk)
1845                  END DO
1846               END DO
1847
1848            CASE ( 'V' )
1849               DO jk = 1, jpk
1850                  DO ji = 2, nlci
1851                     ijt=iloc-ji+2
1852                     ptab2(ji,nlcj-1,jk) = psgn * ptab2(ijt,nlcj-2,jk)
1853                     ptab2(ji,nlcj  ,jk) = psgn * ptab2(ijt,nlcj-3,jk)
1854                  END DO
1855               END DO
1856
1857            CASE ( 'F', 'G' )
1858               DO jk = 1, jpk
1859                  DO ji = 1, nlci-1
1860                     iju=iloc-ji+1
1861                     ptab2(ji,nlcj-1,jk) = psgn * ptab2(iju,nlcj-2,jk)
1862                     ptab2(ji,nlcj  ,jk) = psgn * ptab2(iju,nlcj-3,jk)
1863                  END DO
1864               END DO
1865 
1866          END SELECT
1867       
1868         CASE ( 5 , 6 ) ! F pivot
1869            iloc=jpiglo-2*(nimpp-1)
1870 
1871            SELECT CASE ( cd_type1 )
1872
1873            CASE ( 'T' , 'S', 'W' )
1874               DO jk = 1, jpk
1875                  DO ji = 1, nlci
1876                     ijt=iloc-ji+1
1877                     ptab1(ji,nlcj,jk) = psgn * ptab1(ijt,nlcj-1,jk)
1878                  END DO
1879               END DO
1880
1881            CASE ( 'U' )
1882               DO jk = 1, jpk
1883                  DO ji = 1, nlci-1
1884                     iju=iloc-ji
1885                     ptab1(ji,nlcj,jk) = psgn * ptab1(iju,nlcj-1,jk)
1886                  END DO
1887               END DO
1888
1889            CASE ( 'V' )
1890               DO jk = 1, jpk
1891                  DO ji = 1, nlci
1892                     ijt=iloc-ji+1
1893                     ptab1(ji,nlcj  ,jk) = psgn * ptab1(ijt,nlcj-2,jk)
1894                  END DO
1895                  DO ji = nlci/2+1, nlci
1896                     ijt=iloc-ji+1
1897                     ptab1(ji,nlcj-1,jk) = psgn * ptab1(ijt,nlcj-1,jk)
1898                  END DO
1899               END DO
1900
1901            CASE ( 'F', 'G' )
1902               DO jk = 1, jpk
1903                  DO ji = 1, nlci-1
1904                     iju=iloc-ji
1905                     ptab1(ji,nlcj,jk) = psgn * ptab1(iju,nlcj-2,jk)
1906                  END DO
1907                  DO ji = nlci/2+1, nlci-1
1908                     iju=iloc-ji
1909                     ptab1(ji,nlcj-1,jk) = psgn * ptab1(iju,nlcj-1,jk)
1910                  END DO
1911               END DO
1912            END SELECT  ! cd_type1
1913
1914            SELECT CASE ( cd_type2 )
1915
1916            CASE ( 'T' , 'S', 'W' )
1917               DO jk = 1, jpk
1918                  DO ji = 1, nlci
1919                     ijt=iloc-ji+1
1920                     ptab2(ji,nlcj,jk) = psgn * ptab2(ijt,nlcj-1,jk)
1921                  END DO
1922               END DO
1923
1924            CASE ( 'U' )
1925               DO jk = 1, jpk
1926                  DO ji = 1, nlci-1
1927                     iju=iloc-ji
1928                     ptab2(ji,nlcj,jk) = psgn * ptab2(iju,nlcj-1,jk)
1929                  END DO
1930               END DO
1931
1932            CASE ( 'V' )
1933               DO jk = 1, jpk
1934                  DO ji = 1, nlci
1935                     ijt=iloc-ji+1
1936                     ptab2(ji,nlcj  ,jk) = psgn * ptab2(ijt,nlcj-2,jk)
1937                  END DO
1938                  DO ji = nlci/2+1, nlci
1939                     ijt=iloc-ji+1
1940                     ptab2(ji,nlcj-1,jk) = psgn * ptab2(ijt,nlcj-1,jk)
1941                  END DO
1942               END DO
1943
1944            CASE ( 'F', 'G' )
1945               DO jk = 1, jpk
1946                  DO ji = 1, nlci-1
1947                     iju=iloc-ji
1948                     ptab2(ji,nlcj,jk) = psgn * ptab2(iju,nlcj-2,jk)
1949                  END DO
1950                  DO ji = nlci/2+1, nlci-1
1951                     iju=iloc-ji
1952                     ptab2(ji,nlcj-1,jk) = psgn * ptab2(iju,nlcj-1,jk)
1953                  END DO
1954               END DO
1955
1956            END SELECT  ! cd_type2
1957
1958         END SELECT     !  npolj
1959 
1960      CASE DEFAULT ! more than 1 proc along I
1961         IF ( npolj /= 0 ) THEN
1962            CALL mpp_lbc_north (ptab1, cd_type1, psgn)  ! only for northern procs.
1963            CALL mpp_lbc_north (ptab2, cd_type2, psgn)  ! only for northern procs.
1964         ENDIF
1965
1966      END SELECT ! jpni
1967
1968
1969      ! 5. East and west directions exchange
1970      ! ------------------------------------
1971
1972      SELECT CASE ( npolj )
1973
1974      CASE ( 3, 4, 5, 6 )
1975
1976         ! 5.1 Read Dirichlet lateral conditions
1977
1978         SELECT CASE ( nbondi )
1979
1980         CASE ( -1, 0, 1 )
1981            iihom = nlci-nreci
1982            DO jl = 1, jpreci
1983               t4ew(:,jl,:,1,1) = ptab1(jpreci+jl,:,:)
1984               t4we(:,jl,:,1,1) = ptab1(iihom +jl,:,:)
1985               t4ew(:,jl,:,2,1) = ptab2(jpreci+jl,:,:)
1986               t4we(:,jl,:,2,1) = ptab2(iihom +jl,:,:)
1987            END DO
1988
1989         END SELECT
1990
1991         ! 5.2 Migrations
1992
1993#if defined key_mpp_shmem
1994         !! SHMEM version
1995
1996         imigr = jpreci * jpj * jpk * 2
1997
1998         SELECT CASE ( nbondi )
1999         CASE ( -1 )
2000            CALL shmem_put( t4we(1,1,1,1,2), t4we(1,1,1,1,1), imigr, noea )
2001         CASE ( 0 )
2002            CALL shmem_put( t4ew(1,1,1,1,2), t4ew(1,1,1,1,1), imigr, nowe )
2003            CALL shmem_put( t4we(1,1,1,1,2), t4we(1,1,1,1,1), imigr, noea )
2004         CASE ( 1 )
2005            CALL shmem_put( t4ew(1,1,1,1,2), t4ew(1,1,1,1,1), imigr, nowe )
2006         END SELECT
2007
2008         CALL barrier()
2009         CALL shmem_udcflush()
2010
2011#elif defined key_mpp_mpi
2012         !! MPI version
2013
2014         imigr = jpreci * jpj * jpk * 2
2015 
2016         SELECT CASE ( nbondi )
2017         CASE ( -1 )
2018            CALL mppsend( 2, t4we(1,1,1,1,1), imigr, noea, ml_req1 )
2019            CALL mpprecv( 1, t4ew(1,1,1,1,2), imigr )
2020            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2021         CASE ( 0 )
2022            CALL mppsend( 1, t4ew(1,1,1,1,1), imigr, nowe, ml_req1 )
2023            CALL mppsend( 2, t4we(1,1,1,1,1), imigr, noea, ml_req2 )
2024            CALL mpprecv( 1, t4ew(1,1,1,1,2), imigr )
2025            CALL mpprecv( 2, t4we(1,1,1,1,2), imigr )
2026            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2027            IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
2028         CASE ( 1 )
2029            CALL mppsend( 1, t4ew(1,1,1,1,1), imigr, nowe, ml_req1 )
2030            CALL mpprecv( 2, t4we(1,1,1,1,2), imigr )
2031            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2032         END SELECT
2033#endif
2034
2035         ! 5.3 Write Dirichlet lateral conditions
2036
2037         iihom = nlci-jpreci
2038
2039         SELECT CASE ( nbondi)
2040         CASE ( -1 )
2041            DO jl = 1, jpreci
2042               ptab1(iihom+jl,:,:) = t4ew(:,jl,:,1,2)
2043               ptab2(iihom+jl,:,:) = t4ew(:,jl,:,2,2)
2044            END DO
2045         CASE ( 0 ) 
2046            DO jl = 1, jpreci
2047               ptab1(jl      ,:,:) = t4we(:,jl,:,1,2)
2048               ptab1(iihom+jl,:,:) = t4ew(:,jl,:,1,2)
2049               ptab2(jl      ,:,:) = t4we(:,jl,:,2,2)
2050               ptab2(iihom+jl,:,:) = t4ew(:,jl,:,2,2)
2051            END DO
2052         CASE ( 1 )
2053            DO jl = 1, jpreci
2054               ptab1(jl      ,:,:) = t4we(:,jl,:,1,2)
2055               ptab2(jl      ,:,:) = t4we(:,jl,:,2,2)
2056            END DO
2057         END SELECT
2058
2059      END SELECT    ! npolj
2060
2061   END SUBROUTINE mpp_lnk_3d_gather
2062
2063
2064   SUBROUTINE mpp_lnk_2d_e( pt2d, cd_type, psgn )
2065      !!----------------------------------------------------------------------
2066      !!                  ***  routine mpp_lnk_2d_e  ***
2067      !!                 
2068      !! ** Purpose :   Message passing manadgement for 2d array (with halo)
2069      !!
2070      !! ** Method  :   Use mppsend and mpprecv function for passing mask
2071      !!      between processors following neighboring subdomains.
2072      !!            domain parameters
2073      !!                    nlci   : first dimension of the local subdomain
2074      !!                    nlcj   : second dimension of the local subdomain
2075      !!                    jpr2di : number of rows for extra outer halo
2076      !!                    jpr2dj : number of columns for extra outer halo
2077      !!                    nbondi : mark for "east-west local boundary"
2078      !!                    nbondj : mark for "north-south local boundary"
2079      !!                    noea   : number for local neighboring processors
2080      !!                    nowe   : number for local neighboring processors
2081      !!                    noso   : number for local neighboring processors
2082      !!                    nono   : number for local neighboring processors
2083      !!   
2084      !! History :
2085      !!       
2086      !!   9.0  !  05-09  (R. Benshila, G. Madec)  original code
2087      !!
2088      !!----------------------------------------------------------------------
2089      !! * Arguments
2090      CHARACTER(len=1) , INTENT( in ) ::   &
2091         cd_type       ! define the nature of pt2d array grid-points
2092         !             !  = T , U , V , F , W
2093         !             !  = S : T-point, north fold treatment
2094         !             !  = G : F-point, north fold treatment
2095         !             !  = I : sea-ice velocity at F-point with index shift
2096      REAL(wp), INTENT( in ) ::   &
2097         psgn          ! control of the sign change
2098         !             !   = -1. , the sign is changed if north fold boundary
2099         !             !   =  1. , the sign is kept  if north fold boundary
2100      REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj), INTENT( inout ) ::   &
2101         pt2d          ! 2D array on which the boundary condition is applied
2102
2103      !! * Local variables
2104      INTEGER  ::   ji, jl      ! dummy loop indices
2105      INTEGER  ::   &
2106         imigr, iihom, ijhom,    &  ! temporary integers
2107         iloc, ijt, iju             !    "          "
2108      INTEGER  ::   &
2109         ipreci, iprecj             ! temporary integers
2110      INTEGER  ::   ml_req1, ml_req2, ml_err     ! for isend
2111      INTEGER  ::   ml_stat(MPI_STATUS_SIZE)     ! for isend
2112     !!---------------------------------------------------------------------
2113
2114      ! take into account outer extra 2D overlap area
2115      ipreci = jpreci + jpr2di
2116      iprecj = jprecj + jpr2dj
2117
2118
2119      ! 1. standard boundary treatment
2120      ! ------------------------------
2121
2122      !                                        ! East-West boundaries
2123      !                                        ! ====================
2124      IF( nbondi == 2 .AND.   &      ! Cyclic east-west
2125         &    (nperio == 1 .OR. nperio == 4 .OR. nperio == 6) ) THEN
2126         pt2d(1-jpr2di:     1    ,:) = pt2d(jpim1-jpr2di:  jpim1 ,:)
2127         pt2d(   jpi  :jpi+jpr2di,:) = pt2d(     2      :2+jpr2di,:)
2128
2129      ELSE                           ! ... closed
2130         SELECT CASE ( cd_type )
2131         CASE ( 'T', 'U', 'V', 'W' , 'I' )
2132            pt2d(  1-jpr2di   :jpreci    ,:) = 0.e0
2133            pt2d(nlci-jpreci+1:jpi+jpr2di,:) = 0.e0
2134         CASE ( 'F' )
2135            pt2d(nlci-jpreci+1:jpi+jpr2di,:) = 0.e0
2136         END SELECT
2137      ENDIF
2138
2139      !                                        ! North-South boundaries
2140      !                                        ! ======================
2141      SELECT CASE ( cd_type )
2142      CASE ( 'T', 'U', 'V', 'W' , 'I' )
2143         pt2d(:,  1-jpr2dj   :  jprecj  ) = 0.e0
2144         pt2d(:,nlcj-jprecj+1:jpj+jpr2dj) = 0.e0
2145      CASE ( 'F' )
2146         pt2d(:,nlcj-jprecj+1:jpj+jpr2dj) = 0.e0
2147      END SELECT
2148
2149
2150      ! 2. East and west directions
2151      ! ---------------------------
2152
2153      ! 2.1 Read Dirichlet lateral conditions
2154
2155      SELECT CASE ( nbondi )
2156      CASE ( -1, 0, 1 )    ! all except 2
2157         iihom = nlci-nreci-jpr2di
2158         DO jl = 1, ipreci
2159            tr2ew(:,jl,1) = pt2d(jpreci+jl,:)
2160            tr2we(:,jl,1) = pt2d(iihom +jl,:)
2161         END DO
2162      END SELECT
2163
2164      ! 2.2 Migrations
2165
2166#if defined key_mpp_shmem
2167      !! * SHMEM version
2168
2169      imigr = ipreci * ( jpj + 2*jpr2dj)
2170
2171      SELECT CASE ( nbondi )
2172      CASE ( -1 )
2173         CALL shmem_put( tr2we(1-jpr2dj,1,2), tr2we(1,1,1), imigr, noea )
2174      CASE ( 0 )
2175         CALL shmem_put( tr2ew(1-jpr2dj,1,2), tr2ew(1,1,1), imigr, nowe )
2176         CALL shmem_put( tr2we(1-jpr2dj,1,2), tr2we(1,1,1), imigr, noea )
2177      CASE ( 1 )
2178         CALL shmem_put( tr2ew(1-jpr2dj,1,2), tr2ew(1,1,1), imigr, nowe )
2179      END SELECT
2180
2181      CALL barrier()
2182      CALL shmem_udcflush()
2183
2184#elif defined key_mpp_mpi
2185      !! * MPI version
2186
2187      imigr = ipreci * ( jpj + 2*jpr2dj)
2188
2189      SELECT CASE ( nbondi )
2190      CASE ( -1 )
2191         CALL mppsend( 2, tr2we(1-jpr2dj,1,1), imigr, noea, ml_req1 )
2192         CALL mpprecv( 1, tr2ew(1-jpr2dj,1,2), imigr )
2193         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2194      CASE ( 0 )
2195         CALL mppsend( 1, tr2ew(1-jpr2dj,1,1), imigr, nowe, ml_req1 )
2196         CALL mppsend( 2, tr2we(1-jpr2dj,1,1), imigr, noea, ml_req2 )
2197         CALL mpprecv( 1, tr2ew(1-jpr2dj,1,2), imigr )
2198         CALL mpprecv( 2, tr2we(1-jpr2dj,1,2), imigr )
2199         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2200         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
2201      CASE ( 1 )
2202         CALL mppsend( 1, tr2ew(1-jpr2dj,1,1), imigr, nowe, ml_req1 )
2203         CALL mpprecv( 2, tr2we(1-jpr2dj,1,2), imigr )
2204         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2205      END SELECT
2206
2207#endif
2208
2209      ! 2.3 Write Dirichlet lateral conditions
2210
2211      iihom = nlci - jpreci
2212
2213      SELECT CASE ( nbondi )
2214      CASE ( -1 )
2215         DO jl = 1, ipreci
2216            pt2d(iihom+jl,:) = tr2ew(:,jl,2)
2217         END DO
2218      CASE ( 0 )
2219         DO jl = 1, ipreci
2220            pt2d(jl-jpr2di,:) = tr2we(:,jl,2)
2221            pt2d( iihom+jl,:) = tr2ew(:,jl,2)
2222         END DO
2223      CASE ( 1 )
2224         DO jl = 1, ipreci
2225            pt2d(jl-jpr2di,:) = tr2we(:,jl,2)
2226         END DO
2227      END SELECT
2228
2229
2230      ! 3. North and south directions
2231      ! -----------------------------
2232
2233      ! 3.1 Read Dirichlet lateral conditions
2234
2235      IF( nbondj /= 2 ) THEN
2236         ijhom = nlcj-nrecj-jpr2dj
2237         DO jl = 1, iprecj
2238            tr2sn(:,jl,1) = pt2d(:,ijhom +jl)
2239            tr2ns(:,jl,1) = pt2d(:,jprecj+jl)
2240         END DO
2241      ENDIF
2242
2243      ! 3.2 Migrations
2244
2245#if defined key_mpp_shmem
2246      !! * SHMEM version
2247
2248      imigr = iprecj * ( jpi + 2*jpr2di )
2249
2250      SELECT CASE ( nbondj )
2251      CASE ( -1 )
2252         CALL shmem_put( tr2sn(1-jpr2di,1,2), tr2sn(1,1,1), imigr, nono )
2253      CASE ( 0 )
2254         CALL shmem_put( tr2ns(1-jpr2di,1,2), tr2ns(1,1,1), imigr, noso )
2255         CALL shmem_put( tr2sn(1-jpr2di,1,2), tr2sn(1,1,1), imigr, nono )
2256      CASE ( 1 )
2257         CALL shmem_put( tr2ns(1-jpr2di,1,2), tr2ns(1,1,1), imigr, noso )
2258      END SELECT
2259      CALL barrier()
2260      CALL shmem_udcflush()
2261
2262#elif defined key_mpp_mpi
2263      !! * MPI version
2264
2265      imigr = iprecj * ( jpi + 2*jpr2di )
2266
2267      SELECT CASE ( nbondj )
2268      CASE ( -1 )
2269         CALL mppsend( 4, tr2sn(1-jpr2di,1,1), imigr, nono, ml_req1 )
2270         CALL mpprecv( 3, tr2ns(1-jpr2di,1,2), imigr )
2271         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2272      CASE ( 0 )
2273         CALL mppsend( 3, tr2ns(1-jpr2di,1,1), imigr, noso, ml_req1 )
2274         CALL mppsend( 4, tr2sn(1-jpr2di,1,1), imigr, nono, ml_req2 )
2275         CALL mpprecv( 3, tr2ns(1-jpr2di,1,2), imigr )
2276         CALL mpprecv( 4, tr2sn(1-jpr2di,1,2), imigr )
2277         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2278         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
2279      CASE ( 1 )
2280         CALL mppsend( 3, tr2ns(1-jpr2di,1,1), imigr, noso, ml_req1 )
2281         CALL mpprecv( 4, tr2sn(1-jpr2di,1,2), imigr )
2282         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2283      END SELECT
2284 
2285#endif
2286
2287      ! 3.3 Write Dirichlet lateral conditions
2288
2289      ijhom = nlcj - jprecj 
2290
2291      SELECT CASE ( nbondj )
2292      CASE ( -1 )
2293         DO jl = 1, iprecj
2294            pt2d(:,ijhom+jl) = tr2ns(:,jl,2)
2295         END DO
2296      CASE ( 0 )
2297         DO jl = 1, iprecj
2298            pt2d(:,jl-jpr2dj) = tr2sn(:,jl,2)
2299            pt2d(:,ijhom+jl ) = tr2ns(:,jl,2)
2300         END DO
2301      CASE ( 1 ) 
2302         DO jl = 1, iprecj
2303            pt2d(:,jl-jpr2dj) = tr2sn(:,jl,2)
2304         END DO
2305      END SELECT 
2306 
2307
2308      ! 4. north fold treatment
2309      ! -----------------------
2310 
2311      ! 4.1 treatment without exchange (jpni odd)
2312     
2313      SELECT CASE ( jpni )
2314 
2315      CASE ( 1 ) ! only one proc along I, no mpp exchange
2316 
2317         SELECT CASE ( npolj )
2318 
2319         CASE ( 3 , 4 )   !  T pivot
2320            iloc = jpiglo - 2 * ( nimpp - 1 )
2321 
2322            SELECT CASE ( cd_type )
2323 
2324            CASE ( 'T', 'S', 'W' )
2325               DO jl = 0, iprecj-1
2326                  DO ji = 2-jpr2di, nlci+jpr2di
2327                     ijt=iloc-ji+2
2328                     pt2d(ji,nlcj+jl) = psgn * pt2d(ijt,nlcj-2-jl)
2329                  END DO
2330               END DO
2331               DO ji = nlci/2+1, nlci+jpr2di
2332                  ijt=iloc-ji+2
2333                  pt2d(ji,nlcj-1) = psgn * pt2d(ijt,nlcj-1)
2334               END DO
2335 
2336            CASE ( 'U' )
2337               DO jl =0, iprecj-1
2338                  DO ji = 1-jpr2di, nlci-1-jpr2di
2339                     iju=iloc-ji+1
2340                     pt2d(ji,nlcj+jl) = psgn * pt2d(iju,nlcj-2-jl)
2341                  END DO
2342               END DO
2343               DO ji = nlci/2, nlci-1+jpr2di
2344                  iju=iloc-ji+1
2345                  pt2d(ji,nlcj-1) = psgn * pt2d(iju,nlcj-1)
2346               END DO
2347 
2348            CASE ( 'V' )
2349               DO jl = -1, iprecj-1
2350                  DO ji = 2-jpr2di, nlci+jpr2di
2351                     ijt=iloc-ji+2
2352                     pt2d(ji,nlcj+jl) = psgn * pt2d(ijt,nlcj-3-jl)
2353                  END DO
2354               END DO
2355 
2356            CASE ( 'F', 'G' )
2357               DO jl = -1, iprecj-1
2358                  DO ji = 1-jpr2di, nlci-1+jpr2di
2359                     iju=iloc-ji+1
2360                     pt2d(ji,nlcj+jl) = psgn * pt2d(iju,nlcj-3-jl)
2361                  END DO
2362               END DO
2363 
2364            CASE ( 'I' )                                  ! ice U-V point
2365               DO jl = 0, iprecj-1
2366                  pt2d(2,nlcj+jl) = psgn * pt2d(3,nlcj-1-jl)
2367                  DO ji = 3, nlci+jpr2di
2368                     iju = iloc - ji + 3
2369                     pt2d(ji,nlcj+jl) = psgn * pt2d(iju,nlcj-1-jl)
2370                  END DO
2371               END DO
2372 
2373            END SELECT
2374 
2375         CASE ( 5 , 6 )                 ! F pivot
2376            iloc=jpiglo-2*(nimpp-1)
2377 
2378            SELECT CASE (cd_type )
2379 
2380            CASE ( 'T', 'S', 'W' )
2381               DO jl = 0, iprecj-1
2382                  DO ji = 1-jpr2di, nlci+jpr2di
2383                     ijt=iloc-ji+1
2384                     pt2d(ji,nlcj+jl) = psgn * pt2d(ijt,nlcj-1-jl)
2385                  END DO
2386               END DO
2387 
2388            CASE ( 'U' )
2389               DO jl = 0, iprecj-1
2390                  DO ji = 1-jpr2di, nlci-1+jpr2di
2391                     iju=iloc-ji
2392                     pt2d(ji,nlcj+jl) = psgn * pt2d(iju,nlcj-1-jl)
2393                  END DO
2394               END DO
2395 
2396            CASE ( 'V' )
2397               DO jl = 0, iprecj-1
2398                  DO ji = 1-jpr2di, nlci+jpr2di
2399                     ijt=iloc-ji+1
2400                     pt2d(ji,nlcj+jl) = psgn * pt2d(ijt,nlcj-2-jl)
2401                  END DO
2402               END DO
2403               DO ji = nlci/2+1, nlci+jpr2di
2404                  ijt=iloc-ji+1
2405                  pt2d(ji,nlcj-1) = psgn * pt2d(ijt,nlcj-1)
2406               END DO
2407 
2408            CASE ( 'F', 'G' )
2409               DO jl = 0, iprecj-1
2410                  DO ji = 1-jpr2di, nlci-1+jpr2di
2411                     iju=iloc-ji
2412                     pt2d(ji,nlcj+jl) = psgn * pt2d(iju,nlcj-2-jl)
2413                  END DO
2414               END DO
2415               DO ji = nlci/2+1, nlci-1+jpr2di
2416                  iju=iloc-ji
2417                  pt2d(ji,nlcj-1) = psgn * pt2d(iju,nlcj-1)
2418               END DO
2419 
2420            CASE ( 'I' )                                  ! ice U-V point
2421               pt2d( 2 ,nlcj) = 0.e0
2422               DO jl = 0, iprecj-1
2423                  DO ji = 2 , nlci-1+jpr2di
2424                     ijt = iloc - ji + 2
2425                     pt2d(ji,nlcj+jl)= 0.5 * ( pt2d(ji,nlcj-1-jl) + psgn * pt2d(ijt,nlcj-1-jl) )
2426                  END DO
2427               END DO
2428 
2429            END SELECT   ! cd_type
2430 
2431         END SELECT   ! npolj
2432
2433      CASE DEFAULT   ! more than 1 proc along I
2434         IF( npolj /= 0 )   CALL mpp_lbc_north_e( pt2d, cd_type, psgn )   ! only for northern procs
2435         
2436      END SELECT   ! jpni
2437
2438
2439      ! 5. East and west directions
2440      ! ---------------------------
2441
2442      SELECT CASE ( npolj )
2443
2444      CASE ( 3, 4, 5, 6 )
2445
2446         ! 5.1 Read Dirichlet lateral conditions
2447
2448         SELECT CASE ( nbondi )
2449         CASE ( -1, 0, 1 )
2450            iihom = nlci-nreci-jpr2di
2451            DO jl = 1, ipreci
2452               tr2ew(:,jl,1) = pt2d(jpreci+jl,:)
2453               tr2we(:,jl,1) = pt2d(iihom +jl,:)
2454            END DO
2455         END SELECT
2456
2457         ! 5.2 Migrations
2458
2459#if defined key_mpp_shmem
2460         !! * SHMEM version
2461
2462         imigr = ipreci * ( jpj + 2*jpr2dj )
2463
2464         SELECT CASE ( nbondi )
2465         CASE ( -1 )
2466            CALL shmem_put( tr2we(1-jpr2dj,1,2), tr2we(1,1,1), imigr, noea )
2467         CASE ( 0 )
2468            CALL shmem_put( tr2ew(1-jpr2dj,1,2), tr2ew(1,1,1), imigr, nowe )
2469            CALL shmem_put( tr2we(1-jpr2dj,1,2), tr2we(1,1,1), imigr, noea )
2470         CASE ( 1 )
2471            CALL shmem_put( tr2ew(1-jpr2dj,1,2), tr2ew(1,1,1), imigr, nowe )
2472         END SELECT
2473
2474         CALL barrier()
2475         CALL shmem_udcflush()
2476 
2477#elif defined key_mpp_mpi
2478         !! * MPI version
2479 
2480         imigr=ipreci* ( jpj + 2*jpr2dj )
2481 
2482         SELECT CASE ( nbondi )
2483         CASE ( -1 )
2484            CALL mppsend( 2, tr2we(1-jpr2dj,1,1), imigr, noea, ml_req1 )
2485            CALL mpprecv( 1, tr2ew(1-jpr2dj,1,2), imigr )
2486            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2487         CASE ( 0 )
2488            CALL mppsend( 1, tr2ew(1-jpr2dj,1,1), imigr, nowe, ml_req1 )
2489            CALL mppsend( 2, tr2we(1-jpr2dj,1,1), imigr, noea, ml_req2 )
2490            CALL mpprecv( 1, tr2ew(1-jpr2dj,1,2), imigr )
2491            CALL mpprecv( 2, tr2we(1-jpr2dj,1,2), imigr )
2492            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2493            IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
2494         CASE ( 1 )
2495            CALL mppsend( 1, tr2ew(1-jpr2dj,1,1), imigr, nowe, ml_req1 )
2496            CALL mpprecv( 2, tr2we(1-jpr2dj,1,2), imigr )
2497            IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2498         END SELECT 
2499#endif
2500
2501         ! 5.3 Write Dirichlet lateral conditions
2502 
2503         iihom = nlci - jpreci
2504 
2505         SELECT CASE ( nbondi )
2506         CASE ( -1 )
2507            DO jl = 1, ipreci
2508               pt2d(iihom+jl,:) = tr2ew(:,jl,2)
2509            END DO
2510         CASE ( 0 )
2511            DO jl = 1, ipreci
2512               pt2d(jl- jpr2di,:) = tr2we(:,jl,2)
2513               pt2d(iihom+jl,:) = tr2ew(:,jl,2)
2514            END DO
2515         CASE ( 1 )
2516            DO jl = 1, ipreci
2517               pt2d(jl-jpr2di,:) = tr2we(:,jl,2)
2518            END DO
2519         END SELECT
2520 
2521      END SELECT   ! npolj
2522 
2523   END SUBROUTINE mpp_lnk_2d_e
2524
2525
2526   SUBROUTINE mpplnks( ptab )
2527      !!----------------------------------------------------------------------
2528      !!                  ***  routine mpplnks  ***
2529      !!
2530      !! ** Purpose :   Message passing manadgement for add 2d array local boundary
2531      !!
2532      !! ** Method  :   Use mppsend and mpprecv function for passing mask between
2533      !!       processors following neighboring subdomains.
2534      !!            domain parameters
2535      !!                    nlci   : first dimension of the local subdomain
2536      !!                    nlcj   : second dimension of the local subdomain
2537      !!                    nbondi : mark for "east-west local boundary"
2538      !!                    nbondj : mark for "north-south local boundary"
2539      !!                    noea   : number for local neighboring processors
2540      !!                    nowe   : number for local neighboring processors
2541      !!                    noso   : number for local neighboring processors
2542      !!                    nono   : number for local neighboring processors
2543      !!
2544      !!----------------------------------------------------------------------
2545      !! * Arguments
2546      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   &
2547         ptab                     ! 2D array
2548 
2549      !! * Local variables
2550      INTEGER ::   ji, jl         ! dummy loop indices
2551      INTEGER ::   &
2552         imigr, iihom, ijhom      ! temporary integers
2553      INTEGER ::   ml_req1, ml_req2, ml_err     ! for key_mpi_isend
2554      INTEGER ::   ml_stat(MPI_STATUS_SIZE)     ! for key_mpi_isend
2555      !!----------------------------------------------------------------------
2556
2557
2558      ! 1. north fold treatment
2559      ! -----------------------
2560
2561      ! 1.1 treatment without exchange (jpni odd)
2562 
2563      SELECT CASE ( npolj )
2564      CASE ( 4 )
2565         DO ji = 1, nlci
2566            ptab(ji,nlcj-2) = ptab(ji,nlcj-2) + t2p1(ji,1,1)
2567         END DO
2568      CASE ( 6 )
2569         DO ji = 1, nlci
2570            ptab(ji,nlcj-1) = ptab(ji,nlcj-1) + t2p1(ji,1,1)
2571         END DO
2572
2573      ! 1.2 treatment with exchange (jpni greater than 1)
2574      !
2575      CASE ( 3 )
2576#if defined key_mpp_shmem
2577 
2578         !! * SHMEN version
2579 
2580         imigr=jprecj*jpi
2581 
2582         CALL shmem_put(t2p1(1,1,2),t2p1(1,1,1),imigr,nono)
2583         CALL barrier()
2584         CALL shmem_udcflush()
2585
2586#  elif defined key_mpp_mpi
2587       !! * MPI version
2588
2589       imigr=jprecj*jpi
2590
2591       CALL mppsend(3,t2p1(1,1,1),imigr,nono, ml_req1)
2592       CALL mpprecv(3,t2p1(1,1,2),imigr)
2593       IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2594
2595#endif     
2596
2597       ! Write north fold conditions
2598
2599       DO ji = 1, nlci
2600          ptab(ji,nlcj-2) = ptab(ji,nlcj-2)+t2p1(ji,1,2)
2601       END DO
2602
2603    CASE ( 5 )
2604
2605#if defined key_mpp_shmem
2606
2607       !! * SHMEN version
2608
2609       imigr=jprecj*jpi
2610
2611       CALL shmem_put(t2p1(1,1,2),t2p1(1,1,1),imigr,nono)
2612       CALL barrier()
2613       CALL shmem_udcflush()
2614
2615#  elif defined key_mpp_mpi
2616       !! * Local variables   (MPI version)
2617
2618       imigr=jprecj*jpi
2619
2620       CALL mppsend(3,t2p1(1,1,1),imigr,nono, ml_req1)
2621       CALL mpprecv(3,t2p1(1,1,2),imigr)
2622       IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2623
2624#endif     
2625
2626       ! Write north fold conditions
2627
2628       DO ji = 1, nlci
2629          ptab(ji,nlcj-1) = ptab(ji,nlcj-1)+t2p1(ji,1,2)
2630       END DO
2631
2632    END SELECT
2633
2634
2635    ! 2. East and west directions
2636    ! ---------------------------
2637
2638    ! 2.1 Read Dirichlet lateral conditions
2639
2640    iihom = nlci-jpreci
2641
2642    SELECT CASE ( nbondi )
2643
2644    CASE ( -1, 0, 1 )  ! all except 2
2645       DO jl = 1, jpreci
2646             t2ew(:,jl,1) = ptab(  jl    ,:)
2647             t2we(:,jl,1) = ptab(iihom+jl,:)
2648       END DO
2649    END SELECT
2650
2651    ! 2.2 Migrations
2652
2653#if defined key_mpp_shmem
2654
2655    !! * SHMEN version
2656
2657    imigr=jpreci*jpj
2658
2659    SELECT CASE ( nbondi )
2660
2661    CASE ( -1 )
2662       CALL shmem_put(t2we(1,1,2),t2we(1,1,1),imigr,noea)
2663
2664    CASE ( 0 )
2665       CALL shmem_put(t2ew(1,1,2),t2ew(1,1,1),imigr,nowe)
2666       CALL shmem_put(t2we(1,1,2),t2we(1,1,1),imigr,noea)
2667
2668    CASE ( 1 )
2669       CALL shmem_put(t2ew(1,1,2),t2ew(1,1,1),imigr,nowe)
2670
2671    END SELECT
2672    CALL  barrier()
2673    CALL  shmem_udcflush()
2674
2675#  elif defined key_mpp_mpi
2676    !! * Local variables   (MPI version)
2677
2678    imigr=jpreci*jpj
2679
2680    SELECT CASE ( nbondi )
2681
2682    CASE ( -1 )
2683       CALL mppsend(2,t2we(1,1,1),imigr,noea, ml_req1)
2684       CALL mpprecv(1,t2ew(1,1,2),imigr)
2685       IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2686    CASE ( 0 )
2687       CALL mppsend(1,t2ew(1,1,1),imigr,nowe, ml_req1)
2688       CALL mppsend(2,t2we(1,1,1),imigr,noea, ml_req2)
2689       CALL mpprecv(1,t2ew(1,1,2),imigr)
2690       CALL mpprecv(2,t2we(1,1,2),imigr)
2691       IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2692       IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
2693
2694    CASE ( 1 )
2695       CALL mppsend(1,t2ew(1,1,1),imigr,nowe, ml_req1)
2696       CALL mpprecv(2,t2we(1,1,2),imigr)
2697       IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2698
2699    END SELECT
2700
2701#endif
2702
2703    ! 2.3 Write Dirichlet lateral conditions
2704
2705       iihom = nlci-nreci
2706
2707    SELECT CASE ( nbondi )
2708
2709    CASE ( -1 )
2710       DO jl = 1, jpreci
2711             ptab(iihom +jl,:) = ptab(iihom +jl,:)+t2ew(:,jl,2)
2712       END DO
2713
2714    CASE ( 0 )
2715       DO jl = 1, jpreci
2716             ptab(jpreci+jl,:) = ptab(jpreci+jl,:)+t2we(:,jl,2)
2717             ptab(iihom +jl,:) = ptab(iihom +jl,:)+t2ew(:,jl,2)
2718       END DO
2719
2720    CASE ( 1 )
2721       DO jl = 1, jpreci
2722             ptab(jpreci+jl,:) = ptab(jpreci+jl,:)+t2we(:,jl,2)
2723       END DO
2724    END SELECT
2725
2726
2727    ! 3. North and south directions
2728    ! -----------------------------
2729
2730    ! 3.1 Read Dirichlet lateral conditions
2731
2732    ijhom = nlcj-jprecj
2733
2734    SELECT CASE ( nbondj )
2735
2736    CASE ( -1, 0, 1 )
2737       DO jl = 1, jprecj
2738             t2sn(:,jl,1) = ptab(:,ijhom+jl)
2739             t2ns(:,jl,1) = ptab(:,   jl   )
2740       END DO
2741
2742    END SELECT 
2743
2744    ! 3.2 Migrations
2745
2746#if defined key_mpp_shmem
2747
2748    !! * SHMEN version
2749
2750    imigr=jprecj*jpi
2751
2752    SELECT CASE ( nbondj )
2753
2754    CASE ( -1 )
2755       CALL shmem_put(t2sn(1,1,2),t2sn(1,1,1),imigr,nono)
2756
2757    CASE ( 0 )
2758       CALL shmem_put(t2ns(1,1,2),t2ns(1,1,1),imigr,noso)
2759       CALL shmem_put(t2sn(1,1,2),t2sn(1,1,1),imigr,nono)
2760
2761    CASE ( 1 )
2762       CALL shmem_put(t2ns(1,1,2),t2ns(1,1,1),imigr,noso)
2763
2764    END SELECT
2765    CALL  barrier()
2766    CALL  shmem_udcflush()
2767
2768#  elif defined key_mpp_mpi
2769    !! * Local variables   (MPI version)
2770
2771    imigr=jprecj*jpi
2772
2773    SELECT CASE ( nbondj )
2774
2775    CASE ( -1 )
2776       CALL mppsend(4,t2sn(1,1,1),imigr,nono, ml_req1)
2777       CALL mpprecv(3,t2ns(1,1,2),imigr)
2778       IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2779
2780    CASE ( 0 )
2781       CALL mppsend(3,t2ns(1,1,1),imigr,noso, ml_req1)
2782       CALL mppsend(4,t2sn(1,1,1),imigr,nono, ml_req2)
2783       CALL mpprecv(3,t2ns(1,1,2),imigr)
2784       CALL mpprecv(4,t2sn(1,1,2),imigr)
2785       IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2786       IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
2787
2788    CASE ( 1 )
2789       CALL mppsend(3,t2ns(1,1,1),imigr,noso, ml_req1)
2790       CALL mpprecv(4,t2sn(1,1,2),imigr)
2791       IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
2792    END SELECT
2793
2794#endif
2795
2796    ! 3.3 Write Dirichlet lateral conditions
2797
2798       ijhom = nlcj-nrecj
2799
2800    SELECT CASE ( nbondj )
2801
2802    CASE ( -1 )
2803       DO jl = 1, jprecj
2804             ptab(:,ijhom +jl) = ptab(:,ijhom +jl)+t2ns(:,jl,2)
2805       END DO
2806
2807    CASE ( 0 )
2808       DO jl = 1, jprecj
2809             ptab(:,jprecj+jl) = ptab(:,jprecj+jl)+t2sn(:,jl,2)
2810             ptab(:,ijhom +jl) = ptab(:,ijhom +jl)+t2ns(:,jl,2)
2811       END DO
2812
2813    CASE ( 1 ) 
2814       DO jl = 1, jprecj
2815             ptab(:,jprecj+jl) = ptab(:,jprecj+jl)+t2sn(:,jl,2)
2816       END DO
2817
2818    END SELECT
2819
2820  END SUBROUTINE mpplnks
2821
2822
2823   SUBROUTINE mppsend( ktyp, pmess, kbytes, kdest, md_req)
2824      !!----------------------------------------------------------------------
2825      !!                  ***  routine mppsend  ***
2826      !!                   
2827      !! ** Purpose :   Send messag passing array
2828      !!
2829      !!----------------------------------------------------------------------
2830      !! * Arguments
2831      REAL(wp), INTENT(inout) ::   pmess(*)       ! array of real
2832      INTEGER , INTENT( in  ) ::   kbytes,     &  ! size of the array pmess
2833         &                         kdest ,     &  ! receive process number
2834         &                         ktyp,       &  ! Tag of the message
2835         &                         md_req         ! Argument for isend
2836      !!----------------------------------------------------------------------
2837#if defined key_mpp_shmem
2838      !! * SHMEM version  :    routine not used
2839
2840#elif defined key_mpp_mpi
2841      !! * MPI version
2842      INTEGER ::   iflag
2843
2844      SELECT CASE ( c_mpi_send )
2845      CASE ( 'S' )                ! Standard mpi send (blocking)
2846         CALL mpi_send ( pmess, kbytes, mpi_double_precision, kdest, ktyp,   &
2847            &                          mpi_comm_opa, iflag )
2848      CASE ( 'B' )                ! Buffer mpi send (blocking)
2849         CALL mpi_bsend( pmess, kbytes, mpi_double_precision, kdest, ktyp,   &
2850            &                          mpi_comm_opa, iflag )
2851      CASE ( 'I' )                ! Immediate mpi send (non-blocking send)
2852         ! Be carefull, one more argument here : the mpi request identifier..
2853         CALL mpi_isend( pmess, kbytes, mpi_double_precision, kdest, ktyp,   &
2854            &                          mpi_comm_opa, md_req, iflag )
2855      END SELECT
2856#endif
2857
2858   END SUBROUTINE mppsend
2859
2860
2861   SUBROUTINE mpprecv( ktyp, pmess, kbytes )
2862      !!----------------------------------------------------------------------
2863      !!                  ***  routine mpprecv  ***
2864      !!
2865      !! ** Purpose :   Receive messag passing array
2866      !!
2867      !!----------------------------------------------------------------------
2868      !! * Arguments
2869      REAL(wp), INTENT(inout) ::   pmess(*)       ! array of real
2870      INTEGER , INTENT( in  ) ::   kbytes,     &  ! suze of the array pmess
2871         &                         ktyp           ! Tag of the recevied message
2872      !!----------------------------------------------------------------------
2873#if defined key_mpp_shmem
2874      !! * SHMEM version  :    routine not used
2875
2876#  elif defined key_mpp_mpi
2877      !! * MPI version
2878      INTEGER :: istatus(mpi_status_size)
2879      INTEGER :: iflag
2880
2881      CALL mpi_recv( pmess, kbytes, mpi_double_precision, mpi_any_source, ktyp,   &
2882         &                          mpi_comm_opa, istatus, iflag )
2883#endif
2884
2885   END SUBROUTINE mpprecv
2886
2887
2888   SUBROUTINE mppgather( ptab, kp, pio )
2889      !!----------------------------------------------------------------------
2890      !!                   ***  routine mppgather  ***
2891      !!                   
2892      !! ** Purpose :   Transfert between a local subdomain array and a work
2893      !!     array which is distributed following the vertical level.
2894      !!
2895      !! ** Method  :
2896      !!
2897      !!----------------------------------------------------------------------
2898      !! * Arguments
2899      REAL(wp), DIMENSION(jpi,jpj),       INTENT( in  ) ::   ptab   ! subdomain input array
2900      INTEGER ,                           INTENT( in  ) ::   kp     ! record length
2901      REAL(wp), DIMENSION(jpi,jpj,jpnij), INTENT( out ) ::   pio    ! subdomain input array
2902      !!---------------------------------------------------------------------
2903#if defined key_mpp_shmem
2904      !! * SHMEM version
2905
2906      CALL barrier()
2907      CALL shmem_put( pio(1,1,npvm_me+1), ptab, jpi*jpj, kp )
2908      CALL barrier()
2909
2910#elif defined key_mpp_mpi
2911      !! * Local variables   (MPI version)
2912      INTEGER :: itaille,ierror
2913 
2914      itaille=jpi*jpj
2915      CALL mpi_gather( ptab, itaille, mpi_double_precision, pio, itaille,   &
2916         &                            mpi_double_precision, kp , mpi_comm_opa, ierror ) 
2917#endif
2918
2919   END SUBROUTINE mppgather
2920
2921
2922   SUBROUTINE mppscatter( pio, kp, ptab )
2923      !!----------------------------------------------------------------------
2924      !!                  ***  routine mppscatter  ***
2925      !!
2926      !! ** Purpose :   Transfert between awork array which is distributed
2927      !!      following the vertical level and the local subdomain array.
2928      !!
2929      !! ** Method :
2930      !!
2931      !!----------------------------------------------------------------------
2932      REAL(wp), DIMENSION(jpi,jpj,jpnij)  ::  pio        ! output array
2933      INTEGER                             ::   kp        ! Tag (not used with MPI
2934      REAL(wp), DIMENSION(jpi,jpj)        ::  ptab       ! subdomain array input
2935      !!---------------------------------------------------------------------
2936#if defined key_mpp_shmem
2937      !! * SHMEM version
2938
2939      CALL barrier()
2940      CALL shmem_get( ptab, pio(1,1,npvm_me+1), jpi*jpj, kp )
2941      CALL barrier()
2942
2943#  elif defined key_mpp_mpi
2944      !! * Local variables   (MPI version)
2945      INTEGER :: itaille, ierror
2946 
2947      itaille=jpi*jpj
2948
2949      CALL mpi_scatter( pio, itaille, mpi_double_precision, ptab, itaille,   &
2950         &                            mpi_double_precision, kp, mpi_comm_opa, ierror )
2951#endif
2952
2953   END SUBROUTINE mppscatter
2954
2955
2956   SUBROUTINE mppisl_a_int( ktab, kdim )
2957      !!----------------------------------------------------------------------
2958      !!                  ***  routine mppisl_a_int  ***
2959      !!                   
2960      !! ** Purpose :   Massively parallel processors
2961      !!                Find the  non zero value
2962      !!
2963      !!----------------------------------------------------------------------
2964      !! * Arguments
2965      INTEGER, INTENT( in  )                  ::   kdim       ! ???
2966      INTEGER, INTENT(inout), DIMENSION(kdim) ::   ktab       ! ???
2967 
2968#if defined key_mpp_shmem
2969      !! * Local variables   (SHMEM version)
2970      INTEGER :: ji
2971      INTEGER, SAVE :: ibool=0
2972
2973      IF( kdim > jpmppsum ) CALL ctl_stop( 'mppisl_a_int routine : kdim is too big', &
2974           &                               'change jpmppsum dimension in mpp.h' )
2975
2976      DO ji = 1, kdim
2977         niitab_shmem(ji) = ktab(ji)
2978      END DO
2979      CALL  barrier()
2980      IF(ibool == 0 ) THEN
2981         CALL shmem_int8_min_to_all (ni11tab_shmem,niitab_shmem,kdim,0   &
2982              ,0,N$PES,ni11wrk_shmem,ni11sync_shmem)
2983         CALL shmem_int8_max_to_all (ni12tab_shmem,niitab_shmem,kdim,0   &
2984              ,0,N$PES,ni12wrk_shmem,ni12sync_shmem)
2985      ELSE
2986         CALL shmem_int8_min_to_all (ni11tab_shmem,niitab_shmem,kdim,0   &
2987              ,0,N$PES,ni21wrk_shmem,ni21sync_shmem)
2988         CALL shmem_int8_max_to_all (ni12tab_shmem,niitab_shmem,kdim,0   &
2989              ,0,N$PES,ni22wrk_shmem,ni22sync_shmem)
2990      ENDIF
2991      CALL  barrier()
2992      ibool=ibool+1
2993      ibool=MOD( ibool,2)
2994      DO ji = 1, kdim
2995         IF( ni11tab_shmem(ji) /= 0. ) THEN
2996            ktab(ji) = ni11tab_shmem(ji)
2997         ELSE
2998            ktab(ji) = ni12tab_shmem(ji)
2999         ENDIF
3000      END DO
3001 
3002#  elif defined key_mpp_mpi
3003      !! * Local variables   (MPI version)
3004      LOGICAL  :: lcommute
3005      INTEGER, DIMENSION(kdim) ::   iwork
3006      INTEGER  :: mpi_isl,ierror
3007 
3008      lcommute = .TRUE.
3009      CALL mpi_op_create( lc_isl, lcommute, mpi_isl, ierror )
3010      CALL mpi_allreduce( ktab, iwork, kdim, mpi_integer   &
3011           , mpi_isl, mpi_comm_opa, ierror )
3012      ktab(:) = iwork(:)
3013#endif
3014
3015   END SUBROUTINE mppisl_a_int
3016
3017
3018   SUBROUTINE mppisl_int( ktab )
3019      !!----------------------------------------------------------------------
3020      !!                  ***  routine mppisl_int  ***
3021      !!                   
3022      !! ** Purpose :   Massively parallel processors
3023      !!                Find the non zero value
3024      !!
3025      !!----------------------------------------------------------------------
3026      !! * Arguments
3027      INTEGER , INTENT( inout ) ::   ktab        !
3028
3029#if defined key_mpp_shmem
3030      !! * Local variables   (SHMEM version)
3031      INTEGER, SAVE :: ibool=0
3032
3033      niitab_shmem(1) = ktab
3034      CALL  barrier()
3035      IF(ibool == 0 ) THEN
3036         CALL shmem_int8_min_to_all (ni11tab_shmem,niitab_shmem,1,0   &
3037              ,0,N$PES,ni11wrk_shmem,ni11sync_shmem)
3038         CALL shmem_int8_max_to_all (ni12tab_shmem,niitab_shmem,1,0   &
3039              ,0,N$PES,ni12wrk_shmem,ni12sync_shmem)
3040      ELSE
3041         CALL shmem_int8_min_to_all (ni11tab_shmem,niitab_shmem,1,0   &
3042              ,0,N$PES,ni21wrk_shmem,ni21sync_shmem)
3043         CALL shmem_int8_max_to_all (ni12tab_shmem,niitab_shmem,1,0   &
3044              ,0,N$PES,ni22wrk_shmem,ni22sync_shmem)
3045      ENDIF
3046      CALL  barrier()
3047      ibool=ibool+1
3048      ibool=MOD( ibool,2)
3049      IF( ni11tab_shmem(1) /= 0. ) THEN
3050         ktab = ni11tab_shmem(1)
3051      ELSE
3052         ktab = ni12tab_shmem(1)
3053      ENDIF
3054 
3055#  elif defined key_mpp_mpi
3056 
3057      !! * Local variables   (MPI version)
3058      LOGICAL :: lcommute
3059      INTEGER :: mpi_isl,ierror
3060      INTEGER ::   iwork
3061 
3062      lcommute = .TRUE.
3063      CALL mpi_op_create(lc_isl,lcommute,mpi_isl,ierror)
3064      CALL mpi_allreduce(ktab, iwork, 1,mpi_integer   &
3065           ,mpi_isl,mpi_comm_opa,ierror)
3066      ktab = iwork
3067#endif
3068
3069   END SUBROUTINE mppisl_int
3070
3071
3072   SUBROUTINE mppmin_a_int( ktab, kdim )
3073      !!----------------------------------------------------------------------
3074      !!                  ***  routine mppmin_a_int  ***
3075      !!
3076      !! ** Purpose :   Find minimum value in an integer layout array
3077      !!
3078      !!----------------------------------------------------------------------
3079      !! * Arguments
3080      INTEGER , INTENT( in  )                  ::   kdim        ! size of array
3081      INTEGER , INTENT(inout), DIMENSION(kdim) ::   ktab        ! input array
3082 
3083#if defined key_mpp_shmem
3084      !! * Local declarations    (SHMEM version)
3085      INTEGER :: ji
3086      INTEGER, SAVE :: ibool=0
3087 
3088      IF( kdim > jpmppsum ) CALL ctl_stop( 'mppmin_a_int routine : kdim is too big', &
3089           &                               'change jpmppsum dimension in mpp.h' )
3090 
3091      DO ji = 1, kdim
3092         niltab_shmem(ji) = ktab(ji)
3093      END DO
3094      CALL  barrier()
3095      IF(ibool == 0 ) THEN
3096         CALL shmem_int8_min_to_all (niltab_shmem,niltab_shmem,kdim,0,0   &
3097              ,N$PES,nil1wrk_shmem,nil1sync_shmem )
3098      ELSE
3099         CALL shmem_int8_min_to_all (niltab_shmem,niltab_shmem,kdim,0,0   &
3100              ,N$PES,nil2wrk_shmem,nil2sync_shmem )
3101      ENDIF
3102      CALL  barrier()
3103      ibool=ibool+1
3104      ibool=MOD( ibool,2)
3105      DO ji = 1, kdim
3106         ktab(ji) = niltab_shmem(ji)
3107      END DO
3108 
3109#  elif defined key_mpp_mpi
3110 
3111      !! * Local variables   (MPI version)
3112      INTEGER :: ierror
3113      INTEGER, DIMENSION(kdim) ::   iwork
3114 
3115      CALL mpi_allreduce( ktab, iwork, kdim, mpi_integer,   &
3116           &                mpi_min, mpi_comm_opa, ierror )
3117 
3118      ktab(:) = iwork(:)
3119#endif
3120
3121   END SUBROUTINE mppmin_a_int
3122
3123
3124   SUBROUTINE mppmin_int( ktab )
3125      !!----------------------------------------------------------------------
3126      !!                  ***  routine mppmin_int  ***
3127      !!
3128      !! ** Purpose :
3129      !!     Massively parallel processors
3130      !!     Find minimum value in an integer layout array
3131      !!
3132      !!----------------------------------------------------------------------
3133      !! * Arguments
3134      INTEGER, INTENT(inout) ::   ktab      ! ???
3135 
3136      !! * Local declarations
3137
3138#if defined key_mpp_shmem
3139
3140      !! * Local variables   (SHMEM version)
3141      INTEGER :: ji
3142      INTEGER, SAVE :: ibool=0
3143 
3144      niltab_shmem(1) = ktab
3145      CALL  barrier()
3146      IF(ibool == 0 ) THEN
3147         CALL shmem_int8_min_to_all (niltab_shmem,niltab_shmem, 1,0,0   &
3148              ,N$PES,nil1wrk_shmem,nil1sync_shmem )
3149      ELSE
3150         CALL shmem_int8_min_to_all (niltab_shmem,niltab_shmem, 1,0,0   &
3151              ,N$PES,nil2wrk_shmem,nil2sync_shmem )
3152      ENDIF
3153      CALL  barrier()
3154      ibool=ibool+1
3155      ibool=MOD( ibool,2)
3156      ktab = niltab_shmem(1)
3157 
3158#  elif defined key_mpp_mpi
3159
3160      !! * Local variables   (MPI version)
3161      INTEGER ::  ierror, iwork
3162 
3163      CALL mpi_allreduce(ktab,iwork, 1,mpi_integer   &
3164           &              ,mpi_min,mpi_comm_opa,ierror)
3165 
3166      ktab = iwork
3167#endif
3168
3169   END SUBROUTINE mppmin_int
3170
3171
3172   SUBROUTINE mppsum_a_int( ktab, kdim )
3173      !!----------------------------------------------------------------------
3174      !!                  ***  routine mppsum_a_int  ***
3175      !!                   
3176      !! ** Purpose :   Massively parallel processors
3177      !!                Global integer sum
3178      !!
3179      !!----------------------------------------------------------------------
3180      !! * Arguments
3181      INTEGER, INTENT( in  )                   ::   kdim      ! ???
3182      INTEGER, INTENT(inout), DIMENSION (kdim) ::   ktab      ! ???
3183 
3184#if defined key_mpp_shmem
3185
3186      !! * Local variables   (SHMEM version)
3187      INTEGER :: ji
3188      INTEGER, SAVE :: ibool=0
3189
3190      IF( kdim > jpmppsum ) CALL ctl_stop( 'mppsum_a_int routine : kdim is too big', &
3191           &                               'change jpmppsum dimension in mpp.h' )
3192
3193      DO ji = 1, kdim
3194         nistab_shmem(ji) = ktab(ji)
3195      END DO
3196      CALL  barrier()
3197      IF(ibool == 0 ) THEN
3198         CALL shmem_int8_sum_to_all(nistab_shmem,nistab_shmem,kdim,0,0,   &
3199              N$PES,nis1wrk_shmem,nis1sync_shmem)
3200      ELSE
3201         CALL shmem_int8_sum_to_all(nistab_shmem,nistab_shmem,kdim,0,0,   &
3202              N$PES,nis2wrk_shmem,nis2sync_shmem)
3203      ENDIF
3204      CALL  barrier()
3205      ibool = ibool + 1
3206      ibool = MOD( ibool, 2 )
3207      DO ji = 1, kdim
3208         ktab(ji) = nistab_shmem(ji)
3209      END DO
3210 
3211#  elif defined key_mpp_mpi
3212
3213      !! * Local variables   (MPI version)
3214      INTEGER :: ierror
3215      INTEGER, DIMENSION (kdim) ::  iwork
3216 
3217      CALL mpi_allreduce(ktab, iwork,kdim,mpi_integer   &
3218           ,mpi_sum,mpi_comm_opa,ierror)
3219 
3220      ktab(:) = iwork(:)
3221#endif
3222
3223   END SUBROUTINE mppsum_a_int
3224
3225
3226  SUBROUTINE mppsum_int( ktab )
3227    !!----------------------------------------------------------------------
3228    !!                 ***  routine mppsum_int  ***
3229    !!                 
3230    !! ** Purpose :   Global integer sum
3231    !!
3232    !!----------------------------------------------------------------------
3233    !! * Arguments
3234    INTEGER, INTENT(inout) ::   ktab
3235
3236#if defined key_mpp_shmem
3237
3238    !! * Local variables   (SHMEM version)
3239    INTEGER, SAVE :: ibool=0
3240
3241    nistab_shmem(1) = ktab
3242    CALL  barrier()
3243    IF(ibool == 0 ) THEN
3244       CALL shmem_int8_sum_to_all(nistab_shmem,nistab_shmem, 1,0,0,   &
3245            N$PES,nis1wrk_shmem,nis1sync_shmem)
3246    ELSE
3247       CALL shmem_int8_sum_to_all(nistab_shmem,nistab_shmem, 1,0,0,   &
3248            N$PES,nis2wrk_shmem,nis2sync_shmem)
3249    ENDIF
3250    CALL  barrier()
3251    ibool=ibool+1
3252    ibool=MOD( ibool,2)
3253    ktab = nistab_shmem(1)
3254
3255#  elif defined key_mpp_mpi
3256
3257    !! * Local variables   (MPI version)
3258    INTEGER :: ierror, iwork
3259
3260    CALL mpi_allreduce(ktab,iwork, 1,mpi_integer   &
3261         ,mpi_sum,mpi_comm_opa,ierror)
3262
3263    ktab = iwork
3264
3265#endif
3266
3267  END SUBROUTINE mppsum_int
3268
3269
3270  SUBROUTINE mppisl_a_real( ptab, kdim )
3271    !!----------------------------------------------------------------------
3272    !!                 ***  routine mppisl_a_real  ***
3273    !!         
3274    !! ** Purpose :   Massively parallel processors
3275    !!           Find the non zero island barotropic stream function value
3276    !!
3277    !!   Modifications:
3278    !!        !  93-09 (M. Imbard)
3279    !!        !  96-05 (j. Escobar)
3280    !!        !  98-05 (M. Imbard, J. Escobar, L. Colombet ) SHMEM and MPI
3281    !!----------------------------------------------------------------------
3282    INTEGER , INTENT( in  )                  ::   kdim      ! ???
3283    REAL(wp), INTENT(inout), DIMENSION(kdim) ::   ptab      ! ???
3284
3285#if defined key_mpp_shmem
3286
3287    !! * Local variables   (SHMEM version)
3288    INTEGER :: ji
3289    INTEGER, SAVE :: ibool=0
3290
3291    IF( kdim > jpmppsum ) CALL ctl_stop( 'mppisl_a_real routine : kdim is too big', &
3292         &                               'change jpmppsum dimension in mpp.h' )
3293
3294    DO ji = 1, kdim
3295       wiltab_shmem(ji) = ptab(ji)
3296    END DO
3297    CALL  barrier()
3298    IF(ibool == 0 ) THEN
3299       CALL shmem_real8_min_to_all (wi1tab_shmem,wiltab_shmem,kdim,0   &
3300            ,0,N$PES,wi11wrk_shmem,ni11sync_shmem)
3301       CALL shmem_real8_max_to_all (wi2tab_shmem,wiltab_shmem,kdim,0   &
3302            ,0,N$PES,wi12wrk_shmem,ni12sync_shmem)
3303    ELSE
3304       CALL shmem_real8_min_to_all (wi1tab_shmem,wiltab_shmem,kdim,0   &
3305            ,0,N$PES,wi21wrk_shmem,ni21sync_shmem)
3306       CALL shmem_real8_max_to_all (wi2tab_shmem,wiltab_shmem,kdim,0   &
3307            ,0,N$PES,wi22wrk_shmem,ni22sync_shmem)
3308    ENDIF
3309    CALL  barrier()
3310    ibool=ibool+1
3311    ibool=MOD( ibool,2)
3312    DO ji = 1, kdim
3313       IF(wi1tab_shmem(ji) /= 0. ) THEN
3314          ptab(ji) = wi1tab_shmem(ji)
3315       ELSE
3316          ptab(ji) = wi2tab_shmem(ji)
3317       ENDIF
3318    END DO
3319
3320#  elif defined key_mpp_mpi
3321
3322    !! * Local variables   (MPI version)
3323    LOGICAL ::   lcommute = .TRUE.
3324    INTEGER ::   mpi_isl, ierror
3325    REAL(wp), DIMENSION(kdim) ::  zwork
3326
3327    CALL mpi_op_create(lc_isl,lcommute,mpi_isl,ierror)
3328    CALL mpi_allreduce(ptab, zwork,kdim,mpi_double_precision   &
3329         ,mpi_isl,mpi_comm_opa,ierror)
3330    ptab(:) = zwork(:)
3331
3332#endif
3333
3334  END SUBROUTINE mppisl_a_real
3335
3336
3337   SUBROUTINE mppisl_real( ptab )
3338      !!----------------------------------------------------------------------
3339      !!                  ***  routine mppisl_real  ***
3340      !!                 
3341      !! ** Purpose :   Massively parallel processors
3342      !!       Find the  non zero island barotropic stream function value
3343      !!
3344      !!     Modifications:
3345      !!        !  93-09 (M. Imbard)
3346      !!        !  96-05 (j. Escobar)
3347      !!        !  98-05 (M. Imbard, J. Escobar, L. Colombet ) SHMEM and MPI
3348      !!----------------------------------------------------------------------
3349      REAL(wp), INTENT(inout) ::   ptab
3350
3351#if defined key_mpp_shmem
3352
3353      !! * Local variables   (SHMEM version)
3354      INTEGER, SAVE :: ibool=0
3355
3356      wiltab_shmem(1) = ptab
3357      CALL  barrier()
3358      IF(ibool == 0 ) THEN
3359         CALL shmem_real8_min_to_all (wi1tab_shmem,wiltab_shmem, 1,0   &
3360            ,0,N$PES,wi11wrk_shmem,ni11sync_shmem)
3361         CALL shmem_real8_max_to_all (wi2tab_shmem,wiltab_shmem, 1,0   &
3362            ,0,N$PES,wi12wrk_shmem,ni12sync_shmem)
3363      ELSE
3364         CALL shmem_real8_min_to_all (wi1tab_shmem,wiltab_shmem, 1,0   &
3365            ,0,N$PES,wi21wrk_shmem,ni21sync_shmem)
3366         CALL shmem_real8_max_to_all (wi2tab_shmem,wiltab_shmem, 1,0   &
3367            ,0,N$PES,wi22wrk_shmem,ni22sync_shmem)
3368      ENDIF
3369      CALL barrier()
3370      ibool = ibool + 1
3371      ibool = MOD( ibool, 2 )
3372      IF( wi1tab_shmem(1) /= 0. ) THEN
3373         ptab = wi1tab_shmem(1)
3374      ELSE
3375         ptab = wi2tab_shmem(1)
3376      ENDIF
3377
3378#  elif defined key_mpp_mpi
3379
3380      !! * Local variables   (MPI version)
3381      LOGICAL  ::   lcommute = .TRUE.
3382      INTEGER  ::   mpi_isl, ierror
3383      REAL(wp) ::   zwork
3384
3385      CALL mpi_op_create( lc_isl, lcommute, mpi_isl, ierror )
3386      CALL mpi_allreduce( ptab, zwork, 1, mpi_double_precision,   &
3387         &                                mpi_isl  , mpi_comm_opa, ierror )
3388      ptab = zwork
3389
3390#endif
3391
3392   END SUBROUTINE mppisl_real
3393
3394
3395  FUNCTION lc_isl( py, px, kdim, kdtatyp )
3396    INTEGER :: kdim
3397    REAL(wp), DIMENSION(kdim) ::  px, py
3398    INTEGER :: kdtatyp, ji
3399    INTEGER :: lc_isl
3400    DO ji = 1, kdim
3401       IF( py(ji) /= 0. )   px(ji) = py(ji)
3402    END DO
3403    lc_isl=0
3404
3405  END FUNCTION lc_isl
3406
3407
3408  SUBROUTINE mppmax_a_real( ptab, kdim )
3409    !!----------------------------------------------------------------------
3410    !!                 ***  routine mppmax_a_real  ***
3411    !!                 
3412    !! ** Purpose :   Maximum
3413    !!
3414    !!----------------------------------------------------------------------
3415    !! * Arguments
3416    INTEGER , INTENT( in  )                  ::   kdim
3417    REAL(wp), INTENT(inout), DIMENSION(kdim) ::   ptab
3418
3419#if defined key_mpp_shmem
3420
3421    !! * Local variables   (SHMEM version)
3422    INTEGER :: ji
3423    INTEGER, SAVE :: ibool=0
3424
3425    IF( kdim > jpmppsum ) CALL ctl_stop( 'mppmax_a_real routine : kdim is too big', &
3426         &                               'change jpmppsum dimension in mpp.h' )
3427
3428    DO ji = 1, kdim
3429       wintab_shmem(ji) = ptab(ji)
3430    END DO
3431    CALL  barrier()
3432    IF(ibool == 0 ) THEN
3433       CALL shmem_real8_max_to_all (wintab_shmem,wintab_shmem,kdim,0   &
3434            ,0,N$PES,wi1wrk_shmem,ni1sync_shmem)
3435    ELSE
3436       CALL shmem_real8_max_to_all (wintab_shmem,wintab_shmem,kdim,0   &
3437            ,0,N$PES,wi2wrk_shmem,ni2sync_shmem)
3438    ENDIF
3439    CALL  barrier()
3440    ibool=ibool+1
3441    ibool=MOD( ibool,2)
3442    DO ji = 1, kdim
3443       ptab(ji) = wintab_shmem(ji)
3444    END DO
3445
3446#  elif defined key_mpp_mpi
3447
3448    !! * Local variables   (MPI version)
3449    INTEGER :: ierror
3450    REAL(wp), DIMENSION(kdim) ::  zwork
3451
3452    CALL mpi_allreduce(ptab, zwork,kdim,mpi_double_precision   &
3453         ,mpi_max,mpi_comm_opa,ierror)
3454    ptab(:) = zwork(:)
3455
3456#endif
3457
3458  END SUBROUTINE mppmax_a_real
3459
3460
3461  SUBROUTINE mppmax_real( ptab )
3462    !!----------------------------------------------------------------------
3463    !!                  ***  routine mppmax_real  ***
3464    !!                   
3465    !! ** Purpose :   Maximum
3466    !!
3467    !!----------------------------------------------------------------------
3468    !! * Arguments
3469    REAL(wp), INTENT(inout) ::   ptab      ! ???
3470
3471#if defined key_mpp_shmem
3472
3473    !! * Local variables   (SHMEM version)
3474    INTEGER, SAVE :: ibool=0
3475
3476    wintab_shmem(1) = ptab
3477    CALL  barrier()
3478    IF(ibool == 0 ) THEN
3479       CALL shmem_real8_max_to_all (wintab_shmem,wintab_shmem, 1,0   &
3480            ,0,N$PES,wi1wrk_shmem,ni1sync_shmem)
3481    ELSE
3482       CALL shmem_real8_max_to_all (wintab_shmem,wintab_shmem, 1,0   &
3483            ,0,N$PES,wi2wrk_shmem,ni2sync_shmem)
3484    ENDIF
3485    CALL  barrier()
3486    ibool=ibool+1
3487    ibool=MOD( ibool,2)
3488    ptab = wintab_shmem(1)
3489
3490#  elif defined key_mpp_mpi
3491
3492    !! * Local variables   (MPI version)
3493    INTEGER  ::   ierror
3494    REAL(wp) ::   zwork
3495
3496    CALL mpi_allreduce( ptab, zwork  , 1             , mpi_double_precision,   &
3497       &                      mpi_max, mpi_comm_opa, ierror     )
3498    ptab = zwork
3499
3500#endif
3501
3502  END SUBROUTINE mppmax_real
3503
3504
3505  SUBROUTINE mppmin_a_real( ptab, kdim )
3506    !!----------------------------------------------------------------------
3507    !!                 ***  routine mppmin_a_real  ***
3508    !!                 
3509    !! ** Purpose :   Minimum
3510    !!
3511    !!-----------------------------------------------------------------------
3512    !! * Arguments
3513    INTEGER , INTENT( in  )                  ::   kdim
3514    REAL(wp), INTENT(inout), DIMENSION(kdim) ::   ptab
3515
3516#if defined key_mpp_shmem
3517
3518    !! * Local variables   (SHMEM version)
3519    INTEGER :: ji
3520    INTEGER, SAVE :: ibool=0
3521
3522    IF( kdim > jpmppsum ) CALL ctl_stop( 'mpprmin routine : kdim is too big', &
3523         &                               'change jpmppsum dimension in mpp.h' )
3524
3525    DO ji = 1, kdim
3526       wintab_shmem(ji) = ptab(ji)
3527    END DO
3528    CALL  barrier()
3529    IF(ibool == 0 ) THEN
3530       CALL shmem_real8_min_to_all (wintab_shmem,wintab_shmem,kdim,0   &
3531            ,0,N$PES,wi1wrk_shmem,ni1sync_shmem)
3532    ELSE
3533       CALL shmem_real8_min_to_all (wintab_shmem,wintab_shmem,kdim,0   &
3534            ,0,N$PES,wi2wrk_shmem,ni2sync_shmem)
3535    ENDIF
3536    CALL  barrier()
3537    ibool=ibool+1
3538    ibool=MOD( ibool,2)
3539    DO ji = 1, kdim
3540       ptab(ji) = wintab_shmem(ji)
3541    END DO
3542
3543#  elif defined key_mpp_mpi
3544
3545    !! * Local variables   (MPI version)
3546    INTEGER :: ierror
3547    REAL(wp), DIMENSION(kdim) ::   zwork
3548
3549    CALL mpi_allreduce(ptab, zwork,kdim,mpi_double_precision   &
3550         ,mpi_min,mpi_comm_opa,ierror)
3551    ptab(:) = zwork(:)
3552
3553#endif
3554
3555  END SUBROUTINE mppmin_a_real
3556
3557
3558  SUBROUTINE mppmin_real( ptab )
3559    !!----------------------------------------------------------------------
3560    !!                  ***  routine mppmin_real  ***
3561    !!
3562    !! ** Purpose :   minimum in Massively Parallel Processing
3563    !!                REAL scalar case
3564    !!
3565    !!-----------------------------------------------------------------------
3566    !! * Arguments
3567    REAL(wp), INTENT( inout ) ::   ptab        !
3568
3569#if defined key_mpp_shmem
3570
3571    !! * Local variables   (SHMEM version)
3572    INTEGER, SAVE :: ibool=0
3573
3574    wintab_shmem(1) = ptab
3575    CALL  barrier()
3576    IF(ibool == 0 ) THEN
3577       CALL shmem_real8_min_to_all (wintab_shmem,wintab_shmem, 1,0   &
3578            ,0,N$PES,wi1wrk_shmem,ni1sync_shmem)
3579    ELSE
3580       CALL shmem_real8_min_to_all (wintab_shmem,wintab_shmem, 1,0   &
3581            ,0,N$PES,wi2wrk_shmem,ni2sync_shmem)
3582    ENDIF
3583    CALL  barrier()
3584    ibool=ibool+1
3585    ibool=MOD( ibool,2)
3586    ptab = wintab_shmem(1)
3587
3588#  elif defined key_mpp_mpi
3589
3590    !! * Local variables   (MPI version)
3591    INTEGER  ::   ierror
3592    REAL(wp) ::   zwork
3593
3594    CALL mpi_allreduce( ptab, zwork, 1,mpi_double_precision   &
3595         &               ,mpi_min,mpi_comm_opa,ierror)
3596    ptab = zwork
3597
3598#endif
3599
3600  END SUBROUTINE mppmin_real
3601
3602
3603  SUBROUTINE mppsum_a_real( ptab, kdim )
3604    !!----------------------------------------------------------------------
3605    !!                  ***  routine mppsum_a_real  ***
3606    !!
3607    !! ** Purpose :   global sum in Massively Parallel Processing
3608    !!                REAL ARRAY argument case
3609    !!
3610    !!-----------------------------------------------------------------------
3611    INTEGER , INTENT( in )                     ::   kdim      ! size of ptab
3612    REAL(wp), DIMENSION(kdim), INTENT( inout ) ::   ptab      ! input array
3613
3614#if defined key_mpp_shmem
3615
3616    !! * Local variables   (SHMEM version)
3617    INTEGER :: ji
3618    INTEGER, SAVE :: ibool=0
3619
3620    IF( kdim > jpmppsum ) CALL ctl_stop( 'mppsum_a_real routine : kdim is too big', &
3621         &                               'change jpmppsum dimension in mpp.h' )
3622
3623    DO ji = 1, kdim
3624       wrstab_shmem(ji) = ptab(ji)
3625    END DO
3626    CALL  barrier()
3627    IF(ibool == 0 ) THEN
3628       CALL shmem_real8_sum_to_all (wrstab_shmem,wrstab_shmem,kdim,0   &
3629            ,0,N$PES,wrs1wrk_shmem,nrs1sync_shmem )
3630    ELSE
3631       CALL shmem_real8_sum_to_all (wrstab_shmem,wrstab_shmem,kdim,0   &
3632            ,0,N$PES,wrs2wrk_shmem,nrs2sync_shmem )
3633    ENDIF
3634    CALL  barrier()
3635    ibool=ibool+1
3636    ibool=MOD( ibool,2)
3637    DO ji = 1, kdim
3638       ptab(ji) = wrstab_shmem(ji)
3639    END DO
3640
3641#  elif defined key_mpp_mpi
3642
3643    !! * Local variables   (MPI version)
3644    INTEGER                   ::   ierror    ! temporary integer
3645    REAL(wp), DIMENSION(kdim) ::   zwork     ! temporary workspace
3646
3647    CALL mpi_allreduce(ptab, zwork,kdim,mpi_double_precision   &
3648         &              ,mpi_sum,mpi_comm_opa,ierror)
3649    ptab(:) = zwork(:)
3650
3651#endif
3652
3653  END SUBROUTINE mppsum_a_real
3654
3655
3656  SUBROUTINE mppsum_real( ptab )
3657    !!----------------------------------------------------------------------
3658    !!                  ***  routine mppsum_real  ***
3659    !!             
3660    !! ** Purpose :   global sum in Massively Parallel Processing
3661    !!                SCALAR argument case
3662    !!
3663    !!-----------------------------------------------------------------------
3664    REAL(wp), INTENT(inout) ::   ptab        ! input scalar
3665
3666#if defined key_mpp_shmem
3667
3668    !! * Local variables   (SHMEM version)
3669    INTEGER, SAVE :: ibool=0
3670
3671    wrstab_shmem(1) = ptab
3672    CALL  barrier()
3673    IF(ibool == 0 ) THEN
3674       CALL shmem_real8_sum_to_all (wrstab_shmem,wrstab_shmem, 1,0   &
3675            ,0,N$PES,wrs1wrk_shmem,nrs1sync_shmem )
3676    ELSE
3677       CALL shmem_real8_sum_to_all (wrstab_shmem,wrstab_shmem, 1,0   &
3678            ,0,N$PES,wrs2wrk_shmem,nrs2sync_shmem )
3679    ENDIF
3680    CALL  barrier()
3681    ibool = ibool + 1
3682    ibool = MOD( ibool, 2 )
3683    ptab = wrstab_shmem(1)
3684
3685#  elif defined key_mpp_mpi
3686
3687    !! * Local variables   (MPI version)
3688    INTEGER  ::   ierror
3689    REAL(wp) ::   zwork
3690
3691    CALL mpi_allreduce(ptab, zwork, 1,mpi_double_precision   &
3692         &              ,mpi_sum,mpi_comm_opa,ierror)
3693    ptab = zwork
3694
3695#endif
3696
3697  END SUBROUTINE mppsum_real
3698
3699  SUBROUTINE mpp_minloc2d(ptab, pmask, pmin, ki,kj )
3700    !!------------------------------------------------------------------------
3701    !!             ***  routine mpp_minloc  ***
3702    !!
3703    !! ** Purpose :  Compute the global minimum of an array ptab
3704    !!              and also give its global position
3705    !!
3706    !! ** Method : Use MPI_ALLREDUCE with MPI_MINLOC
3707    !!
3708    !! ** Arguments : I : ptab =local 2D array
3709    !!                O : pmin = global minimum
3710    !!                O : ki,kj = global position of minimum
3711    !!
3712    !! ** Author : J.M. Molines 10/10/2004
3713    !!--------------------------------------------------------------------------
3714#ifdef key_mpp_shmem
3715    CALL ctl_stop( ' mpp_minloc not yet available in SHMEM' )
3716# elif key_mpp_mpi
3717    !! * Arguments
3718    REAL(wp), DIMENSION (jpi,jpj), INTENT (in)  :: ptab ,& ! Local 2D array
3719         &                                         pmask   ! Local mask
3720    REAL(wp)                     , INTENT (out) :: pmin    ! Global minimum of ptab
3721    INTEGER                      , INTENT (out) :: ki,kj   ! index of minimum in global frame
3722
3723    !! * Local variables
3724    REAL(wp) :: zmin   ! local minimum
3725    REAL(wp) ,DIMENSION(2,1) :: zain, zaout
3726    INTEGER, DIMENSION (2)  :: ilocs
3727    INTEGER :: ierror
3728
3729
3730    zmin  = MINVAL( ptab(:,:) , mask= pmask == 1.e0 )
3731    ilocs = MINLOC( ptab(:,:) , mask= pmask == 1.e0 )
3732
3733    ki = ilocs(1) + nimpp - 1
3734    kj = ilocs(2) + njmpp - 1
3735
3736    zain(1,:)=zmin
3737    zain(2,:)=ki+10000.*kj
3738
3739    CALL MPI_ALLREDUCE( zain,zaout, 1, MPI_2DOUBLE_PRECISION,MPI_MINLOC,MPI_COMM_OPA,ierror)
3740
3741    pmin=zaout(1,1)
3742    kj= INT(zaout(2,1)/10000.)
3743    ki= INT(zaout(2,1) - 10000.*kj )
3744#endif
3745
3746  END SUBROUTINE mpp_minloc2d
3747
3748
3749  SUBROUTINE mpp_minloc3d(ptab, pmask, pmin, ki,kj ,kk)
3750    !!------------------------------------------------------------------------
3751    !!             ***  routine mpp_minloc  ***
3752    !!
3753    !! ** Purpose :  Compute the global minimum of an array ptab
3754    !!              and also give its global position
3755    !!
3756    !! ** Method : Use MPI_ALLREDUCE with MPI_MINLOC
3757    !!
3758    !! ** Arguments : I : ptab =local 2D array
3759    !!                O : pmin = global minimum
3760    !!                O : ki,kj = global position of minimum
3761    !!
3762    !! ** Author : J.M. Molines 10/10/2004
3763    !!--------------------------------------------------------------------------
3764#ifdef key_mpp_shmem
3765    CALL ctl_stop( ' mpp_minloc not yet available in SHMEM' )
3766# elif key_mpp_mpi
3767    !! * Arguments
3768    REAL(wp), DIMENSION (jpi,jpj,jpk), INTENT (in)  :: ptab ,& ! Local 2D array
3769         &                                         pmask   ! Local mask
3770    REAL(wp)                     , INTENT (out) :: pmin    ! Global minimum of ptab
3771    INTEGER                      , INTENT (out) :: ki,kj,kk ! index of minimum in global frame
3772
3773    !! * Local variables
3774    REAL(wp) :: zmin   ! local minimum
3775    REAL(wp) ,DIMENSION(2,1) :: zain, zaout
3776    INTEGER, DIMENSION (3)  :: ilocs
3777    INTEGER :: ierror
3778
3779
3780    zmin  = MINVAL( ptab(:,:,:) , mask= pmask == 1.e0 )
3781    ilocs = MINLOC( ptab(:,:,:) , mask= pmask == 1.e0 )
3782
3783    ki = ilocs(1) + nimpp - 1
3784    kj = ilocs(2) + njmpp - 1
3785    kk = ilocs(3)
3786
3787    zain(1,:)=zmin
3788    zain(2,:)=ki+10000.*kj+100000000.*kk
3789
3790    CALL MPI_ALLREDUCE( zain,zaout, 1, MPI_2DOUBLE_PRECISION,MPI_MINLOC,MPI_COMM_OPA,ierror)
3791
3792    pmin=zaout(1,1)
3793    kk= INT(zaout(2,1)/100000000.)
3794    kj= INT(zaout(2,1) - kk * 100000000. )/10000
3795    ki= INT(zaout(2,1) - kk * 100000000. -kj * 10000. )
3796#endif
3797
3798  END SUBROUTINE mpp_minloc3d
3799
3800
3801  SUBROUTINE mpp_maxloc2d(ptab, pmask, pmax, ki,kj )
3802    !!------------------------------------------------------------------------
3803    !!             ***  routine mpp_maxloc  ***
3804    !!
3805    !! ** Purpose :  Compute the global maximum of an array ptab
3806    !!              and also give its global position
3807    !!
3808    !! ** Method : Use MPI_ALLREDUCE with MPI_MINLOC
3809    !!
3810    !! ** Arguments : I : ptab =local 2D array
3811    !!                O : pmax = global maximum
3812    !!                O : ki,kj = global position of maximum
3813    !!
3814    !! ** Author : J.M. Molines 10/10/2004
3815    !!--------------------------------------------------------------------------
3816#ifdef key_mpp_shmem
3817    CALL ctl_stop( ' mpp_maxloc not yet available in SHMEM' )
3818# elif key_mpp_mpi
3819    !! * Arguments
3820    REAL(wp), DIMENSION (jpi,jpj), INTENT (in)  :: ptab ,& ! Local 2D array
3821         &                                         pmask   ! Local mask
3822    REAL(wp)                     , INTENT (out) :: pmax    ! Global maximum of ptab
3823    INTEGER                      , INTENT (out) :: ki,kj   ! index of maximum in global frame
3824
3825    !! * Local variables
3826    REAL(wp) :: zmax   ! local maximum
3827    REAL(wp) ,DIMENSION(2,1) :: zain, zaout
3828    INTEGER, DIMENSION (2)  :: ilocs
3829    INTEGER :: ierror
3830
3831
3832    zmax  = MAXVAL( ptab(:,:) , mask= pmask == 1.e0 )
3833    ilocs = MAXLOC( ptab(:,:) , mask= pmask == 1.e0 )
3834
3835    ki = ilocs(1) + nimpp - 1
3836    kj = ilocs(2) + njmpp - 1
3837
3838    zain(1,:)=zmax
3839    zain(2,:)=ki+10000.*kj
3840
3841    CALL MPI_ALLREDUCE( zain,zaout, 1, MPI_2DOUBLE_PRECISION,MPI_MAXLOC,MPI_COMM_OPA,ierror)
3842
3843    pmax=zaout(1,1)
3844    kj= INT(zaout(2,1)/10000.)
3845    ki= INT(zaout(2,1) - 10000.*kj )
3846#endif
3847
3848  END SUBROUTINE mpp_maxloc2d
3849
3850  SUBROUTINE mpp_maxloc3d(ptab, pmask, pmax, ki,kj,kk )
3851    !!------------------------------------------------------------------------
3852    !!             ***  routine mpp_maxloc  ***
3853    !!
3854    !! ** Purpose :  Compute the global maximum of an array ptab
3855    !!              and also give its global position
3856    !!
3857    !! ** Method : Use MPI_ALLREDUCE with MPI_MINLOC
3858    !!
3859    !! ** Arguments : I : ptab =local 2D array
3860    !!                O : pmax = global maximum
3861    !!                O : ki,kj = global position of maximum
3862    !!
3863    !! ** Author : J.M. Molines 10/10/2004
3864    !!--------------------------------------------------------------------------
3865#ifdef key_mpp_shmem
3866    CALL ctl_stop( ' mpp_maxloc not yet available in SHMEM' )
3867# elif key_mpp_mpi
3868    !! * Arguments
3869    REAL(wp), DIMENSION (jpi,jpj,jpk), INTENT (in)  :: ptab ,& ! Local 2D array
3870         &                                         pmask   ! Local mask
3871    REAL(wp)                     , INTENT (out) :: pmax    ! Global maximum of ptab
3872    INTEGER                      , INTENT (out) :: ki,kj,kk   ! index of maximum in global frame
3873
3874    !! * Local variables
3875    REAL(wp) :: zmax   ! local maximum
3876    REAL(wp) ,DIMENSION(2,1) :: zain, zaout
3877    INTEGER, DIMENSION (3)  :: ilocs
3878    INTEGER :: ierror
3879
3880
3881    zmax  = MAXVAL( ptab(:,:,:) , mask= pmask == 1.e0 )
3882    ilocs = MAXLOC( ptab(:,:,:) , mask= pmask == 1.e0 )
3883
3884    ki = ilocs(1) + nimpp - 1
3885    kj = ilocs(2) + njmpp - 1
3886    kk = ilocs(3)
3887
3888    zain(1,:)=zmax
3889    zain(2,:)=ki+10000.*kj+100000000.*kk
3890
3891    CALL MPI_ALLREDUCE( zain,zaout, 1, MPI_2DOUBLE_PRECISION,MPI_MAXLOC,MPI_COMM_OPA,ierror)
3892
3893    pmax=zaout(1,1)
3894    kk= INT(zaout(2,1)/100000000.)
3895    kj= INT(zaout(2,1) - kk * 100000000. )/10000
3896    ki= INT(zaout(2,1) - kk * 100000000. -kj * 10000. )
3897#endif
3898
3899  END SUBROUTINE mpp_maxloc3d
3900
3901  SUBROUTINE mppsync()
3902    !!----------------------------------------------------------------------
3903    !!                  ***  routine mppsync  ***
3904    !!                   
3905    !! ** Purpose :   Massively parallel processors, synchroneous
3906    !!
3907    !!-----------------------------------------------------------------------
3908
3909#if defined key_mpp_shmem
3910
3911    !! * Local variables   (SHMEM version)
3912    CALL barrier()
3913
3914#  elif defined key_mpp_mpi
3915
3916    !! * Local variables   (MPI version)
3917    INTEGER :: ierror
3918
3919    CALL mpi_barrier(mpi_comm_opa,ierror)
3920
3921#endif
3922
3923  END SUBROUTINE mppsync
3924
3925
3926  SUBROUTINE mppstop
3927    !!----------------------------------------------------------------------
3928    !!                  ***  routine mppstop  ***
3929    !!                   
3930    !! ** purpose :   Stop massilively parallel processors method
3931    !!
3932    !!----------------------------------------------------------------------
3933    !! * Local declarations
3934    INTEGER ::   info
3935    !!----------------------------------------------------------------------
3936
3937    ! 1. Mpp synchroneus
3938    ! ------------------
3939
3940    CALL mppsync
3941#if defined key_mpp_mpi
3942    CALL mpi_finalize( info )
3943#endif
3944
3945  END SUBROUTINE mppstop
3946
3947
3948  SUBROUTINE mppobc( ptab, kd1, kd2, kl, kk, ktype, kij )
3949    !!----------------------------------------------------------------------
3950    !!                  ***  routine mppobc  ***
3951    !!
3952    !! ** Purpose :   Message passing manadgement for open boundary
3953    !!     conditions array
3954    !!
3955    !! ** Method  :   Use mppsend and mpprecv function for passing mask
3956    !!       between processors following neighboring subdomains.
3957    !!       domain parameters
3958    !!                    nlci   : first dimension of the local subdomain
3959    !!                    nlcj   : second dimension of the local subdomain
3960    !!                    nbondi : mark for "east-west local boundary"
3961    !!                    nbondj : mark for "north-south local boundary"
3962    !!                    noea   : number for local neighboring processors
3963    !!                    nowe   : number for local neighboring processors
3964    !!                    noso   : number for local neighboring processors
3965    !!                    nono   : number for local neighboring processors
3966    !!
3967    !! History :
3968    !!        !  98-07 (J.M. Molines) Open boundary conditions
3969    !!----------------------------------------------------------------------
3970    !! * Arguments
3971    INTEGER , INTENT( in ) ::   &
3972         kd1, kd2,   &  ! starting and ending indices
3973         kl ,        &  ! index of open boundary
3974         kk,         &  ! vertical dimension
3975         ktype,      &  ! define north/south or east/west cdt
3976         !              !  = 1  north/south  ;  = 2  east/west
3977         kij            ! horizontal dimension
3978    REAL(wp), DIMENSION(kij,kk), INTENT( inout )  ::   &
3979         ptab           ! variable array
3980
3981    !! * Local variables
3982    INTEGER  ::   ji, jj, jk, jl   ! dummy loop indices
3983    INTEGER  ::   &
3984         iipt0, iipt1, ilpt1,     &  ! temporary integers
3985         ijpt0, ijpt1,            &  !    "          "
3986         imigr, iihom, ijhom         !    "          "
3987    INTEGER ::   ml_req1, ml_req2, ml_err     ! for key_mpi_isend
3988    INTEGER ::   ml_stat(MPI_STATUS_SIZE)     ! for key_mpi_isend
3989    REAL(wp), DIMENSION(jpi,jpj) ::   &
3990         ztab                        ! temporary workspace
3991    !!----------------------------------------------------------------------
3992
3993
3994    ! boundary condition initialization
3995    ! ---------------------------------
3996
3997    ztab(:,:) = 0.e0
3998
3999    IF( ktype==1 ) THEN                                  ! north/south boundaries
4000       iipt0 = MAX( 1, MIN(kd1 - nimpp+1, nlci     ) )
4001       iipt1 = MAX( 0, MIN(kd2 - nimpp+1, nlci - 1 ) )
4002       ilpt1 = MAX( 1, MIN(kd2 - nimpp+1, nlci     ) )
4003       ijpt0 = MAX( 1, MIN(kl  - njmpp+1, nlcj     ) )
4004       ijpt1 = MAX( 0, MIN(kl  - njmpp+1, nlcj - 1 ) )
4005    ELSEIF( ktype==2 ) THEN                              ! east/west boundaries
4006       iipt0 = MAX( 1, MIN(kl  - nimpp+1, nlci     ) )
4007       iipt1 = MAX( 0, MIN(kl  - nimpp+1, nlci - 1 ) )
4008       ijpt0 = MAX( 1, MIN(kd1 - njmpp+1, nlcj     ) )
4009       ijpt1 = MAX( 0, MIN(kd2 - njmpp+1, nlcj - 1 ) )
4010       ilpt1 = MAX( 1, MIN(kd2 - njmpp+1, nlcj     ) )
4011    ELSE
4012       CALL ctl_stop( 'mppobc: bad ktype' )
4013    ENDIF
4014
4015    DO jk = 1, kk
4016       IF( ktype==1 ) THEN                               ! north/south boundaries
4017          DO jj = ijpt0, ijpt1
4018             DO ji = iipt0, iipt1
4019                ztab(ji,jj) = ptab(ji,jk)
4020             END DO
4021          END DO
4022       ELSEIF( ktype==2 ) THEN                           ! east/west boundaries
4023          DO jj = ijpt0, ijpt1
4024             DO ji = iipt0, iipt1
4025                ztab(ji,jj) = ptab(jj,jk)
4026             END DO
4027          END DO
4028       ENDIF
4029
4030
4031       ! 1. East and west directions
4032       ! ---------------------------
4033
4034       ! 1.1 Read Dirichlet lateral conditions
4035
4036       IF( nbondi /= 2 ) THEN
4037          iihom = nlci-nreci
4038
4039          DO jl = 1, jpreci
4040             t2ew(:,jl,1) = ztab(jpreci+jl,:)
4041             t2we(:,jl,1) = ztab(iihom +jl,:)
4042          END DO
4043       ENDIF
4044
4045       ! 1.2 Migrations
4046
4047#if defined key_mpp_shmem
4048       !! *  (SHMEM version)
4049       imigr=jpreci*jpj*jpbyt
4050
4051       IF( nbondi == -1 ) THEN
4052          CALL shmem_put( t2we(1,1,2), t2we(1,1,1), imigr/jpbyt, noea )
4053       ELSEIF( nbondi == 0 ) THEN
4054          CALL shmem_put( t2ew(1,1,2), t2ew(1,1,1), imigr/jpbyt, nowe )
4055          CALL shmem_put( t2we(1,1,2), t2we(1,1,1), imigr/jpbyt, noea )
4056       ELSEIF( nbondi == 1 ) THEN
4057          CALL shmem_put( t2ew(1,1,2), t2ew(1,1,1), imigr/jpbyt, nowe )
4058       ENDIF
4059       CALL barrier()
4060       CALL shmem_udcflush()
4061
4062#  elif key_mpp_mpi
4063       !! * (MPI version)
4064
4065       imigr=jpreci*jpj
4066
4067       IF( nbondi == -1 ) THEN
4068          CALL mppsend(2,t2we(1,1,1),imigr,noea, ml_req1)
4069          CALL mpprecv(1,t2ew(1,1,2),imigr)
4070          IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
4071       ELSEIF( nbondi == 0 ) THEN
4072          CALL mppsend(1,t2ew(1,1,1),imigr,nowe, ml_req1)
4073          CALL mppsend(2,t2we(1,1,1),imigr,noea, ml_req2)
4074          CALL mpprecv(1,t2ew(1,1,2),imigr)
4075          CALL mpprecv(2,t2we(1,1,2),imigr)
4076          IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
4077          IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
4078       ELSEIF( nbondi == 1 ) THEN
4079          CALL mppsend(1,t2ew(1,1,1),imigr,nowe, ml_req1)
4080          CALL mpprecv(2,t2we(1,1,2),imigr)
4081          IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
4082       ENDIF
4083#endif
4084
4085
4086       ! 1.3 Write Dirichlet lateral conditions
4087
4088       iihom = nlci-jpreci
4089       IF( nbondi == 0 .OR. nbondi == 1 ) THEN
4090          DO jl = 1, jpreci
4091             ztab(jl,:) = t2we(:,jl,2)
4092          END DO
4093       ENDIF
4094
4095       IF( nbondi == -1 .OR. nbondi == 0 ) THEN
4096          DO jl = 1, jpreci
4097             ztab(iihom+jl,:) = t2ew(:,jl,2)
4098          END DO
4099       ENDIF
4100
4101
4102       ! 2. North and south directions
4103       ! -----------------------------
4104
4105       ! 2.1 Read Dirichlet lateral conditions
4106
4107       IF( nbondj /= 2 ) THEN
4108          ijhom = nlcj-nrecj
4109          DO jl = 1, jprecj
4110             t2sn(:,jl,1) = ztab(:,ijhom +jl)
4111             t2ns(:,jl,1) = ztab(:,jprecj+jl)
4112          END DO
4113       ENDIF
4114
4115       ! 2.2 Migrations
4116
4117#if defined key_mpp_shmem
4118       !! * SHMEM version
4119
4120       imigr=jprecj*jpi*jpbyt
4121
4122       IF( nbondj == -1 ) THEN
4123          CALL shmem_put( t2sn(1,1,2), t2sn(1,1,1), imigr/jpbyt, nono )
4124       ELSEIF( nbondj == 0 ) THEN
4125          CALL shmem_put( t2ns(1,1,2), t2ns(1,1,1), imigr/jpbyt, noso )
4126          CALL shmem_put( t2sn(1,1,2), t2sn(1,1,1), imigr/jpbyt, nono )
4127       ELSEIF( nbondj == 1 ) THEN
4128          CALL shmem_put( t2ns(1,1,2), t2ns(1,1,1), imigr/jpbyt, noso )
4129       ENDIF
4130       CALL barrier()
4131       CALL shmem_udcflush()
4132
4133#  elif key_mpp_mpi
4134       !! * Local variables   (MPI version)
4135
4136       imigr=jprecj*jpi
4137
4138       IF( nbondj == -1 ) THEN
4139          CALL mppsend(4,t2sn(1,1,1),imigr,nono, ml_req1)
4140          CALL mpprecv(3,t2ns(1,1,2),imigr)
4141          IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
4142       ELSEIF( nbondj == 0 ) THEN
4143          CALL mppsend(3,t2ns(1,1,1),imigr,noso, ml_req1)
4144          CALL mppsend(4,t2sn(1,1,1),imigr,nono, ml_req2)
4145          CALL mpprecv(3,t2ns(1,1,2),imigr)
4146          CALL mpprecv(4,t2sn(1,1,2),imigr)
4147          IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
4148          IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err)
4149       ELSEIF( nbondj == 1 ) THEN
4150          CALL mppsend(3,t2ns(1,1,1),imigr,noso, ml_req1)
4151          CALL mpprecv(4,t2sn(1,1,2),imigr)
4152          IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err)
4153       ENDIF
4154
4155#endif
4156
4157       ! 2.3 Write Dirichlet lateral conditions
4158
4159       ijhom = nlcj - jprecj
4160       IF( nbondj == 0 .OR. nbondj == 1 ) THEN
4161          DO jl = 1, jprecj
4162             ztab(:,jl) = t2sn(:,jl,2)
4163          END DO
4164       ENDIF
4165
4166       IF( nbondj == 0 .OR. nbondj == -1 ) THEN
4167          DO jl = 1, jprecj
4168             ztab(:,ijhom+jl) = t2ns(:,jl,2)
4169          END DO
4170       ENDIF
4171
4172       IF( ktype==1 .AND. kd1 <= jpi+nimpp-1 .AND. nimpp <= kd2 ) THEN
4173          ! north/south boundaries
4174          DO jj = ijpt0,ijpt1
4175             DO ji = iipt0,ilpt1
4176                ptab(ji,jk) = ztab(ji,jj) 
4177             END DO
4178          END DO
4179       ELSEIF( ktype==2 .AND. kd1 <= jpj+njmpp-1 .AND. njmpp <= kd2 ) THEN
4180          ! east/west boundaries
4181          DO jj = ijpt0,ilpt1
4182             DO ji = iipt0,iipt1
4183                ptab(jj,jk) = ztab(ji,jj) 
4184             END DO
4185          END DO
4186       ENDIF
4187
4188    END DO
4189
4190  END SUBROUTINE mppobc
4191
4192
4193  SUBROUTINE mpp_ini_north
4194    !!----------------------------------------------------------------------
4195    !!               ***  routine mpp_ini_north  ***
4196    !!
4197    !! ** Purpose :   Initialize special communicator for north folding
4198    !!      condition together with global variables needed in the mpp folding
4199    !!
4200    !! ** Method  : - Look for northern processors
4201    !!              - Put their number in nrank_north
4202    !!              - Create groups for the world processors and the north processors
4203    !!              - Create a communicator for northern processors
4204    !!
4205    !! ** output
4206    !!      njmppmax = njmpp for northern procs
4207    !!      ndim_rank_north = number of processors in the northern line
4208    !!      nrank_north (ndim_rank_north) = number  of the northern procs.
4209    !!      ngrp_world = group ID for the world processors
4210    !!      ngrp_north = group ID for the northern processors
4211    !!      ncomm_north = communicator for the northern procs.
4212    !!      north_root = number (in the world) of proc 0 in the northern comm.
4213    !!
4214    !! History :
4215    !!        !  03-09 (J.M. Molines, MPI only )
4216    !!----------------------------------------------------------------------
4217#ifdef key_mpp_shmem
4218    CALL ctl_stop( ' mpp_ini_north not available in SHMEM' )
4219# elif key_mpp_mpi
4220    INTEGER :: ierr
4221    INTEGER :: jproc
4222    INTEGER :: ii,ji
4223    !!----------------------------------------------------------------------
4224
4225    njmppmax=MAXVAL(njmppt)
4226
4227    ! Look for how many procs on the northern boundary
4228    !
4229    ndim_rank_north=0
4230    DO jproc=1,jpnij
4231       IF ( njmppt(jproc) == njmppmax ) THEN
4232          ndim_rank_north = ndim_rank_north + 1
4233       END IF
4234    END DO
4235
4236
4237    ! Allocate the right size to nrank_north
4238    !
4239    ALLOCATE(nrank_north(ndim_rank_north))
4240
4241    ! Fill the nrank_north array with proc. number of northern procs.
4242    ! Note : the rank start at 0 in MPI
4243    !
4244    ii=0
4245    DO ji = 1, jpnij
4246       IF ( njmppt(ji) == njmppmax   ) THEN
4247          ii=ii+1
4248          nrank_north(ii)=ji-1
4249       END IF
4250    END DO
4251    ! create the world group
4252    !
4253    CALL MPI_COMM_GROUP(mpi_comm_opa,ngrp_world,ierr)
4254    !
4255    ! Create the North group from the world group
4256    CALL MPI_GROUP_INCL(ngrp_world,ndim_rank_north,nrank_north,ngrp_north,ierr)
4257
4258    ! Create the North communicator , ie the pool of procs in the north group
4259    !
4260    CALL MPI_COMM_CREATE(mpi_comm_opa,ngrp_north,ncomm_north,ierr)
4261
4262
4263    ! find proc number in the world of proc 0 in the north
4264    CALL MPI_GROUP_TRANSLATE_RANKS(ngrp_north,1,0,ngrp_world,north_root,ierr)
4265#endif
4266
4267  END SUBROUTINE mpp_ini_north
4268
4269
4270   SUBROUTINE mpp_lbc_north_3d ( pt3d, cd_type, psgn )
4271      !!---------------------------------------------------------------------
4272      !!                   ***  routine mpp_lbc_north_3d  ***
4273      !!
4274      !! ** Purpose :
4275      !!      Ensure proper north fold horizontal bondary condition in mpp configuration
4276      !!      in case of jpn1 > 1
4277      !!
4278      !! ** Method :
4279      !!      Gather the 4 northern lines of the global domain on 1 processor and
4280      !!      apply lbc north-fold on this sub array. Then scatter the fold array
4281      !!      back to the processors.
4282      !!
4283      !! History :
4284      !!   8.5  !  03-09  (J.M. Molines ) For mpp folding condition at north
4285      !!                                  from lbc routine
4286      !!   9.0  !  03-12  (J.M. Molines ) encapsulation into lib_mpp, coding rules of lbc_lnk
4287      !!----------------------------------------------------------------------
4288      !! * Arguments
4289      CHARACTER(len=1), INTENT( in ) ::   &
4290         cd_type       ! nature of pt3d grid-points
4291         !             !   = T ,  U , V , F or W  gridpoints
4292      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( inout ) ::   &
4293         pt3d          ! 3D array on which the boundary condition is applied
4294      REAL(wp), INTENT( in ) ::   &
4295         psgn          ! control of the sign change
4296         !             !   = -1. , the sign is changed if north fold boundary
4297         !             !   =  1. , the sign is kept  if north fold boundary
4298
4299      !! * Local declarations
4300      INTEGER :: ji, jj, jk, jr, jproc
4301      INTEGER :: ierr
4302      INTEGER :: ildi,ilei,iilb
4303      INTEGER :: ijpj,ijpjm1,ij,ijt,iju
4304      INTEGER :: itaille
4305      REAL(wp), DIMENSION(jpiglo,4,jpk) :: ztab
4306      REAL(wp), DIMENSION(jpi,4,jpk,jpni) :: znorthgloio
4307      REAL(wp), DIMENSION(jpi,4,jpk) :: znorthloc
4308      !!----------------------------------------------------------------------
4309
4310    ! If we get in this routine it s because : North fold condition and mpp with more
4311    !   than one proc across i : we deal only with the North condition
4312
4313    ! 0. Sign setting
4314    ! ---------------
4315
4316    ijpj=4
4317    ijpjm1=3
4318
4319    ! put in znorthloc the last 4 jlines of pt3d
4320    DO jk = 1, jpk 
4321       DO jj = nlcj - ijpj +1, nlcj
4322          ij = jj - nlcj + ijpj
4323          znorthloc(:,ij,jk) = pt3d(:,jj,jk)
4324       END DO
4325    END DO
4326
4327
4328    IF (npolj /= 0 ) THEN
4329       ! Build in proc 0 of ncomm_north the znorthgloio
4330       znorthgloio(:,:,:,:) = 0_wp
4331
4332#ifdef key_mpp_shmem
4333       not done : compiler error
4334#elif defined key_mpp_mpi
4335       itaille=jpi*jpk*ijpj
4336       CALL MPI_GATHER(znorthloc,itaille,MPI_DOUBLE_PRECISION,znorthgloio,itaille,MPI_DOUBLE_PRECISION,0,ncomm_north,ierr)
4337#endif
4338
4339    ENDIF
4340
4341    IF (narea == north_root+1 ) THEN
4342       ! recover the global north array
4343       ztab(:,:,:) = 0_wp
4344
4345       DO jr = 1, ndim_rank_north
4346          jproc = nrank_north(jr) + 1
4347          ildi  = nldit (jproc)
4348          ilei  = nleit (jproc)
4349          iilb  = nimppt(jproc)
4350          DO jk = 1, jpk 
4351             DO jj = 1, 4
4352                DO ji = ildi, ilei
4353                   ztab(ji+iilb-1,jj,jk) = znorthgloio(ji,jj,jk,jr)
4354                END DO
4355             END DO
4356          END DO
4357       END DO
4358
4359
4360       ! Horizontal slab
4361       ! ===============
4362
4363       DO jk = 1, jpk 
4364
4365
4366          ! 2. North-Fold boundary conditions
4367          ! ----------------------------------
4368
4369          SELECT CASE ( npolj )
4370
4371          CASE ( 3, 4 )                       ! *  North fold  T-point pivot
4372
4373             ztab( 1    ,ijpj,jk) = 0.e0
4374             ztab(jpiglo,ijpj,jk) = 0.e0
4375
4376             SELECT CASE ( cd_type )
4377
4378             CASE ( 'T' , 'S' , 'W' )                   ! T-, W-point
4379                DO ji = 2, jpiglo
4380                   ijt = jpiglo-ji+2
4381                   ztab(ji,ijpj,jk) = psgn * ztab(ijt,ijpj-2,jk)
4382                END DO
4383                DO ji = jpiglo/2+1, jpiglo
4384                   ijt = jpiglo-ji+2
4385                   ztab(ji,ijpjm1,jk) = psgn * ztab(ijt,ijpjm1,jk)
4386                END DO
4387
4388             CASE ( 'U' )                               ! U-point
4389                DO ji = 1, jpiglo-1
4390                   iju = jpiglo-ji+1
4391                   ztab(ji,ijpj,jk) = psgn * ztab(iju,ijpj-2,jk)
4392                END DO
4393                DO ji = jpiglo/2, jpiglo-1
4394                   iju = jpiglo-ji+1
4395                   ztab(ji,ijpjm1,jk) = psgn * ztab(iju,ijpjm1,jk)
4396                END DO
4397
4398             CASE ( 'V' )                               ! V-point
4399                DO ji = 2, jpiglo
4400                   ijt = jpiglo-ji+2
4401                   ztab(ji,ijpj-1,jk) = psgn * ztab(ijt,ijpj-2,jk)
4402                   ztab(ji,ijpj  ,jk) = psgn * ztab(ijt,ijpj-3,jk)
4403                END DO
4404
4405             CASE ( 'F' , 'G' )                         ! F-point
4406                DO ji = 1, jpiglo-1
4407                   iju = jpiglo-ji+1
4408                   ztab(ji,ijpj-1,jk) = psgn * ztab(iju,ijpj-2,jk)
4409                   ztab(ji,ijpj  ,jk) = psgn * ztab(iju,ijpj-3,jk)
4410                END DO
4411
4412             END SELECT
4413
4414          CASE ( 5, 6 )                        ! *  North fold  F-point pivot
4415
4416             ztab( 1    ,ijpj,jk) = 0.e0
4417             ztab(jpiglo,ijpj,jk) = 0.e0
4418
4419             SELECT CASE ( cd_type )
4420
4421             CASE ( 'T' , 'S' , 'W' )                   ! T-, W-point
4422                DO ji = 1, jpiglo
4423                   ijt = jpiglo-ji+1
4424                   ztab(ji,ijpj,jk) = psgn * ztab(ijt,ijpj-1,jk)
4425                END DO
4426
4427             CASE ( 'U' )                               ! U-point
4428                DO ji = 1, jpiglo-1
4429                   iju = jpiglo-ji
4430                   ztab(ji,ijpj,jk) = psgn * ztab(iju,ijpj-1,jk)
4431                END DO
4432
4433             CASE ( 'V' )                               ! V-point
4434                DO ji = 1, jpiglo
4435                   ijt = jpiglo-ji+1
4436                   ztab(ji,ijpj,jk) = psgn * ztab(ijt,ijpj-2,jk)
4437                END DO
4438                DO ji = jpiglo/2+1, jpiglo
4439                   ijt = jpiglo-ji+1
4440                   ztab(ji,ijpjm1,jk) = psgn * ztab(ijt,ijpjm1,jk)
4441                END DO
4442
4443             CASE ( 'F' , 'G' )                         ! F-point
4444                DO ji = 1, jpiglo-1
4445                   iju = jpiglo-ji
4446                   ztab(ji,ijpj  ,jk) = psgn * ztab(iju,ijpj-2,jk)
4447                END DO
4448                DO ji = jpiglo/2+1, jpiglo-1
4449                   iju = jpiglo-ji
4450                   ztab(ji,ijpjm1,jk) = psgn * ztab(iju,ijpjm1,jk)
4451                END DO
4452
4453             END SELECT
4454
4455          CASE DEFAULT                           ! *  closed
4456
4457             SELECT CASE ( cd_type) 
4458
4459             CASE ( 'T' , 'U' , 'V' , 'W' )             ! T-, U-, V-, W-points
4460                ztab(:, 1  ,jk) = 0.e0
4461                ztab(:,ijpj,jk) = 0.e0
4462
4463             CASE ( 'F' )                               ! F-point
4464                ztab(:,ijpj,jk) = 0.e0
4465
4466             END SELECT
4467
4468          END SELECT
4469
4470          !     End of slab
4471          !     ===========
4472
4473       END DO
4474
4475       !! Scatter back to pt3d
4476       DO jr = 1, ndim_rank_north
4477          jproc=nrank_north(jr)+1
4478          ildi=nldit (jproc)
4479          ilei=nleit (jproc)
4480          iilb=nimppt(jproc)
4481          DO jk=  1, jpk
4482             DO jj=1,ijpj
4483                DO ji=ildi,ilei
4484                   znorthgloio(ji,jj,jk,jr)=ztab(ji+iilb-1,jj,jk)
4485                END DO
4486             END DO
4487          END DO
4488       END DO
4489
4490    ENDIF      ! only done on proc 0 of ncomm_north
4491
4492#ifdef key_mpp_shmem
4493    not done yet in shmem : compiler error
4494#elif key_mpp_mpi
4495    IF ( npolj /= 0 ) THEN
4496       itaille=jpi*jpk*ijpj
4497       CALL MPI_SCATTER(znorthgloio,itaille,MPI_DOUBLE_PRECISION,znorthloc,itaille,MPI_DOUBLE_PRECISION,0,ncomm_north,ierr)
4498    ENDIF
4499#endif
4500
4501    ! put in the last ijpj jlines of pt3d znorthloc
4502    DO jk = 1 , jpk 
4503       DO jj = nlcj - ijpj + 1 , nlcj
4504          ij = jj - nlcj + ijpj
4505          pt3d(:,jj,jk)= znorthloc(:,ij,jk)
4506       END DO
4507    END DO
4508
4509  END SUBROUTINE mpp_lbc_north_3d
4510
4511
4512  SUBROUTINE mpp_lbc_north_2d ( pt2d, cd_type, psgn)
4513    !!---------------------------------------------------------------------
4514    !!                   ***  routine mpp_lbc_north_2d  ***
4515    !!
4516    !! ** Purpose :
4517    !!      Ensure proper north fold horizontal bondary condition in mpp configuration
4518    !!      in case of jpn1 > 1 (for 2d array )
4519    !!
4520    !! ** Method :
4521    !!      Gather the 4 northern lines of the global domain on 1 processor and
4522    !!      apply lbc north-fold on this sub array. Then scatter the fold array
4523    !!      back to the processors.
4524    !!
4525    !! History :
4526    !!   8.5  !  03-09  (J.M. Molines ) For mpp folding condition at north
4527    !!                                  from lbc routine
4528    !!   9.0  !  03-12  (J.M. Molines ) encapsulation into lib_mpp, coding rules of lbc_lnk
4529    !!----------------------------------------------------------------------
4530
4531    !! * Arguments
4532    CHARACTER(len=1), INTENT( in ) ::   &
4533         cd_type       ! nature of pt2d grid-points
4534    !             !   = T ,  U , V , F or W  gridpoints
4535    REAL(wp), DIMENSION(jpi,jpj), INTENT( inout ) ::   &
4536         pt2d          ! 2D array on which the boundary condition is applied
4537    REAL(wp), INTENT( in ) ::   &
4538         psgn          ! control of the sign change
4539    !             !   = -1. , the sign is changed if north fold boundary
4540    !             !   =  1. , the sign is kept  if north fold boundary
4541
4542
4543    !! * Local declarations
4544
4545    INTEGER :: ji, jj,  jr, jproc
4546    INTEGER :: ierr
4547    INTEGER :: ildi,ilei,iilb
4548    INTEGER :: ijpj,ijpjm1,ij,ijt,iju
4549    INTEGER :: itaille
4550
4551    REAL(wp), DIMENSION(jpiglo,4) :: ztab
4552    REAL(wp), DIMENSION(jpi,4,jpni) :: znorthgloio
4553    REAL(wp), DIMENSION(jpi,4) :: znorthloc
4554    !!----------------------------------------------------------------------
4555    !!  OPA 8.5, LODYC-IPSL (2002)
4556    !!----------------------------------------------------------------------
4557    ! If we get in this routine it s because : North fold condition and mpp with more
4558    !   than one proc across i : we deal only with the North condition
4559
4560    ! 0. Sign setting
4561    ! ---------------
4562
4563    ijpj=4
4564    ijpjm1=3
4565
4566
4567    ! put in znorthloc the last 4 jlines of pt2d
4568    DO jj = nlcj - ijpj +1, nlcj
4569       ij = jj - nlcj + ijpj
4570       znorthloc(:,ij)=pt2d(:,jj)
4571    END DO
4572
4573    IF (npolj /= 0 ) THEN
4574       ! Build in proc 0 of ncomm_north the znorthgloio
4575       znorthgloio(:,:,:) = 0_wp
4576#ifdef key_mpp_shmem
4577       not done : compiler error
4578#elif defined key_mpp_mpi
4579       itaille=jpi*ijpj
4580       CALL MPI_GATHER(znorthloc,itaille,MPI_DOUBLE_PRECISION,znorthgloio,itaille,MPI_DOUBLE_PRECISION,0,ncomm_north,ierr)
4581#endif
4582    ENDIF
4583
4584    IF (narea == north_root+1 ) THEN
4585       ! recover the global north array
4586       ztab(:,:) = 0_wp
4587
4588       DO jr = 1, ndim_rank_north
4589          jproc=nrank_north(jr)+1
4590          ildi=nldit (jproc)
4591          ilei=nleit (jproc)
4592          iilb=nimppt(jproc)
4593          DO jj=1,4
4594             DO ji=ildi,ilei
4595                ztab(ji+iilb-1,jj)=znorthgloio(ji,jj,jr)
4596             END DO
4597          END DO
4598       END DO
4599
4600
4601       ! 2. North-Fold boundary conditions
4602       ! ----------------------------------
4603
4604       SELECT CASE ( npolj )
4605
4606       CASE ( 3, 4 )                       ! *  North fold  T-point pivot
4607
4608          ztab( 1    ,ijpj) = 0.e0
4609          ztab(jpiglo,ijpj) = 0.e0
4610
4611          SELECT CASE ( cd_type )
4612
4613          CASE ( 'T' , 'W' , 'S' )                         ! T-, W-point
4614             DO ji = 2, jpiglo
4615                ijt = jpiglo-ji+2
4616                ztab(ji,ijpj) = psgn * ztab(ijt,ijpj-2)
4617             END DO
4618             DO ji = jpiglo/2+1, jpiglo
4619                ijt = jpiglo-ji+2
4620                ztab(ji,ijpjm1) = psgn * ztab(ijt,ijpjm1)
4621             END DO
4622
4623          CASE ( 'U' )                                     ! U-point
4624             DO ji = 1, jpiglo-1
4625                iju = jpiglo-ji+1
4626                ztab(ji,ijpj) = psgn * ztab(iju,ijpj-2)
4627             END DO
4628             DO ji = jpiglo/2, jpiglo-1
4629                iju = jpiglo-ji+1
4630                ztab(ji,ijpjm1) = psgn * ztab(iju,ijpjm1)
4631             END DO
4632
4633          CASE ( 'V' )                                     ! V-point
4634             DO ji = 2, jpiglo
4635                ijt = jpiglo-ji+2
4636                ztab(ji,ijpj-1) = psgn * ztab(ijt,ijpj-2)
4637                ztab(ji,ijpj  ) = psgn * ztab(ijt,ijpj-3)
4638             END DO
4639
4640          CASE ( 'F' , 'G' )                               ! F-point
4641             DO ji = 1, jpiglo-1
4642                iju = jpiglo-ji+1
4643                ztab(ji,ijpj-1) = psgn * ztab(iju,ijpj-2)
4644                ztab(ji,ijpj  ) = psgn * ztab(iju,ijpj-3)
4645             END DO
4646
4647          CASE ( 'I' )                                     ! ice U-V point
4648             ztab(2,ijpj) = psgn * ztab(3,ijpj-1)
4649             DO ji = 3, jpiglo
4650                iju = jpiglo - ji + 3
4651                ztab(ji,ijpj) = psgn * ztab(iju,ijpj-1)
4652             END DO
4653
4654          END SELECT
4655
4656       CASE ( 5, 6 )                        ! *  North fold  F-point pivot
4657
4658          ztab( 1 ,ijpj) = 0.e0
4659          ztab(jpiglo,ijpj) = 0.e0
4660
4661          SELECT CASE ( cd_type )
4662
4663          CASE ( 'T' , 'W' ,'S' )                          ! T-, W-point
4664             DO ji = 1, jpiglo
4665                ijt = jpiglo-ji+1
4666                ztab(ji,ijpj) = psgn * ztab(ijt,ijpj-1)
4667             END DO
4668
4669          CASE ( 'U' )                                     ! U-point
4670             DO ji = 1, jpiglo-1
4671                iju = jpiglo-ji
4672                ztab(ji,ijpj) = psgn * ztab(iju,ijpj-1)
4673             END DO
4674
4675          CASE ( 'V' )                                     ! V-point
4676             DO ji = 1, jpiglo
4677                ijt = jpiglo-ji+1
4678                ztab(ji,ijpj) = psgn * ztab(ijt,ijpj-2)
4679             END DO
4680             DO ji = jpiglo/2+1, jpiglo
4681                ijt = jpiglo-ji+1
4682                ztab(ji,ijpjm1) = psgn * ztab(ijt,ijpjm1)
4683             END DO
4684
4685          CASE ( 'F' , 'G' )                               ! F-point
4686             DO ji = 1, jpiglo-1
4687                iju = jpiglo-ji
4688                ztab(ji,ijpj  ) = psgn * ztab(iju,ijpj-2)
4689             END DO
4690             DO ji = jpiglo/2+1, jpiglo-1
4691                iju = jpiglo-ji
4692                ztab(ji,ijpjm1) = psgn * ztab(iju,ijpjm1)
4693             END DO
4694
4695             CASE ( 'I' )                                  ! ice U-V point
4696                ztab( 2 ,ijpj) = 0.e0
4697                DO ji = 2 , jpiglo-1
4698                   ijt = jpiglo - ji + 2
4699                   ztab(ji,ijpj)= 0.5 * ( ztab(ji,ijpj-1) + psgn * ztab(ijt,ijpj-1) )
4700                END DO
4701
4702          END SELECT
4703
4704       CASE DEFAULT                           ! *  closed : the code probably never go through
4705
4706            SELECT CASE ( cd_type) 
4707 
4708            CASE ( 'T' , 'U' , 'V' , 'W' )                 ! T-, U-, V-, W-points
4709               ztab(:, 1 ) = 0.e0
4710               ztab(:,ijpj) = 0.e0
4711
4712            CASE ( 'F' )                                   ! F-point
4713               ztab(:,ijpj) = 0.e0
4714
4715            CASE ( 'I' )                                   ! ice U-V point
4716               ztab(:, 1 ) = 0.e0
4717               ztab(:,ijpj) = 0.e0
4718
4719            END SELECT
4720
4721         END SELECT
4722
4723         !     End of slab
4724         !     ===========
4725
4726         !! Scatter back to pt2d
4727         DO jr = 1, ndim_rank_north
4728            jproc=nrank_north(jr)+1
4729            ildi=nldit (jproc)
4730            ilei=nleit (jproc)
4731            iilb=nimppt(jproc)
4732            DO jj=1,ijpj
4733               DO ji=ildi,ilei
4734                  znorthgloio(ji,jj,jr)=ztab(ji+iilb-1,jj)
4735               END DO
4736            END DO
4737         END DO
4738
4739      ENDIF      ! only done on proc 0 of ncomm_north
4740
4741#ifdef key_mpp_shmem
4742      not done yet in shmem : compiler error
4743#elif key_mpp_mpi
4744      IF ( npolj /= 0 ) THEN
4745         itaille=jpi*ijpj
4746         CALL MPI_SCATTER(znorthgloio,itaille,MPI_DOUBLE_PRECISION,znorthloc,itaille,MPI_DOUBLE_PRECISION,0,ncomm_north,ierr)
4747      ENDIF
4748#endif
4749
4750      ! put in the last ijpj jlines of pt2d znorthloc
4751      DO jj = nlcj - ijpj + 1 , nlcj
4752         ij = jj - nlcj + ijpj
4753         pt2d(:,jj)= znorthloc(:,ij)
4754      END DO
4755
4756   END SUBROUTINE mpp_lbc_north_2d
4757
4758
4759   SUBROUTINE mpp_lbc_north_e ( pt2d, cd_type, psgn)
4760    !!---------------------------------------------------------------------
4761    !!                   ***  routine mpp_lbc_north_2d  ***
4762    !!
4763    !! ** Purpose :
4764    !!      Ensure proper north fold horizontal bondary condition in mpp configuration
4765    !!      in case of jpn1 > 1 (for 2d array with outer extra halo)
4766    !!
4767    !! ** Method :
4768    !!      Gather the 4+2*jpr2dj northern lines of the global domain on 1 processor and
4769    !!      apply lbc north-fold on this sub array. Then scatter the fold array
4770    !!      back to the processors.
4771    !!
4772    !! History :
4773    !!   8.5  !  03-09  (J.M. Molines ) For mpp folding condition at north
4774    !!                                  from lbc routine
4775    !!   9.0  !  03-12  (J.M. Molines ) encapsulation into lib_mpp, coding rules of lbc_lnk
4776    !!   9.0  !  05-09  (R. Benshila )   adapt mpp_lbc_north_2d
4777    !!----------------------------------------------------------------------
4778
4779    !! * Arguments
4780    CHARACTER(len=1), INTENT( in ) ::   &
4781         cd_type       ! nature of pt2d grid-points
4782    !             !   = T ,  U , V , F or W  gridpoints
4783    REAL(wp), DIMENSION(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj), INTENT( inout ) ::   &
4784         pt2d          ! 2D array on which the boundary condition is applied
4785    REAL(wp), INTENT( in ) ::   &
4786         psgn          ! control of the sign change
4787    !             !   = -1. , the sign is changed if north fold boundary
4788    !             !   =  1. , the sign is kept  if north fold boundary
4789
4790
4791    !! * Local declarations
4792
4793    INTEGER :: ji, jj,  jr, jproc, jl
4794    INTEGER :: ierr
4795    INTEGER :: ildi,ilei,iilb
4796    INTEGER :: ijpj,ijpjm1,ij,ijt,iju, iprecj
4797    INTEGER :: itaille
4798
4799    REAL(wp), DIMENSION(jpiglo,1-jpr2dj:4+jpr2dj) :: ztab
4800    REAL(wp), DIMENSION(jpi,1-jpr2dj:4+jpr2dj,jpni) :: znorthgloio
4801    REAL(wp), DIMENSION(jpi,1-jpr2dj:4+jpr2dj) :: znorthloc
4802
4803    ! If we get in this routine it s because : North fold condition and mpp with more
4804    !   than one proc across i : we deal only with the North condition
4805
4806    ! 0. Sign setting
4807    ! ---------------
4808
4809    ijpj=4
4810    ijpjm1=3
4811    iprecj = jpr2dj+jprecj
4812
4813    ! put in znorthloc the last 4 jlines of pt2d
4814    DO jj = nlcj - ijpj + 1 - jpr2dj, nlcj +jpr2dj
4815       ij = jj - nlcj + ijpj
4816       znorthloc(:,ij)=pt2d(1:jpi,jj)
4817    END DO
4818
4819    IF (npolj /= 0 ) THEN
4820       ! Build in proc 0 of ncomm_north the znorthgloio
4821       znorthgloio(:,:,:) = 0_wp
4822#ifdef key_mpp_shmem
4823       not done : compiler error
4824#elif defined key_mpp_mpi
4825       itaille=jpi*(ijpj+2*jpr2dj)
4826       CALL MPI_GATHER(znorthloc(1,1-jpr2dj),itaille,MPI_DOUBLE_PRECISION, &
4827                     & znorthgloio(1,1-jpr2dj,1),itaille,MPI_DOUBLE_PRECISION,0,ncomm_north,ierr)
4828#endif
4829    ENDIF
4830
4831    IF (narea == north_root+1 ) THEN
4832       ! recover the global north array
4833       ztab(:,:) = 0_wp
4834
4835       DO jr = 1, ndim_rank_north
4836          jproc=nrank_north(jr)+1
4837          ildi=nldit (jproc)
4838          ilei=nleit (jproc)
4839          iilb=nimppt(jproc)
4840          DO jj=1-jpr2dj,ijpj+jpr2dj
4841             DO ji=ildi,ilei
4842                ztab(ji+iilb-1,jj)=znorthgloio(ji,jj,jr)
4843             END DO
4844          END DO
4845       END DO
4846
4847
4848       ! 2. North-Fold boundary conditions
4849       ! ----------------------------------
4850
4851       SELECT CASE ( npolj )
4852
4853       CASE ( 3, 4 )                       ! *  North fold  T-point pivot
4854
4855          ztab( 1    ,ijpj:ijpj+jpr2dj) = 0.e0
4856          ztab(jpiglo,ijpj:ijpj+jpr2dj) = 0.e0
4857
4858          SELECT CASE ( cd_type )
4859
4860          CASE ( 'T' , 'W' , 'S' )                         ! T-, W-point
4861             DO jl =0, iprecj-1
4862                DO ji = 2, jpiglo
4863                   ijt = jpiglo-ji+2
4864                   ztab(ji,ijpj+jl) = psgn * ztab(ijt,ijpj-2-jl)
4865                END DO
4866             END DO
4867             DO ji = jpiglo/2+1, jpiglo
4868                ijt = jpiglo-ji+2
4869                ztab(ji,ijpjm1) = psgn * ztab(ijt,ijpjm1)
4870             END DO
4871
4872          CASE ( 'U' )                                     ! U-point
4873             DO jl =0, iprecj-1
4874                DO ji = 1, jpiglo-1
4875                   iju = jpiglo-ji+1
4876                   ztab(ji,ijpj+jl) = psgn * ztab(iju,ijpj-2-jl)
4877                END DO
4878             END DO
4879             DO ji = jpiglo/2, jpiglo-1
4880                iju = jpiglo-ji+1
4881                ztab(ji,ijpjm1) = psgn * ztab(iju,ijpjm1)
4882             END DO
4883
4884          CASE ( 'V' )                                     ! V-point
4885            DO jl =-1, iprecj-1
4886               DO ji = 2, jpiglo
4887                  ijt = jpiglo-ji+2
4888                  ztab(ji,ijpj+jl) = psgn * ztab(ijt,ijpj-3-jl)
4889               END DO
4890            END DO
4891
4892          CASE ( 'F' , 'G' )                               ! F-point
4893            DO jl =-1, iprecj-1
4894               DO ji = 1, jpiglo-1
4895                  iju = jpiglo-ji+1
4896                  ztab(ji,ijpj+jl) = psgn * ztab(iju,ijpj-3-jl)
4897               END DO
4898             END DO
4899
4900          CASE ( 'I' )                                     ! ice U-V point
4901             DO jl =0, iprecj-1
4902                ztab(2,ijpj+jl) = psgn * ztab(3,ijpj-1+jl)
4903                DO ji = 3, jpiglo
4904                   iju = jpiglo - ji + 3
4905                   ztab(ji,ijpj+jl) = psgn * ztab(iju,ijpj-1-jl)
4906                END DO
4907             END DO
4908
4909          END SELECT
4910
4911       CASE ( 5, 6 )                        ! *  North fold  F-point pivot
4912
4913          ztab( 1 ,ijpj:ijpj+jpr2dj) = 0.e0
4914          ztab(jpiglo,ijpj:ijpj+jpr2dj) = 0.e0
4915
4916          SELECT CASE ( cd_type )
4917
4918          CASE ( 'T' , 'W' ,'S' )                          ! T-, W-point
4919             DO jl = 0, iprecj-1
4920                DO ji = 1, jpiglo
4921                   ijt = jpiglo-ji+1
4922                   ztab(ji,ijpj+jl) = psgn * ztab(ijt,ijpj-1-jl)
4923                END DO
4924             END DO
4925
4926          CASE ( 'U' )                                     ! U-point
4927             DO jl = 0, iprecj-1
4928                DO ji = 1, jpiglo-1
4929                   iju = jpiglo-ji
4930                   ztab(ji,ijpj+jl) = psgn * ztab(iju,ijpj-1-jl)
4931                END DO
4932             END DO
4933
4934          CASE ( 'V' )                                     ! V-point
4935             DO jl = 0, iprecj-1
4936                DO ji = 1, jpiglo
4937                   ijt = jpiglo-ji+1
4938                   ztab(ji,ijpj+jl) = psgn * ztab(ijt,ijpj-2-jl)
4939                END DO
4940             END DO
4941             DO ji = jpiglo/2+1, jpiglo
4942                ijt = jpiglo-ji+1
4943                ztab(ji,ijpjm1) = psgn * ztab(ijt,ijpjm1)
4944             END DO
4945
4946          CASE ( 'F' , 'G' )                               ! F-point
4947             DO jl = 0, iprecj-1
4948                DO ji = 1, jpiglo-1
4949                   iju = jpiglo-ji
4950                   ztab(ji,ijpj+jl) = psgn * ztab(iju,ijpj-2-jl)
4951                END DO
4952             END DO
4953             DO ji = jpiglo/2+1, jpiglo-1
4954                iju = jpiglo-ji
4955                ztab(ji,ijpjm1) = psgn * ztab(iju,ijpjm1)
4956             END DO
4957
4958             CASE ( 'I' )                                  ! ice U-V point
4959                ztab( 2 ,ijpj:ijpj+jpr2dj) = 0.e0
4960                DO jl = 0, jpr2dj
4961                   DO ji = 2 , jpiglo-1
4962                      ijt = jpiglo - ji + 2
4963                      ztab(ji,ijpj+jl)= 0.5 * ( ztab(ji,ijpj-1-jl) + psgn * ztab(ijt,ijpj-1-jl) )
4964                   END DO
4965                END DO
4966
4967          END SELECT
4968
4969       CASE DEFAULT                           ! *  closed : the code probably never go through
4970
4971            SELECT CASE ( cd_type) 
4972 
4973            CASE ( 'T' , 'U' , 'V' , 'W' )                 ! T-, U-, V-, W-points
4974               ztab(:, 1:1-jpr2dj     ) = 0.e0
4975               ztab(:,ijpj:ijpj+jpr2dj) = 0.e0
4976
4977            CASE ( 'F' )                                   ! F-point
4978               ztab(:,ijpj:ijpj+jpr2dj) = 0.e0
4979
4980            CASE ( 'I' )                                   ! ice U-V point
4981               ztab(:, 1:1-jpr2dj     ) = 0.e0
4982               ztab(:,ijpj:ijpj+jpr2dj) = 0.e0
4983
4984            END SELECT
4985
4986         END SELECT
4987
4988         !     End of slab
4989         !     ===========
4990
4991         !! Scatter back to pt2d
4992         DO jr = 1, ndim_rank_north
4993            jproc=nrank_north(jr)+1
4994            ildi=nldit (jproc)
4995            ilei=nleit (jproc)
4996            iilb=nimppt(jproc)
4997            DO jj=1-jpr2dj,ijpj+jpr2dj
4998               DO ji=ildi,ilei
4999                  znorthgloio(ji,jj,jr)=ztab(ji+iilb-1,jj)
5000               END DO
5001            END DO
5002         END DO
5003
5004      ENDIF      ! only done on proc 0 of ncomm_north
5005
5006#ifdef key_mpp_shmem
5007      not done yet in shmem : compiler error
5008#elif key_mpp_mpi
5009      IF ( npolj /= 0 ) THEN
5010         itaille=jpi*(ijpj+2*jpr2dj)
5011         CALL MPI_SCATTER(znorthgloio(1,1-jpr2dj,1),itaille,MPI_DOUBLE_PRECISION, &
5012                        & znorthloc(1,1-jpr2dj),itaille,MPI_DOUBLE_PRECISION,0,ncomm_north,ierr)
5013      ENDIF
5014#endif
5015
5016      ! put in the last ijpj jlines of pt2d znorthloc
5017      DO jj = nlcj - ijpj  -jpr2dj + 1 , nlcj +jpr2dj
5018         ij = jj - nlcj + ijpj 
5019         pt2d(1:jpi,jj)= znorthloc(:,ij)
5020      END DO
5021
5022   END SUBROUTINE mpp_lbc_north_e
5023
5024
5025   !!!!!
5026
5027
5028   !!
5029   !!    This is valid on IBM machine ONLY.
5030   !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! -*- Mode: F90 -*- !!!!!!!!!!!!!!!!!!!!!!!!!!!!!
5031   !! mpi_init_opa.f90 : Redefinition du point d'entree MPI_INIT de la bibliotheque
5032   !!                MPI afin de faire, en plus de l'initialisation de
5033   !!                l'environnement MPI, l'allocation d'une zone tampon
5034   !!                qui sera ulterieurement utilisee automatiquement lors
5035   !!                de tous les envois de messages par MPI_BSEND
5036   !!
5037   !! Auteur : CNRS/IDRIS
5038   !! Date   : Tue Nov 13 12:02:14 2001
5039   !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
5040
5041   SUBROUTINE mpi_init_opa(code)
5042      IMPLICIT NONE
5043
5044!$AGRIF_DO_NOT_TREAT
5045#     include <mpif.h>
5046!$AGRIF_END_DO_NOT_TREAT
5047
5048      INTEGER                                 :: code,rang,ierr
5049      LOGICAL                                 :: mpi_was_called
5050 
5051      ! La valeur suivante doit etre au moins egale a la taille
5052      ! du plus grand message qui sera transfere dans le programme
5053      ! (de toute facon, il y aura un message d'erreur si cette
5054      ! valeur s'avere trop petite)
5055      INTEGER                                 :: taille_tampon
5056      CHARACTER(len=9)                        :: taille_tampon_alphanum
5057      REAL(kind=8), ALLOCATABLE, DIMENSION(:) :: tampon
5058 
5059      ! Le point d'entree dans la bibliotheque MPI elle-meme
5060      CALL mpi_initialized(mpi_was_called, code)
5061      IF ( code /= MPI_SUCCESS ) THEN
5062        CALL ctl_stop( ' lib_mpp: Error in routine mpi_initialized' )
5063        CALL mpi_abort( mpi_comm_world, code, ierr )
5064      ENDIF
5065
5066      IF ( .NOT. mpi_was_called ) THEN
5067         CALL mpi_init(code)
5068         CALL mpi_comm_dup( mpi_comm_world, mpi_comm_opa, code)
5069         IF ( code /= MPI_SUCCESS ) THEN
5070            CALL ctl_stop( ' lib_mpp: Error in routine mpi_comm_dup' )
5071            CALL mpi_abort( mpi_comm_world, code, ierr )
5072         ENDIF
5073      ENDIF
5074      ! La definition de la zone tampon pour les futurs envois
5075      ! par MPI_BSEND (on alloue une fois pour toute cette zone
5076      ! tampon, qui sera automatiquement utilisee lors de chaque
5077      ! appel  a MPI_BSEND).
5078      ! La desallocation sera implicite quand on sortira de
5079      ! l'environnement MPI.
5080
5081      ! Recuperation de la valeur de la variable d'environnement
5082      ! BUFFER_LENGTH
5083      ! qui, si elle est definie, doit contenir une valeur superieure
5084      ! a  la taille en octets du plus gros message
5085      CALL getenv('BUFFER_LENGTH',taille_tampon_alphanum)
5086 
5087      ! Si la variable BUFFER_LENGTH n'est pas positionnee, on lui met par
5088      ! defaut la plus grande valeur de la variable MP_EAGER_LIMIT, soit
5089      ! 65 536 octets
5090      IF (taille_tampon_alphanum == ' ') THEN
5091         taille_tampon = 65536
5092      ELSE
5093         READ(taille_tampon_alphanum,'(i9)') taille_tampon
5094      END IF
5095
5096      ! On est limite en mode d'adressage 32 bits a  1750 Mo pour la zone
5097      ! "data" soit 7 segments, c.-a -d. 1750/8 = 210 Mo
5098      IF (taille_tampon > 210000000) THEN
5099         CALL ctl_stop( ' lib_mpp: Attention la valeur BUFFER_LENGTH doit etre <= 210000000' )
5100         CALL mpi_abort(MPI_COMM_WORLD,2,code)
5101      END IF
5102
5103      CALL mpi_comm_rank(MPI_COMM_OPA,rang,code)
5104      IF (rang == 0 ) PRINT *,'Taille du buffer alloue : ',taille_tampon
5105
5106      ! Allocation du tampon et attachement
5107      ALLOCATE(tampon(taille_tampon))
5108      CALL mpi_buffer_attach(tampon,taille_tampon,code)
5109
5110   END SUBROUTINE mpi_init_opa
5111
5112#else
5113   !!----------------------------------------------------------------------
5114   !!   Default case:            Dummy module        share memory computing
5115   !!----------------------------------------------------------------------
5116   INTERFACE mpp_sum
5117      MODULE PROCEDURE mpp_sum_a2s, mpp_sum_as, mpp_sum_ai, mpp_sum_s, mpp_sum_i
5118   END INTERFACE
5119   INTERFACE mpp_max
5120      MODULE PROCEDURE mppmax_a_real, mppmax_real
5121   END INTERFACE
5122   INTERFACE mpp_min
5123      MODULE PROCEDURE mppmin_a_int, mppmin_int, mppmin_a_real, mppmin_real
5124   END INTERFACE
5125   INTERFACE mpp_isl
5126      MODULE PROCEDURE mppisl_a_int, mppisl_int, mppisl_a_real, mppisl_real
5127   END INTERFACE
5128   INTERFACE mppobc
5129      MODULE PROCEDURE mppobc_1d, mppobc_2d, mppobc_3d, mppobc_4d
5130   END INTERFACE
5131  INTERFACE mpp_minloc
5132     MODULE PROCEDURE mpp_minloc2d ,mpp_minloc3d
5133  END INTERFACE
5134  INTERFACE mpp_maxloc
5135     MODULE PROCEDURE mpp_maxloc2d ,mpp_maxloc3d
5136  END INTERFACE
5137
5138
5139   LOGICAL, PUBLIC, PARAMETER ::   lk_mpp = .FALSE.      !: mpp flag
5140
5141CONTAINS
5142
5143   FUNCTION mynode(localComm) RESULT (function_value)
5144      INTEGER, OPTIONAL :: localComm
5145      function_value = 0
5146   END FUNCTION mynode
5147
5148   SUBROUTINE mppsync                       ! Dummy routine
5149   END SUBROUTINE mppsync
5150
5151   SUBROUTINE mpp_sum_as( parr, kdim )      ! Dummy routine
5152      REAL   , DIMENSION(:) :: parr
5153      INTEGER               :: kdim
5154      WRITE(*,*) 'mpp_sum_as: You should not have seen this print! error?', kdim, parr(1)
5155   END SUBROUTINE mpp_sum_as
5156
5157   SUBROUTINE mpp_sum_a2s( parr, kdim )      ! Dummy routine
5158      REAL   , DIMENSION(:,:) :: parr
5159      INTEGER               :: kdim
5160      WRITE(*,*) 'mpp_sum_a2s: You should not have seen this print! error?', kdim, parr(1,1)
5161   END SUBROUTINE mpp_sum_a2s
5162
5163   SUBROUTINE mpp_sum_ai( karr, kdim )      ! Dummy routine
5164      INTEGER, DIMENSION(:) :: karr
5165      INTEGER               :: kdim
5166      WRITE(*,*) 'mpp_sum_ai: You should not have seen this print! error?', kdim, karr(1)
5167   END SUBROUTINE mpp_sum_ai
5168
5169   SUBROUTINE mpp_sum_s( psca )            ! Dummy routine
5170      REAL                  :: psca
5171      WRITE(*,*) 'mpp_sum_s: You should not have seen this print! error?', psca
5172   END SUBROUTINE mpp_sum_s
5173
5174   SUBROUTINE mpp_sum_i( kint )            ! Dummy routine
5175      integer               :: kint
5176      WRITE(*,*) 'mpp_sum_i: You should not have seen this print! error?', kint
5177   END SUBROUTINE mpp_sum_i
5178
5179   SUBROUTINE mppmax_a_real( parr, kdim )
5180      REAL   , DIMENSION(:) :: parr
5181      INTEGER               :: kdim
5182      WRITE(*,*) 'mppmax_a_real: You should not have seen this print! error?', kdim, parr(1)
5183   END SUBROUTINE mppmax_a_real
5184
5185   SUBROUTINE mppmax_real( psca )
5186      REAL                  :: psca
5187      WRITE(*,*) 'mppmax_real: You should not have seen this print! error?', psca
5188   END SUBROUTINE mppmax_real
5189
5190   SUBROUTINE mppmin_a_real( parr, kdim )
5191      REAL   , DIMENSION(:) :: parr
5192      INTEGER               :: kdim
5193      WRITE(*,*) 'mppmin_a_real: You should not have seen this print! error?', kdim, parr(1)
5194   END SUBROUTINE mppmin_a_real
5195
5196   SUBROUTINE mppmin_real( psca )
5197      REAL                  :: psca
5198      WRITE(*,*) 'mppmin_real: You should not have seen this print! error?', psca
5199   END SUBROUTINE mppmin_real
5200
5201   SUBROUTINE mppmin_a_int( karr, kdim )
5202      INTEGER, DIMENSION(:) :: karr
5203      INTEGER               :: kdim
5204      WRITE(*,*) 'mppmin_a_int: You should not have seen this print! error?', kdim, karr(1)
5205   END SUBROUTINE mppmin_a_int
5206
5207   SUBROUTINE mppmin_int( kint )
5208      INTEGER               :: kint
5209      WRITE(*,*) 'mppmin_int: You should not have seen this print! error?', kint
5210   END SUBROUTINE mppmin_int
5211
5212   SUBROUTINE mppobc_1d( parr, kd1, kd2, kl, kk, ktype, kij )
5213    INTEGER  ::   kd1, kd2, kl , kk, ktype, kij
5214    REAL, DIMENSION(:) ::   parr           ! variable array
5215      WRITE(*,*) 'mppobc: You should not have seen this print! error?',   &
5216         &        parr(1), kd1, kd2, kl, kk, ktype, kij
5217   END SUBROUTINE mppobc_1d
5218
5219   SUBROUTINE mppobc_2d( parr, kd1, kd2, kl, kk, ktype, kij )
5220    INTEGER  ::   kd1, kd2, kl , kk, ktype, kij
5221    REAL, DIMENSION(:,:) ::   parr           ! variable array
5222      WRITE(*,*) 'mppobc: You should not have seen this print! error?',   &
5223         &        parr(1,1), kd1, kd2, kl, kk, ktype, kij
5224   END SUBROUTINE mppobc_2d
5225
5226   SUBROUTINE mppobc_3d( parr, kd1, kd2, kl, kk, ktype, kij )
5227    INTEGER  ::   kd1, kd2, kl , kk, ktype, kij
5228    REAL, DIMENSION(:,:,:) ::   parr           ! variable array
5229      WRITE(*,*) 'mppobc: You should not have seen this print! error?',   &
5230         &        parr(1,1,1), kd1, kd2, kl, kk, ktype, kij
5231   END SUBROUTINE mppobc_3d
5232
5233   SUBROUTINE mppobc_4d( parr, kd1, kd2, kl, kk, ktype, kij )
5234    INTEGER  ::   kd1, kd2, kl , kk, ktype, kij
5235    REAL, DIMENSION(:,:,:,:) ::   parr           ! variable array
5236      WRITE(*,*) 'mppobc: You should not have seen this print! error?',   &
5237         &        parr(1,1,1,1), kd1, kd2, kl, kk, ktype, kij
5238   END SUBROUTINE mppobc_4d
5239
5240
5241   SUBROUTINE mpplnks( parr )            ! Dummy routine
5242      REAL, DIMENSION(:,:) :: parr
5243      WRITE(*,*) 'mpplnks: You should not have seen this print! error?', parr(1,1)
5244   END SUBROUTINE mpplnks
5245
5246   SUBROUTINE mppisl_a_int( karr, kdim )
5247      INTEGER, DIMENSION(:) :: karr
5248      INTEGER               :: kdim
5249      WRITE(*,*) 'mppisl_a_int: You should not have seen this print! error?', kdim, karr(1)
5250   END SUBROUTINE mppisl_a_int
5251
5252   SUBROUTINE mppisl_int( kint )
5253      INTEGER               :: kint
5254      WRITE(*,*) 'mppisl_int: You should not have seen this print! error?', kint
5255   END SUBROUTINE mppisl_int
5256
5257   SUBROUTINE mppisl_a_real( parr, kdim )
5258      REAL   , DIMENSION(:) :: parr
5259      INTEGER               :: kdim
5260      WRITE(*,*) 'mppisl_a_real: You should not have seen this print! error?', kdim, parr(1)
5261   END SUBROUTINE mppisl_a_real
5262
5263   SUBROUTINE mppisl_real( psca )
5264      REAL                  :: psca
5265      WRITE(*,*) 'mppisl_real: You should not have seen this print! error?', psca
5266   END SUBROUTINE mppisl_real
5267
5268   SUBROUTINE mpp_minloc2d ( ptab, pmask, pmin, ki, kj )
5269      REAL                   :: pmin
5270      REAL , DIMENSION (:,:) :: ptab, pmask
5271      INTEGER :: ki, kj
5272      WRITE(*,*) 'mppisl_real: You should not have seen this print! error?', pmin, ki, kj
5273      WRITE(*,*) '   "      ":             "                 "            ', ptab(1,1), pmask(1,1)
5274   END SUBROUTINE mpp_minloc2d
5275
5276   SUBROUTINE mpp_minloc3d ( ptab, pmask, pmin, ki, kj, kk )
5277      REAL                     :: pmin
5278      REAL , DIMENSION (:,:,:) :: ptab, pmask
5279      INTEGER :: ki, kj, kk
5280      WRITE(*,*) 'mppisl_real: You should not have seen this print! error?', pmin, ki, kj, kk
5281      WRITE(*,*) '   "      ":             "                 "            ', ptab(1,1,1), pmask(1,1,1)
5282   END SUBROUTINE mpp_minloc3d
5283
5284   SUBROUTINE mpp_maxloc2d ( ptab, pmask, pmax, ki, kj )
5285      REAL                   :: pmax
5286      REAL , DIMENSION (:,:) :: ptab, pmask
5287      INTEGER :: ki, kj
5288      WRITE(*,*) 'mppisl_real: You should not have seen this print! error?', pmax, ki, kj
5289      WRITE(*,*) '   "      ":             "                 "            ', ptab(1,1), pmask(1,1)
5290   END SUBROUTINE mpp_maxloc2d
5291
5292   SUBROUTINE mpp_maxloc3d ( ptab, pmask, pmax, ki, kj, kk )
5293      REAL                     :: pmax
5294      REAL , DIMENSION (:,:,:) :: ptab, pmask
5295      INTEGER :: ki, kj, kk
5296      WRITE(*,*) 'mppisl_real: You should not have seen this print! error?', pmax, ki, kj, kk
5297      WRITE(*,*) '   "      ":             "                 "            ', ptab(1,1,1), pmask(1,1,1)
5298   END SUBROUTINE mpp_maxloc3d
5299
5300   SUBROUTINE mppstop
5301      WRITE(*,*) 'mppstop: You should not have seen this print! error?'
5302   END SUBROUTINE mppstop
5303
5304#endif
5305   !!----------------------------------------------------------------------
5306END MODULE lib_mpp
Note: See TracBrowser for help on using the repository browser.