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.
mppini.F90 in NEMO/branches/2019/dev_r11470_HPC_12_mpi3/src/OCE/LBC – NEMO

source: NEMO/branches/2019/dev_r11470_HPC_12_mpi3/src/OCE/LBC/mppini.F90 @ 11940

Last change on this file since 11940 was 11940, checked in by mocavero, 4 years ago

Add MPI3 neighbourhood collectives halo exchange in LBC and call it in tracer advection FCT scheme #2011

  • Property svn:keywords set to Id
File size: 61.8 KB
Line 
1MODULE mppini
2   !!======================================================================
3   !!                       ***  MODULE mppini   ***
4   !! Ocean initialization : distributed memory computing initialization
5   !!======================================================================
6   !! History :  6.0  !  1994-11  (M. Guyon)  Original code
7   !!  OPA       7.0  !  1995-04  (J. Escobar, M. Imbard)
8   !!            8.0  !  1998-05  (M. Imbard, J. Escobar, L. Colombet )  SHMEM and MPI versions
9   !!  NEMO      1.0  !  2004-01  (G. Madec, J.M Molines)  F90 : free form , north fold jpni > 1
10   !!            3.4  ! 2011-10  (A. C. Coward, NOCS & J. Donners, PRACE) add mpp_init_nfdcom
11   !!            3.   ! 2013-06  (I. Epicoco, S. Mocavero, CMCC) mpp_init_nfdcom: setup avoiding MPI communication
12   !!            4.0  !  2016-06  (G. Madec)  use domain configuration file instead of bathymetry file
13   !!            4.0  !  2017-06  (J.M. Molines, T. Lovato) merge of mppini and mppini_2
14   !!----------------------------------------------------------------------
15
16   !!----------------------------------------------------------------------
17   !!  mpp_init          : Lay out the global domain over processors with/without land processor elimination
18   !!  mpp_init_mask     : Read global bathymetric information to facilitate land suppression
19   !!  mpp_init_ioipsl   : IOIPSL initialization in mpp
20   !!  mpp_init_partition: Calculate MPP domain decomposition
21   !!  factorise         : Calculate the factors of the no. of MPI processes
22   !!  mpp_init_nfdcom   : Setup for north fold exchanges with explicit point-to-point messaging
23   !!----------------------------------------------------------------------
24   USE dom_oce        ! ocean space and time domain
25   USE bdy_oce        ! open BounDarY 
26   !
27   USE lbcnfd  , ONLY : isendto, nsndto, nfsloop, nfeloop   ! Setup of north fold exchanges
28   USE lib_mpp        ! distribued memory computing library
29   USE iom            ! nemo I/O library
30   USE ioipsl         ! I/O IPSL library
31   USE in_out_manager ! I/O Manager
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC mpp_init       ! called by opa.F90
37
38   INTEGER :: numbot = -1  ! 'bottom_level' local logical unit
39   INTEGER :: numbdy = -1  ! 'bdy_msk'      local logical unit
40
41   !!----------------------------------------------------------------------
42   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
43   !! $Id$
44   !! Software governed by the CeCILL license (see ./LICENSE)
45   !!----------------------------------------------------------------------
46CONTAINS
47
48#if ! defined key_mpp_mpi
49   !!----------------------------------------------------------------------
50   !!   Default option :                            shared memory computing
51   !!----------------------------------------------------------------------
52
53   SUBROUTINE mpp_init
54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE mpp_init  ***
56      !!
57      !! ** Purpose :   Lay out the global domain over processors.
58      !!
59      !! ** Method  :   Shared memory computing, set the local processor
60      !!              variables to the value of the global domain
61      !!----------------------------------------------------------------------
62      !
63      jpimax = jpiglo
64      jpjmax = jpjglo
65      jpi    = jpiglo
66      jpj    = jpjglo
67      jpk    = jpkglo
68      jpim1  = jpi-1                                            ! inner domain indices
69      jpjm1  = jpj-1                                            !   "           "
70      jpkm1  = MAX( 1, jpk-1 )                                  !   "           "
71      jpij   = jpi*jpj
72      jpni   = 1
73      jpnj   = 1
74      jpnij  = jpni*jpnj
75      nimpp  = 1           !
76      njmpp  = 1
77      nlci   = jpi
78      nlcj   = jpj
79      nldi   = 1
80      nldj   = 1
81      nlei   = jpi
82      nlej   = jpj
83      nbondi = 2
84      nbondj = 2
85      nidom  = FLIO_DOM_NONE
86      npolj = 0
87      IF( jperio == 3 .OR. jperio == 4 )   npolj = 3
88      IF( jperio == 5 .OR. jperio == 6 )   npolj = 5
89      l_Iperio = jpni == 1 .AND. (jperio == 1 .OR. jperio == 4 .OR. jperio == 6 .OR. jperio == 7)
90      l_Jperio = jpnj == 1 .AND. (jperio == 2 .OR. jperio == 7)
91      !
92      IF(lwp) THEN
93         WRITE(numout,*)
94         WRITE(numout,*) 'mpp_init : NO massively parallel processing'
95         WRITE(numout,*) '~~~~~~~~ '
96         WRITE(numout,*) '   l_Iperio = ', l_Iperio, '    l_Jperio = ', l_Jperio 
97         WRITE(numout,*) '     npolj  = ',   npolj , '      njmpp  = ', njmpp
98      ENDIF
99      !
100      IF(  jpni /= 1 .OR. jpnj /= 1 .OR. jpnij /= 1 )                                     &
101         CALL ctl_stop( 'mpp_init: equality  jpni = jpnj = jpnij = 1 is not satisfied',   &
102            &           'the domain is lay out for distributed memory computing!' )
103         !
104   END SUBROUTINE mpp_init
105
106#else
107   !!----------------------------------------------------------------------
108   !!   'key_mpp_mpi'                     MPI massively parallel processing
109   !!----------------------------------------------------------------------
110
111
112   SUBROUTINE mpp_init
113      !!----------------------------------------------------------------------
114      !!                  ***  ROUTINE mpp_init  ***
115      !!                   
116      !! ** Purpose :   Lay out the global domain over processors.
117      !!      If land processors are to be eliminated, this program requires the
118      !!      presence of the domain configuration file. Land processors elimination
119      !!      is performed if jpni x jpnj /= jpnij. In this case, using the MPP_PREP
120      !!      preprocessing tool, help for defining the best cutting out.
121      !!
122      !! ** Method  :   Global domain is distributed in smaller local domains.
123      !!      Periodic condition is a function of the local domain position
124      !!      (global boundary or neighbouring domain) and of the global
125      !!      periodic
126      !!      Type :         jperio global periodic condition
127      !!
128      !! ** Action : - set domain parameters
129      !!                    nimpp     : longitudinal index
130      !!                    njmpp     : latitudinal  index
131      !!                    narea     : number for local area
132      !!                    nlci      : first dimension
133      !!                    nlcj      : second dimension
134      !!                    nbondi    : mark for "east-west local boundary"
135      !!                    nbondj    : mark for "north-south local boundary"
136      !!                    nproc     : number for local processor
137      !!                    noea      : number for local neighboring processor
138      !!                    nowe      : number for local neighboring processor
139      !!                    noso      : number for local neighboring processor
140      !!                    nono      : number for local neighboring processor
141      !!----------------------------------------------------------------------
142      INTEGER ::   ji, jj, jn, jproc, jarea   ! dummy loop indices
143      INTEGER ::   inijmin
144      INTEGER ::   i2add
145      INTEGER ::   inum                       ! local logical unit
146      INTEGER ::   idir, ifreq, icont         ! local integers
147      INTEGER ::   ii, il1, ili, imil         !   -       -
148      INTEGER ::   ij, il2, ilj, ijm1         !   -       -
149      INTEGER ::   iino, ijno, iiso, ijso     !   -       -
150      INTEGER ::   iiea, ijea, iiwe, ijwe     !   -       -
151      INTEGER ::   iarea0                     !   -       -
152      INTEGER ::   ierr, ios                  !
153      INTEGER ::   inbi, inbj, iimax,  ijmax, icnt1, icnt2
154      LOGICAL ::   llbest, llauto
155      LOGICAL ::   llwrtlay
156      LOGICAL ::   ln_listonly
157      INTEGER, ALLOCATABLE, DIMENSION(:)     ::   iin, ii_nono, ii_noea          ! 1D workspace
158      INTEGER, ALLOCATABLE, DIMENSION(:)     ::   ijn, ii_noso, ii_nowe          !  -     -
159      INTEGER, ALLOCATABLE, DIMENSION(:,:) ::   iimppt, ilci, ibondi, ipproc   ! 2D workspace
160      INTEGER, ALLOCATABLE, DIMENSION(:,:) ::   ijmppt, ilcj, ibondj, ipolj    !  -     -
161      INTEGER, ALLOCATABLE, DIMENSION(:,:) ::   ilei, ildi, iono, ioea         !  -     -
162      INTEGER, ALLOCATABLE, DIMENSION(:,:) ::   ilej, ildj, ioso, iowe         !  -     -
163      LOGICAL, ALLOCATABLE, DIMENSION(:,:) ::   llisoce                        !  -     -
164      NAMELIST/nambdy/ ln_bdy, nb_bdy, ln_coords_file, cn_coords_file,           &
165           &             ln_mask_file, cn_mask_file, cn_dyn2d, nn_dyn2d_dta,     &
166           &             cn_dyn3d, nn_dyn3d_dta, cn_tra, nn_tra_dta,             & 
167           &             ln_tra_dmp, ln_dyn3d_dmp, rn_time_dmp, rn_time_dmp_out, &
168           &             cn_ice, nn_ice_dta,                                     &
169           &             ln_vol, nn_volctl, nn_rimwidth
170      NAMELIST/nammpp/ jpni, jpnj, ln_nnogather, ln_listonly
171      !!----------------------------------------------------------------------
172      !
173      llwrtlay = lwp .OR. ln_ctl .OR. sn_cfctl%l_layout
174      !
175      !  0. read namelists parameters
176      ! -----------------------------------
177      !
178      REWIND( numnam_ref )              ! Namelist nammpp in reference namelist
179      READ  ( numnam_ref, nammpp, IOSTAT = ios, ERR = 901 )
180901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nammpp in reference namelist' )
181      REWIND( numnam_cfg )              ! Namelist nammpp in confguration namelist
182      READ  ( numnam_cfg, nammpp, IOSTAT = ios, ERR = 902 )
183902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nammpp in configuration namelist' )   
184      !
185      IF(lwp) THEN
186            WRITE(numout,*) '   Namelist nammpp'
187         IF( jpni < 1 .OR. jpnj < 1  ) THEN
188            WRITE(numout,*) '      jpni and jpnj will be calculated automatically'
189         ELSE
190            WRITE(numout,*) '      processor grid extent in i                            jpni = ', jpni
191            WRITE(numout,*) '      processor grid extent in j                            jpnj = ', jpnj
192         ENDIF
193            WRITE(numout,*) '      avoid use of mpi_allgather at the north fold  ln_nnogather = ', ln_nnogather
194      ENDIF
195      !
196      IF(lwm)   WRITE( numond, nammpp )
197
198      ! do we need to take into account bdy_msk?
199      REWIND( numnam_ref )              ! Namelist nambdy in reference namelist : BDY
200      READ  ( numnam_ref, nambdy, IOSTAT = ios, ERR = 903)
201903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambdy in reference namelist (mppini)' )
202      REWIND( numnam_cfg )              ! Namelist nambdy in configuration namelist : BDY
203      READ  ( numnam_cfg, nambdy, IOSTAT = ios, ERR = 904 )
204904   IF( ios >  0 )   CALL ctl_nam ( ios , 'nambdy in configuration namelist (mppini)' )
205      !
206      IF(               ln_read_cfg ) CALL iom_open( cn_domcfg,    numbot )
207      IF( ln_bdy .AND. ln_mask_file ) CALL iom_open( cn_mask_file, numbdy )
208      !
209      IF( ln_listonly )   CALL mpp_init_bestpartition( MAX(mppsize,jpni*jpnj), ldlist = .TRUE. )   ! must be done by all core
210      !
211      !  1. Dimension arrays for subdomains
212      ! -----------------------------------
213      !
214      ! If dimensions of processor grid weren't specified in the namelist file
215      ! then we calculate them here now that we have our communicator size
216      IF(lwp) THEN
217         WRITE(numout,*) 'mpp_init:'
218         WRITE(numout,*) '~~~~~~~~ '
219         WRITE(numout,*)
220      ENDIF
221      IF( jpni < 1 .OR. jpnj < 1 ) THEN
222         CALL mpp_init_bestpartition( mppsize, jpni, jpnj )           ! best mpi decomposition for mppsize mpi processes
223         llauto = .TRUE.
224         llbest = .TRUE.
225      ELSE
226         llauto = .FALSE.
227         CALL mpp_init_bestpartition( mppsize, inbi, inbj, icnt2 )    ! best mpi decomposition for mppsize mpi processes
228         ! largest subdomain size for mpi decoposition jpni*jpnj given in the namelist
229         CALL mpp_basic_decomposition( jpni, jpnj, jpimax, jpjmax )
230         ! largest subdomain size for mpi decoposition inbi*inbj given by mpp_init_bestpartition
231         CALL mpp_basic_decomposition( inbi, inbj,  iimax,  ijmax )
232         icnt1 = jpni*jpnj - mppsize   ! number of land subdomains that should be removed to use mppsize mpi processes
233         IF(lwp) THEN
234            WRITE(numout,9000) '   The chosen domain decomposition ', jpni, ' x ', jpnj, ' with ', icnt1, ' land subdomains'
235            WRITE(numout,9002) '      - uses a total of ',  mppsize,' mpi process'
236            WRITE(numout,9000) '      - has mpi subdomains with a maximum size of (jpi = ', jpimax, ', jpj = ', jpjmax,   &
237               &                                                                ', jpi*jpj = ', jpimax*jpjmax, ')'
238            WRITE(numout,9000) '   The best domain decompostion ', inbi, ' x ', inbj, ' with ', icnt2, ' land subdomains'
239            WRITE(numout,9002) '      - uses a total of ',  inbi*inbj-icnt2,' mpi process'
240            WRITE(numout,9000) '      - has mpi subdomains with a maximum size of (jpi = ',  iimax, ', jpj = ',  ijmax,   &
241               &                                                             ', jpi*jpj = ',  iimax* ijmax, ')'
242         ENDIF
243         IF( iimax*ijmax < jpimax*jpjmax ) THEN   ! chosen subdomain size is larger that the best subdomain size
244            llbest = .FALSE.
245            IF ( inbi*inbj-icnt2 < mppsize ) THEN
246               WRITE(ctmp1,*) '   ==> You could therefore have smaller mpi subdomains with less mpi processes'
247            ELSE
248               WRITE(ctmp1,*) '   ==> You could therefore have smaller mpi subdomains with the same number of mpi processes'
249            ENDIF
250            CALL ctl_warn( ' ', ctmp1, ' ', '    ---   YOU ARE WASTING CPU...   ---', ' ' )
251         ELSE IF ( iimax*ijmax == jpimax*jpjmax .AND. (inbi*inbj-icnt2) <  mppsize) THEN
252            llbest = .FALSE.
253            WRITE(ctmp1,*) '   ==> You could therefore have the same mpi subdomains size with less mpi processes'
254            CALL ctl_warn( ' ', ctmp1, ' ', '    ---   YOU ARE WASTING CPU...   ---', ' ' )
255         ELSE
256            llbest = .TRUE.
257         ENDIF
258      ENDIF
259     
260      ! look for land mpi subdomains...
261      ALLOCATE( llisoce(jpni,jpnj) )
262      CALL mpp_init_isoce( jpni, jpnj, llisoce )
263      inijmin = COUNT( llisoce )   ! number of oce subdomains
264
265      IF( mppsize < inijmin ) THEN   ! too many oce subdomains: can happen only if jpni and jpnj are prescribed...
266         WRITE(ctmp1,9001) '   With this specified domain decomposition: jpni = ', jpni, ' jpnj = ', jpnj
267         WRITE(ctmp2,9002) '   we can eliminate only ', jpni*jpnj - inijmin, ' land mpi subdomains therefore '
268         WRITE(ctmp3,9001) '   the number of ocean mpi subdomains (', inijmin,') exceed the number of MPI processes:', mppsize
269         WRITE(ctmp4,*) '   ==>>> There is the list of best domain decompositions you should use: '
270         CALL ctl_stop( ctmp1, ctmp2, ctmp3, ' ', ctmp4, ' ' )
271         CALL mpp_init_bestpartition( mppsize, ldlist = .TRUE. )   ! must be done by all core
272      ENDIF
273
274      IF( mppsize > jpni*jpnj ) THEN   ! not enough mpi subdomains for the total number of mpi processes
275         IF(lwp) THEN
276            WRITE(numout,9003) '   The number of mpi processes: ', mppsize
277            WRITE(numout,9003) '   exceeds the maximum number of subdomains (ocean+land) = ', jpni*jpnj
278            WRITE(numout,9001) '   defined by the following domain decomposition: jpni = ', jpni, ' jpnj = ', jpnj
279            WRITE(numout,   *) '   You should: '
280           IF( llauto ) THEN
281               WRITE(numout,*) '     - either prescribe your domain decomposition with the namelist variables'
282               WRITE(numout,*) '       jpni and jpnj to match the number of mpi process you want to use, '
283               WRITE(numout,*) '       even IF it not the best choice...'
284               WRITE(numout,*) '     - or keep the automatic and optimal domain decomposition by picking up one'
285               WRITE(numout,*) '       of the number of mpi process proposed in the list bellow'
286            ELSE
287               WRITE(numout,*) '     - either properly prescribe your domain decomposition with jpni and jpnj'
288               WRITE(numout,*) '       in order to be consistent with the number of mpi process you want to use'
289               WRITE(numout,*) '       even IF it not the best choice...'
290               WRITE(numout,*) '     - or use the automatic and optimal domain decomposition and pick up one of'
291               WRITE(numout,*) '       the domain decomposition proposed in the list bellow'
292            ENDIF
293            WRITE(numout,*)
294         ENDIF
295         CALL mpp_init_bestpartition( mppsize, ldlist = .TRUE. )   ! must be done by all core
296      ENDIF
297
298      jpnij = mppsize   ! force jpnij definition <-- remove as much land subdomains as needed to reach this condition
299      IF( mppsize > inijmin ) THEN
300         WRITE(ctmp1,9003) '   The number of mpi processes: ', mppsize
301         WRITE(ctmp2,9003) '   exceeds the maximum number of ocean subdomains = ', inijmin
302         WRITE(ctmp3,9002) '   we suppressed ', jpni*jpnj - mppsize, ' land subdomains '
303         WRITE(ctmp4,9002) '   BUT we had to keep ', mppsize - inijmin, ' land subdomains that are useless...'
304         CALL ctl_warn( ctmp1, ctmp2, ctmp3, ctmp4, ' ', '    --- YOU ARE WASTING CPU... ---', ' ' )
305      ELSE   ! mppsize = inijmin
306         IF(lwp) THEN
307            IF(llbest) WRITE(numout,*) '   ==> you use the best mpi decomposition'
308            WRITE(numout,*)
309            WRITE(numout,9003) '   Number of mpi processes: ', mppsize
310            WRITE(numout,9003) '   Number of ocean subdomains = ', inijmin
311            WRITE(numout,9003) '   Number of suppressed land subdomains = ', jpni*jpnj - inijmin
312            WRITE(numout,*)
313         ENDIF
314      ENDIF
3159000  FORMAT (a, i4, a, i4, a, i7, a)
3169001  FORMAT (a, i4, a, i4)
3179002  FORMAT (a, i4, a)
3189003  FORMAT (a, i5)
319
320      IF( numbot /= -1 )   CALL iom_close( numbot )
321      IF( numbdy /= -1 )   CALL iom_close( numbdy )
322   
323      ALLOCATE(  nfiimpp(jpni,jpnj), nfipproc(jpni,jpnj), nfilcit(jpni,jpnj) ,    &
324         &       nimppt(jpnij) , ibonit(jpnij) , nlcit(jpnij) , nlcjt(jpnij) ,    &
325         &       njmppt(jpnij) , ibonjt(jpnij) , nldit(jpnij) , nldjt(jpnij) ,    &
326         &                                       nleit(jpnij) , nlejt(jpnij) ,    &
327         &       iin(jpnij), ii_nono(jpnij), ii_noea(jpnij),   &
328         &       ijn(jpnij), ii_noso(jpnij), ii_nowe(jpnij),   &
329         &       iimppt(jpni,jpnj), ilci(jpni,jpnj), ibondi(jpni,jpnj), ipproc(jpni,jpnj),   &
330         &       ijmppt(jpni,jpnj), ilcj(jpni,jpnj), ibondj(jpni,jpnj), ipolj(jpni,jpnj),   &
331         &       ilei(jpni,jpnj), ildi(jpni,jpnj), iono(jpni,jpnj), ioea(jpni,jpnj),   &
332         &       ilej(jpni,jpnj), ildj(jpni,jpnj), ioso(jpni,jpnj), iowe(jpni,jpnj),   &
333         &       STAT=ierr )
334      CALL mpp_sum( 'mppini', ierr )
335      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'mpp_init: unable to allocate standard ocean arrays' )
336     
337#if defined key_agrif
338      IF( .NOT. Agrif_Root() ) THEN       ! AGRIF children: specific setting (cf. agrif_user.F90)
339         IF( jpiglo /= nbcellsx + 2 + 2*nbghostcells )   &
340            CALL ctl_stop( 'STOP', 'mpp_init: Agrif children requires jpiglo == nbcellsx + 2 + 2*nbghostcells' )
341         IF( jpjglo /= nbcellsy + 2 + 2*nbghostcells )   &
342            CALL ctl_stop( 'STOP', 'mpp_init: Agrif children requires jpjglo == nbcellsy + 2 + 2*nbghostcells' )
343         IF( ln_use_jattr )   CALL ctl_stop( 'STOP', 'mpp_init:Agrif children requires ln_use_jattr = .false. ' )
344      ENDIF
345#endif
346      !
347      !  2. Index arrays for subdomains
348      ! -----------------------------------
349      !
350      nreci = 2 * nn_hls
351      nrecj = 2 * nn_hls
352      CALL mpp_basic_decomposition( jpni, jpnj, jpimax, jpjmax, iimppt, ijmppt, ilci, ilcj )
353      nfiimpp(:,:) = iimppt(:,:)
354      nfilcit(:,:) = ilci(:,:)
355      !
356      IF(lwp) THEN
357         WRITE(numout,*)
358         WRITE(numout,*) 'MPI Message Passing MPI - domain lay out over processors'
359         WRITE(numout,*)
360         WRITE(numout,*) '   defines mpp subdomains'
361         WRITE(numout,*) '      jpni = ', jpni 
362         WRITE(numout,*) '      jpnj = ', jpnj
363         WRITE(numout,*)
364         WRITE(numout,*) '      sum ilci(i,1) = ', sum(ilci(:,1)), ' jpiglo = ', jpiglo
365         WRITE(numout,*) '      sum ilcj(1,j) = ', sum(ilcj(1,:)), ' jpjglo = ', jpjglo
366      ENDIF
367     
368      ! 3. Subdomain description in the Regular Case
369      ! --------------------------------------------
370      ! specific cases where there is no communication -> must do the periodicity by itself
371      ! Warning: because of potential land-area suppression, do not use nbond[ij] == 2 
372      l_Iperio = jpni == 1 .AND. (jperio == 1 .OR. jperio == 4 .OR. jperio == 6 .OR. jperio == 7)
373      l_Jperio = jpnj == 1 .AND. (jperio == 2 .OR. jperio == 7)
374     
375      DO jarea = 1, jpni*jpnj
376         !
377         iarea0 = jarea - 1
378         ii = 1 + MOD(iarea0,jpni)
379         ij = 1 +     iarea0/jpni
380         ili = ilci(ii,ij)
381         ilj = ilcj(ii,ij)
382         ibondi(ii,ij) = 0                         ! default: has e-w neighbours
383         IF( ii   ==    1 )   ibondi(ii,ij) = -1   ! first column, has only e neighbour
384         IF( ii   == jpni )   ibondi(ii,ij) =  1   ! last column,  has only w neighbour
385         IF( jpni ==    1 )   ibondi(ii,ij) =  2   ! has no e-w neighbour
386         ibondj(ii,ij) = 0                         ! default: has n-s neighbours
387         IF( ij   ==    1 )   ibondj(ii,ij) = -1   ! first row, has only n neighbour
388         IF( ij   == jpnj )   ibondj(ii,ij) =  1   ! last row,  has only s neighbour
389         IF( jpnj ==    1 )   ibondj(ii,ij) =  2   ! has no n-s neighbour
390
391         ! Subdomain neighbors (get their zone number): default definition
392         ioso(ii,ij) = iarea0 - jpni
393         iowe(ii,ij) = iarea0 - 1
394         ioea(ii,ij) = iarea0 + 1
395         iono(ii,ij) = iarea0 + jpni
396         ildi(ii,ij) =  1  + nn_hls
397         ilei(ii,ij) = ili - nn_hls
398         ildj(ii,ij) =  1  + nn_hls
399         ilej(ii,ij) = ilj - nn_hls
400
401         ! East-West periodicity: change ibondi, ioea, iowe
402         IF( jperio == 1 .OR. jperio == 4 .OR. jperio == 6 .OR. jperio == 7 ) THEN
403            IF( jpni  /= 1 )   ibondi(ii,ij) = 0                        ! redefine: all have e-w neighbours
404            IF( ii ==    1 )   iowe(ii,ij) = iarea0 +        (jpni-1)   ! redefine: first column, address of w neighbour
405            IF( ii == jpni )   ioea(ii,ij) = iarea0 -        (jpni-1)   ! redefine: last column,  address of e neighbour
406         ENDIF
407
408         ! Simple North-South periodicity: change ibondj, ioso, iono
409         IF( jperio == 2 .OR. jperio == 7 ) THEN
410            IF( jpnj  /= 1 )   ibondj(ii,ij) = 0                        ! redefine: all have n-s neighbours
411            IF( ij ==    1 )   ioso(ii,ij) = iarea0 + jpni * (jpnj-1)   ! redefine: first row, address of s neighbour
412            IF( ij == jpnj )   iono(ii,ij) = iarea0 - jpni * (jpnj-1)   ! redefine: last row,  address of n neighbour
413         ENDIF
414
415         ! North fold: define ipolj, change iono. Warning: we do not change ibondj...
416         ipolj(ii,ij) = 0
417         IF( jperio == 3 .OR. jperio == 4 ) THEN
418            ijm1 = jpni*(jpnj-1)
419            imil = ijm1+(jpni+1)/2
420            IF( jarea > ijm1 ) ipolj(ii,ij) = 3
421            IF( MOD(jpni,2) == 1 .AND. jarea == imil ) ipolj(ii,ij) = 4
422            IF( ipolj(ii,ij) == 3 ) iono(ii,ij) = jpni*jpnj-jarea+ijm1   ! MPI rank of northern neighbour
423         ENDIF
424         IF( jperio == 5 .OR. jperio == 6 ) THEN
425            ijm1 = jpni*(jpnj-1)
426            imil = ijm1+(jpni+1)/2
427            IF( jarea > ijm1) ipolj(ii,ij) = 5
428            IF( MOD(jpni,2) == 1 .AND. jarea == imil ) ipolj(ii,ij) = 6
429            IF( ipolj(ii,ij) == 5) iono(ii,ij) = jpni*jpnj-jarea+ijm1    ! MPI rank of northern neighbour
430         ENDIF
431         !
432      END DO
433
434      ! 4. deal with land subdomains
435      ! ----------------------------
436      !
437      ! specify which subdomains are oce subdomains; other are land subdomains
438      ipproc(:,:) = -1
439      icont = -1
440      DO jarea = 1, jpni*jpnj
441         iarea0 = jarea - 1
442         ii = 1 + MOD(iarea0,jpni)
443         ij = 1 +     iarea0/jpni
444         IF( llisoce(ii,ij) ) THEN
445            icont = icont + 1
446            ipproc(ii,ij) = icont
447            iin(icont+1) = ii
448            ijn(icont+1) = ij
449         ENDIF
450      END DO
451      ! if needed add some land subdomains to reach jpnij active subdomains
452      i2add = jpnij - inijmin
453      DO jarea = 1, jpni*jpnj
454         iarea0 = jarea - 1
455         ii = 1 + MOD(iarea0,jpni)
456         ij = 1 +     iarea0/jpni
457         IF( .NOT. llisoce(ii,ij) .AND. i2add > 0 ) THEN
458            icont = icont + 1
459            ipproc(ii,ij) = icont
460            iin(icont+1) = ii
461            ijn(icont+1) = ij
462            i2add = i2add - 1
463         ENDIF
464      END DO
465      nfipproc(:,:) = ipproc(:,:)
466
467      ! compute rank for MPI3 neighbourhood colectives
468      ALLOCATE(nranks(jpni*jpnj))
469      icont = 1
470      DO ji = 1, jpni
471         DO jj = 1, jpnj
472            nranks(icont) = ipproc(ji,jj)
473            icont = icont + 1
474         END DO
475      END DO
476
477      ! neighbour treatment: change ibondi, ibondj if next to a land zone
478      DO jarea = 1, jpni*jpnj
479         ii = 1 + MOD( jarea-1  , jpni )
480         ij = 1 +     (jarea-1) / jpni
481         ! land-only area with an active n neigbour
482         IF ( ipproc(ii,ij) == -1 .AND. 0 <= iono(ii,ij) .AND. iono(ii,ij) <= jpni*jpnj-1 ) THEN
483            iino = 1 + MOD( iono(ii,ij) , jpni )                    ! ii index of this n neigbour
484            ijno = 1 +      iono(ii,ij) / jpni                      ! ij index of this n neigbour
485            ! In case of north fold exchange: I am the n neigbour of my n neigbour!! (#1057)
486            ! --> for northern neighbours of northern row processors (in case of north-fold)
487            !     need to reverse the LOGICAL direction of communication
488            idir = 1                                           ! we are indeed the s neigbour of this n neigbour
489            IF( ij == jpnj .AND. ijno == jpnj )   idir = -1    ! both are on the last row, we are in fact the n neigbour
490            IF( ibondj(iino,ijno) == idir     )   ibondj(iino,ijno) =   2     ! this n neigbour had only a s/n neigbour -> no more
491            IF( ibondj(iino,ijno) == 0        )   ibondj(iino,ijno) = -idir   ! this n neigbour had both, n-s neighbours -> keep 1
492         ENDIF
493         ! land-only area with an active s neigbour
494         IF( ipproc(ii,ij) == -1 .AND. 0 <= ioso(ii,ij) .AND. ioso(ii,ij) <= jpni*jpnj-1 ) THEN
495            iiso = 1 + MOD( ioso(ii,ij) , jpni )                    ! ii index of this s neigbour
496            ijso = 1 +      ioso(ii,ij) / jpni                      ! ij index of this s neigbour
497            IF( ibondj(iiso,ijso) == -1 )   ibondj(iiso,ijso) = 2   ! this s neigbour had only a n neigbour    -> no more neigbour
498            IF( ibondj(iiso,ijso) ==  0 )   ibondj(iiso,ijso) = 1   ! this s neigbour had both, n-s neighbours -> keep s neigbour
499         ENDIF
500         ! land-only area with an active e neigbour
501         IF( ipproc(ii,ij) == -1 .AND. 0 <= ioea(ii,ij) .AND. ioea(ii,ij) <= jpni*jpnj-1 ) THEN
502            iiea = 1 + MOD( ioea(ii,ij) , jpni )                    ! ii index of this e neigbour
503            ijea = 1 +      ioea(ii,ij) / jpni                      ! ij index of this e neigbour
504            IF( ibondi(iiea,ijea) == 1 )   ibondi(iiea,ijea) =  2   ! this e neigbour had only a w neigbour    -> no more neigbour
505            IF( ibondi(iiea,ijea) == 0 )   ibondi(iiea,ijea) = -1   ! this e neigbour had both, e-w neighbours -> keep e neigbour
506         ENDIF
507         ! land-only area with an active w neigbour
508         IF( ipproc(ii,ij) == -1 .AND. 0 <= iowe(ii,ij) .AND. iowe(ii,ij) <= jpni*jpnj-1) THEN
509            iiwe = 1 + MOD( iowe(ii,ij) , jpni )                    ! ii index of this w neigbour
510            ijwe = 1 +      iowe(ii,ij) / jpni                      ! ij index of this w neigbour
511            IF( ibondi(iiwe,ijwe) == -1 )   ibondi(iiwe,ijwe) = 2   ! this w neigbour had only a e neigbour    -> no more neigbour
512            IF( ibondi(iiwe,ijwe) ==  0 )   ibondi(iiwe,ijwe) = 1   ! this w neigbour had both, e-w neighbours -> keep w neigbour
513         ENDIF
514      END DO
515
516      ! Update il[de][ij] according to modified ibond[ij]
517      ! ----------------------
518      DO jproc = 1, jpnij
519         ii = iin(jproc)
520         ij = ijn(jproc)
521         IF( ibondi(ii,ij) == -1 .OR. ibondi(ii,ij) == 2 ) ildi(ii,ij) =  1
522         IF( ibondi(ii,ij) ==  1 .OR. ibondi(ii,ij) == 2 ) ilei(ii,ij) = ilci(ii,ij)
523         IF( ibondj(ii,ij) == -1 .OR. ibondj(ii,ij) == 2 ) ildj(ii,ij) =  1
524         IF( ibondj(ii,ij) ==  1 .OR. ibondj(ii,ij) == 2 ) ilej(ii,ij) = ilcj(ii,ij)
525      END DO
526     
527      ! 5. Subdomain print
528      ! ------------------
529      IF(lwp) THEN
530         ifreq = 4
531         il1 = 1
532         DO jn = 1, (jpni-1)/ifreq+1
533            il2 = MIN(jpni,il1+ifreq-1)
534            WRITE(numout,*)
535            WRITE(numout,9400) ('***',ji=il1,il2-1)
536            DO jj = jpnj, 1, -1
537               WRITE(numout,9403) ('   ',ji=il1,il2-1)
538               WRITE(numout,9402) jj, (ilci(ji,jj),ilcj(ji,jj),ji=il1,il2)
539               WRITE(numout,9404) (ipproc(ji,jj),ji=il1,il2)
540               WRITE(numout,9403) ('   ',ji=il1,il2-1)
541               WRITE(numout,9400) ('***',ji=il1,il2-1)
542            END DO
543            WRITE(numout,9401) (ji,ji=il1,il2)
544            il1 = il1+ifreq
545         END DO
546 9400    FORMAT('           ***'   ,20('*************',a3)    )
547 9403    FORMAT('           *     ',20('         *   ',a3)    )
548 9401    FORMAT('              '   ,20('   ',i3,'          ') )
549 9402    FORMAT('       ',i3,' *  ',20(i3,'  x',i3,'   *   ') )
550 9404    FORMAT('           *  '   ,20('     ' ,i4,'   *   ') )
551      ENDIF
552         
553      ! just to save nono etc for all proc
554      ! warning ii*ij (zone) /= nproc (processors)!
555      ! ioso = zone number, ii_noso = proc number
556      ii_noso(:) = -1
557      ii_nono(:) = -1
558      ii_noea(:) = -1
559      ii_nowe(:) = -1 
560      DO jproc = 1, jpnij
561         ii = iin(jproc)
562         ij = ijn(jproc)
563         IF( 0 <= ioso(ii,ij) .AND. ioso(ii,ij) <= (jpni*jpnj-1) ) THEN
564            iiso = 1 + MOD( ioso(ii,ij) , jpni )
565            ijso = 1 +      ioso(ii,ij) / jpni
566            ii_noso(jproc) = ipproc(iiso,ijso)
567         ENDIF
568         IF( 0 <= iowe(ii,ij) .AND. iowe(ii,ij) <= (jpni*jpnj-1) ) THEN
569          iiwe = 1 + MOD( iowe(ii,ij) , jpni )
570          ijwe = 1 +      iowe(ii,ij) / jpni
571          ii_nowe(jproc) = ipproc(iiwe,ijwe)
572         ENDIF
573         IF( 0 <= ioea(ii,ij) .AND. ioea(ii,ij) <= (jpni*jpnj-1) ) THEN
574            iiea = 1 + MOD( ioea(ii,ij) , jpni )
575            ijea = 1 +      ioea(ii,ij) / jpni
576            ii_noea(jproc)= ipproc(iiea,ijea)
577         ENDIF
578         IF( 0 <= iono(ii,ij) .AND. iono(ii,ij) <= (jpni*jpnj-1) ) THEN
579            iino = 1 + MOD( iono(ii,ij) , jpni )
580            ijno = 1 +      iono(ii,ij) / jpni
581            ii_nono(jproc)= ipproc(iino,ijno)
582         ENDIF
583      END DO
584   
585      ! 6. Change processor name
586      ! ------------------------
587      ii = iin(narea)
588      ij = ijn(narea)
589      !
590      ! set default neighbours
591      noso = ii_noso(narea)
592      nowe = ii_nowe(narea)
593      noea = ii_noea(narea)
594      nono = ii_nono(narea)
595      nlci = ilci(ii,ij) 
596      nldi = ildi(ii,ij)
597      nlei = ilei(ii,ij)
598      nlcj = ilcj(ii,ij) 
599      nldj = ildj(ii,ij)
600      nlej = ilej(ii,ij)
601      nbondi = ibondi(ii,ij)
602      nbondj = ibondj(ii,ij)
603      nimpp = iimppt(ii,ij) 
604      njmpp = ijmppt(ii,ij)
605      jpi = nlci
606      jpj = nlcj
607      jpk = jpkglo                                             ! third dim
608#if defined key_agrif
609      ! simple trick to use same vertical grid as parent but different number of levels:
610      ! Save maximum number of levels in jpkglo, then define all vertical grids with this number.
611      ! Suppress once vertical online interpolation is ok
612!!$      IF(.NOT.Agrif_Root())   jpkglo = Agrif_Parent( jpkglo )
613#endif
614      jpim1 = jpi-1                                            ! inner domain indices
615      jpjm1 = jpj-1                                            !   "           "
616      jpkm1 = MAX( 1, jpk-1 )                                  !   "           "
617      jpij  = jpi*jpj                                          !  jpi x j
618      DO jproc = 1, jpnij
619         ii = iin(jproc)
620         ij = ijn(jproc)
621         nlcit(jproc) = ilci(ii,ij)
622         nldit(jproc) = ildi(ii,ij)
623         nleit(jproc) = ilei(ii,ij)
624         nlcjt(jproc) = ilcj(ii,ij)
625         nldjt(jproc) = ildj(ii,ij)
626         nlejt(jproc) = ilej(ii,ij)
627         ibonit(jproc) = ibondi(ii,ij)
628         ibonjt(jproc) = ibondj(ii,ij)
629         nimppt(jproc) = iimppt(ii,ij) 
630         njmppt(jproc) = ijmppt(ii,ij) 
631      END DO
632
633      ! Save processor layout in ascii file
634      IF (llwrtlay) THEN
635         CALL ctl_opn( inum, 'layout.dat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., narea )
636         WRITE(inum,'(a)') '   jpnij   jpimax  jpjmax    jpk  jpiglo  jpjglo'//&
637   &           ' ( local:    narea     jpi     jpj )'
638         WRITE(inum,'(6i8,a,3i8,a)') jpnij,jpimax,jpjmax,jpk,jpiglo,jpjglo,&
639   &           ' ( local: ',narea,jpi,jpj,' )'
640         WRITE(inum,'(a)') 'nproc nlci nlcj nldi nldj nlei nlej nimp njmp nono noso nowe noea nbondi nbondj '
641
642         DO jproc = 1, jpnij
643            WRITE(inum,'(13i5,2i7)')   jproc-1, nlcit  (jproc), nlcjt  (jproc),   &
644               &                                nldit  (jproc), nldjt  (jproc),   &
645               &                                nleit  (jproc), nlejt  (jproc),   &
646               &                                nimppt (jproc), njmppt (jproc),   & 
647               &                                ii_nono(jproc), ii_noso(jproc),   &
648               &                                ii_nowe(jproc), ii_noea(jproc),   &
649               &                                ibonit (jproc), ibonjt (jproc) 
650         END DO
651      END IF
652
653      !                          ! north fold parameter
654      ! Defined npolj, either 0, 3 , 4 , 5 , 6
655      ! In this case the important thing is that npolj /= 0
656      ! Because if we go through these line it is because jpni >1 and thus
657      ! we must use lbcnorthmpp, which tests only npolj =0 or npolj /= 0
658      npolj = 0
659      ij = ijn(narea)
660      IF( jperio == 3 .OR. jperio == 4 ) THEN
661         IF( ij == jpnj )   npolj = 3
662      ENDIF
663      IF( jperio == 5 .OR. jperio == 6 ) THEN
664         IF( ij == jpnj )   npolj = 5
665      ENDIF
666      !
667      nproc = narea-1
668      IF(lwp) THEN
669         WRITE(numout,*)
670         WRITE(numout,*) '   resulting internal parameters : '
671         WRITE(numout,*) '      nproc  = ', nproc
672         WRITE(numout,*) '      nowe   = ', nowe  , '   noea  =  ', noea
673         WRITE(numout,*) '      nono   = ', nono  , '   noso  =  ', noso
674         WRITE(numout,*) '      nbondi = ', nbondi
675         WRITE(numout,*) '      nbondj = ', nbondj
676         WRITE(numout,*) '      npolj  = ', npolj
677         WRITE(numout,*) '    l_Iperio = ', l_Iperio
678         WRITE(numout,*) '    l_Jperio = ', l_Jperio
679         WRITE(numout,*) '      nlci   = ', nlci
680         WRITE(numout,*) '      nlcj   = ', nlcj
681         WRITE(numout,*) '      nimpp  = ', nimpp
682         WRITE(numout,*) '      njmpp  = ', njmpp
683         WRITE(numout,*) '      nreci  = ', nreci 
684         WRITE(numout,*) '      nrecj  = ', nrecj 
685         WRITE(numout,*) '      nn_hls = ', nn_hls 
686      ENDIF
687
688      !                          ! Prepare mpp north fold
689      IF( jperio >= 3 .AND. jperio <= 6 .AND. jpni > 1 ) THEN
690         CALL mpp_ini_north
691         IF (lwp) THEN
692            WRITE(numout,*)
693            WRITE(numout,*) '   ==>>>   North fold boundary prepared for jpni >1'
694            ! additional prints in layout.dat
695         ENDIF
696         IF (llwrtlay) THEN
697            WRITE(inum,*)
698            WRITE(inum,*)
699            WRITE(inum,*) 'number of subdomains located along the north fold : ', ndim_rank_north
700            WRITE(inum,*) 'Rank of the subdomains located along the north fold : ', ndim_rank_north
701            DO jproc = 1, ndim_rank_north, 5
702               WRITE(inum,*) nrank_north( jproc:MINVAL( (/jproc+4,ndim_rank_north/) ) )
703            END DO
704         ENDIF
705      ENDIF
706
707      CALL mpp_ini_nc
708      !
709      CALL mpp_init_ioipsl       ! Prepare NetCDF output file (if necessary)
710      !     
711      IF (( jperio >= 3 .AND. jperio <= 6 .AND. jpni > 1 ).AND.( ln_nnogather )) THEN
712         CALL mpp_init_nfdcom     ! northfold neighbour lists
713         IF (llwrtlay) THEN
714            WRITE(inum,*)
715            WRITE(inum,*)
716            WRITE(inum,*) 'north fold exchanges with explicit point-to-point messaging :'
717            WRITE(inum,*) 'nfsloop : ', nfsloop
718            WRITE(inum,*) 'nfeloop : ', nfeloop
719            WRITE(inum,*) 'nsndto : ', nsndto
720            WRITE(inum,*) 'isendto : ', isendto
721         ENDIF
722      ENDIF
723      !
724      IF (llwrtlay) CLOSE(inum)   
725      !
726      DEALLOCATE(iin, ijn, ii_nono, ii_noea, ii_noso, ii_nowe,    &
727         &       iimppt, ijmppt, ibondi, ibondj, ipproc, ipolj,   &
728         &       ilci, ilcj, ilei, ilej, ildi, ildj,              &
729         &       iono, ioea, ioso, iowe, llisoce)
730      !
731    END SUBROUTINE mpp_init
732
733
734    SUBROUTINE mpp_basic_decomposition( knbi, knbj, kimax, kjmax, kimppt, kjmppt, klci, klcj)
735      !!----------------------------------------------------------------------
736      !!                  ***  ROUTINE mpp_basic_decomposition  ***
737      !!                   
738      !! ** Purpose :   Lay out the global domain over processors.
739      !!
740      !! ** Method  :   Global domain is distributed in smaller local domains.
741      !!
742      !! ** Action : - set for all knbi*knbj domains:
743      !!                    kimppt     : longitudinal index
744      !!                    kjmppt     : latitudinal  index
745      !!                    klci       : first dimension
746      !!                    klcj       : second dimension
747      !!----------------------------------------------------------------------
748      INTEGER,                                 INTENT(in   ) ::   knbi, knbj
749      INTEGER,                                 INTENT(  out) ::   kimax, kjmax
750      INTEGER, DIMENSION(knbi,knbj), OPTIONAL, INTENT(  out) ::   kimppt, kjmppt
751      INTEGER, DIMENSION(knbi,knbj), OPTIONAL, INTENT(  out) ::   klci, klcj
752      !
753      INTEGER ::   ji, jj
754      INTEGER ::   iresti, irestj, irm, ijpjmin
755      INTEGER ::   ireci, irecj
756      !!----------------------------------------------------------------------
757      !
758#if defined key_nemocice_decomp
759      kimax = ( nx_global+2-2*nn_hls + (knbi-1) ) / knbi + 2*nn_hls    ! first  dim.
760      kjmax = ( ny_global+2-2*nn_hls + (knbj-1) ) / knbj + 2*nn_hls    ! second dim.
761#else
762      kimax = ( jpiglo - 2*nn_hls + (knbi-1) ) / knbi + 2*nn_hls    ! first  dim.
763      kjmax = ( jpjglo - 2*nn_hls + (knbj-1) ) / knbj + 2*nn_hls    ! second dim.
764#endif
765      IF( .NOT. PRESENT(kimppt) ) RETURN
766      !
767      !  1. Dimension arrays for subdomains
768      ! -----------------------------------
769      !  Computation of local domain sizes klci() klcj()
770      !  These dimensions depend on global sizes knbi,knbj and jpiglo,jpjglo
771      !  The subdomains are squares lesser than or equal to the global
772      !  dimensions divided by the number of processors minus the overlap array.
773      !
774      ireci = 2 * nn_hls
775      irecj = 2 * nn_hls
776      iresti = 1 + MOD( jpiglo - ireci -1 , knbi )
777      irestj = 1 + MOD( jpjglo - irecj -1 , knbj )
778      !
779      !  Need to use kimax and kjmax here since jpi and jpj not yet defined
780#if defined key_nemocice_decomp
781      ! Change padding to be consistent with CICE
782      klci(1:knbi-1      ,:) = kimax
783      klci(knbi          ,:) = jpiglo - (knbi - 1) * (kimax - nreci)
784      klcj(:,      1:knbj-1) = kjmax
785      klcj(:,          knbj) = jpjglo - (knbj - 1) * (kjmax - nrecj)
786#else
787      klci(1:iresti      ,:) = kimax
788      klci(iresti+1:knbi ,:) = kimax-1
789      IF( MINVAL(klci) < 3 ) THEN
790         WRITE(ctmp1,*) '   mpp_basic_decomposition: minimum value of jpi must be >= 3'
791         WRITE(ctmp2,*) '   We have ', MINVAL(klci)
792        CALL ctl_stop( 'STOP', ctmp1, ctmp2 )
793      ENDIF
794      IF( jperio == 3 .OR. jperio == 4 .OR. jperio == 5 .OR. jperio == 6 ) THEN
795         ! minimize the size of the last row to compensate for the north pole folding coast
796         IF( jperio == 3 .OR. jperio == 4 )   ijpjmin = 5   ! V and F folding involves line jpj-3 that must not be south boundary
797         IF( jperio == 5 .OR. jperio == 6 )   ijpjmin = 4   ! V and F folding involves line jpj-2 that must not be south boundary
798         irm = knbj - irestj                                    ! total number of lines to be removed
799         klcj(:,            knbj) = MAX( ijpjmin, kjmax-irm )   ! we must have jpj >= ijpjmin in the last row
800         irm = irm - ( kjmax - klcj(1,knbj) )                   ! remaining number of lines to remove
801         irestj = knbj - 1 - irm                       
802         klcj(:,        1:irestj) = kjmax
803         klcj(:, irestj+1:knbj-1) = kjmax-1
804      ELSE
805         ijpjmin = 3
806         klcj(:,      1:irestj) = kjmax
807         klcj(:, irestj+1:knbj) = kjmax-1
808      ENDIF
809      IF( MINVAL(klcj) < ijpjmin ) THEN
810         WRITE(ctmp1,*) '   mpp_basic_decomposition: minimum value of jpj must be >= ', ijpjmin
811         WRITE(ctmp2,*) '   We have ', MINVAL(klcj)
812         CALL ctl_stop( 'STOP', ctmp1, ctmp2 )
813      ENDIF
814#endif
815
816      !  2. Index arrays for subdomains
817      ! -------------------------------
818      kimppt(:,:) = 1
819      kjmppt(:,:) = 1
820      !
821      IF( knbi > 1 ) THEN
822         DO jj = 1, knbj
823            DO ji = 2, knbi
824               kimppt(ji,jj) = kimppt(ji-1,jj) + klci(ji-1,jj) - ireci
825            END DO
826         END DO
827      ENDIF
828      !
829      IF( knbj > 1 )THEN
830         DO jj = 2, knbj
831            DO ji = 1, knbi
832               kjmppt(ji,jj) = kjmppt(ji,jj-1) + klcj(ji,jj-1) - irecj
833            END DO
834         END DO
835      ENDIF
836     
837   END SUBROUTINE mpp_basic_decomposition
838
839
840   SUBROUTINE mpp_init_bestpartition( knbij, knbi, knbj, knbcnt, ldlist )
841      !!----------------------------------------------------------------------
842      !!                 ***  ROUTINE mpp_init_bestpartition  ***
843      !!
844      !! ** Purpose :
845      !!
846      !! ** Method  :
847      !!----------------------------------------------------------------------
848      INTEGER,           INTENT(in   ) ::   knbij         ! total number if subdomains               (knbi*knbj)
849      INTEGER, OPTIONAL, INTENT(  out) ::   knbi, knbj    ! number if subdomains along i and j (knbi and knbj)
850      INTEGER, OPTIONAL, INTENT(  out) ::   knbcnt        ! number of land subdomains
851      LOGICAL, OPTIONAL, INTENT(in   ) ::   ldlist        ! .true.: print the list the best domain decompositions (with land)
852      !
853      INTEGER :: ji, jj, ii, iitarget
854      INTEGER :: iszitst, iszjtst
855      INTEGER :: isziref, iszjref
856      INTEGER :: inbij, iszij
857      INTEGER :: inbimax, inbjmax, inbijmax, inbijold
858      INTEGER :: isz0, isz1
859      INTEGER, DIMENSION(  :), ALLOCATABLE :: indexok
860      INTEGER, DIMENSION(  :), ALLOCATABLE :: inbi0, inbj0, inbij0   ! number of subdomains along i,j
861      INTEGER, DIMENSION(  :), ALLOCATABLE :: iszi0, iszj0, iszij0   ! max size of the subdomains along i,j
862      INTEGER, DIMENSION(  :), ALLOCATABLE :: inbi1, inbj1, inbij1   ! number of subdomains along i,j
863      INTEGER, DIMENSION(  :), ALLOCATABLE :: iszi1, iszj1, iszij1   ! max size of the subdomains along i,j
864      LOGICAL :: llist
865      LOGICAL, DIMENSION(:,:), ALLOCATABLE :: llmsk2d                 ! max size of the subdomains along i,j
866      LOGICAL, DIMENSION(:,:), ALLOCATABLE :: llisoce              !  -     -
867      REAL(wp)::   zpropland
868      !!----------------------------------------------------------------------
869      !
870      llist = .FALSE.
871      IF( PRESENT(ldlist) ) llist = ldlist
872
873      CALL mpp_init_landprop( zpropland )                      ! get the proportion of land point over the gloal domain
874      inbij = NINT( REAL(knbij, wp) / ( 1.0 - zpropland ) )    ! define the largest possible value for jpni*jpnj
875      !
876      IF( llist ) THEN   ;   inbijmax = inbij*2
877      ELSE               ;   inbijmax = inbij
878      ENDIF
879      !
880      ALLOCATE(inbi0(inbijmax),inbj0(inbijmax),iszi0(inbijmax),iszj0(inbijmax))
881      !
882      inbimax = 0
883      inbjmax = 0
884      isziref = jpiglo*jpjglo+1
885      iszjref = jpiglo*jpjglo+1
886      !
887      ! get the list of knbi that gives a smaller jpimax than knbi-1
888      ! get the list of knbj that gives a smaller jpjmax than knbj-1
889      DO ji = 1, inbijmax     
890#if defined key_nemocice_decomp
891         iszitst = ( nx_global+2-2*nn_hls + (ji-1) ) / ji + 2*nn_hls    ! first  dim.
892#else
893         iszitst = ( jpiglo - 2*nn_hls + (ji-1) ) / ji + 2*nn_hls
894#endif
895         IF( iszitst < isziref ) THEN
896            isziref = iszitst
897            inbimax = inbimax + 1
898            inbi0(inbimax) = ji
899            iszi0(inbimax) = isziref
900         ENDIF
901#if defined key_nemocice_decomp
902         iszjtst = ( ny_global+2-2*nn_hls + (ji-1) ) / ji + 2*nn_hls    ! first  dim.
903#else
904         iszjtst = ( jpjglo - 2*nn_hls + (ji-1) ) / ji + 2*nn_hls
905#endif
906         IF( iszjtst < iszjref ) THEN
907            iszjref = iszjtst
908            inbjmax = inbjmax + 1
909            inbj0(inbjmax) = ji
910            iszj0(inbjmax) = iszjref
911         ENDIF
912      END DO
913
914      ! combine these 2 lists to get all possible knbi*knbj <  inbijmax
915      ALLOCATE( llmsk2d(inbimax,inbjmax) )
916      DO jj = 1, inbjmax
917         DO ji = 1, inbimax
918            IF ( inbi0(ji) * inbj0(jj) <= inbijmax ) THEN   ;   llmsk2d(ji,jj) = .TRUE.
919            ELSE                                            ;   llmsk2d(ji,jj) = .FALSE.
920            ENDIF
921         END DO
922      END DO
923      isz1 = COUNT(llmsk2d)
924      ALLOCATE( inbi1(isz1), inbj1(isz1), iszi1(isz1), iszj1(isz1) )
925      ii = 0
926      DO jj = 1, inbjmax
927         DO ji = 1, inbimax
928            IF( llmsk2d(ji,jj) .EQV. .TRUE. ) THEN
929               ii = ii + 1
930               inbi1(ii) = inbi0(ji)
931               inbj1(ii) = inbj0(jj)
932               iszi1(ii) = iszi0(ji)
933               iszj1(ii) = iszj0(jj)
934            END IF
935         END DO
936      END DO
937      DEALLOCATE( inbi0, inbj0, iszi0, iszj0 )
938      DEALLOCATE( llmsk2d )
939
940      ALLOCATE( inbij1(isz1), iszij1(isz1) )
941      inbij1(:) = inbi1(:) * inbj1(:)
942      iszij1(:) = iszi1(:) * iszj1(:)
943
944      ! if therr is no land and no print
945      IF( .NOT. llist .AND. numbot == -1 .AND. numbdy == -1 ) THEN
946         ! get the smaller partition which gives the smallest subdomain size
947         ii = MINLOC(inbij1, mask = iszij1 == MINVAL(iszij1), dim = 1)
948         knbi = inbi1(ii)
949         knbj = inbj1(ii)
950         IF(PRESENT(knbcnt))   knbcnt = 0
951         DEALLOCATE( inbi1, inbj1, inbij1, iszi1, iszj1, iszij1 )
952         RETURN
953      ENDIF
954
955      ! extract only the partitions which reduce the subdomain size in comparison with smaller partitions
956      ALLOCATE( indexok(isz1) )                                 ! to store indices of the best partitions
957      isz0 = 0                                                  ! number of best partitions     
958      inbij = 1                                                 ! start with the min value of inbij1 => 1
959      iszij = jpiglo*jpjglo+1                                   ! default: larger than global domain
960      DO WHILE( inbij <= inbijmax )                             ! if we did not reach the max of inbij1
961         ii = MINLOC(iszij1, mask = inbij1 == inbij, dim = 1)   ! warning: send back the first occurence if multiple results
962         IF ( iszij1(ii) < iszij ) THEN
963            isz0 = isz0 + 1
964            indexok(isz0) = ii
965            iszij = iszij1(ii)
966         ENDIF
967         inbij = MINVAL(inbij1, mask = inbij1 > inbij)   ! warning: return largest integer value if mask = .false. everywhere
968      END DO
969      DEALLOCATE( inbij1, iszij1 )
970
971      ! keep only the best partitions (sorted by increasing order of subdomains number and decreassing subdomain size)
972      ALLOCATE( inbi0(isz0), inbj0(isz0), iszi0(isz0), iszj0(isz0) )
973      DO ji = 1, isz0
974         ii = indexok(ji)
975         inbi0(ji) = inbi1(ii)
976         inbj0(ji) = inbj1(ii)
977         iszi0(ji) = iszi1(ii)
978         iszj0(ji) = iszj1(ii)
979      END DO
980      DEALLOCATE( indexok, inbi1, inbj1, iszi1, iszj1 )
981
982      IF( llist ) THEN
983         IF(lwp) THEN
984            WRITE(numout,*)
985            WRITE(numout,*) '                  For your information:'
986            WRITE(numout,*) '  list of the best partitions including land supression'
987            WRITE(numout,*) '  -----------------------------------------------------'
988            WRITE(numout,*)
989         END IF
990         ji = isz0   ! initialization with the largest value
991         ALLOCATE( llisoce(inbi0(ji), inbj0(ji)) )
992         CALL mpp_init_isoce( inbi0(ji), inbj0(ji), llisoce ) ! Warning: must be call by all cores (call mpp_sum)
993         inbijold = COUNT(llisoce)
994         DEALLOCATE( llisoce )
995         DO ji =isz0-1,1,-1
996            ALLOCATE( llisoce(inbi0(ji), inbj0(ji)) )
997            CALL mpp_init_isoce( inbi0(ji), inbj0(ji), llisoce ) ! Warning: must be call by all cores (call mpp_sum)
998            inbij = COUNT(llisoce)
999            DEALLOCATE( llisoce )
1000            IF(lwp .AND. inbij < inbijold) THEN
1001               WRITE(numout,'(a, i6, a, i6, a, f4.1, a, i9, a, i6, a, i6, a)')                                 &
1002                  &   'nb_cores oce: ', inbij, ', land domains excluded: ', inbi0(ji)*inbj0(ji) - inbij,       &
1003                  &   ' (', REAL(inbi0(ji)*inbj0(ji) - inbij,wp) / REAL(inbi0(ji)*inbj0(ji),wp) *100.,         &
1004                  &   '%), largest oce domain: ', iszi0(ji)*iszj0(ji), ' ( ', iszi0(ji),' x ', iszj0(ji), ' )'
1005               inbijold = inbij
1006            END IF
1007         END DO
1008         DEALLOCATE( inbi0, inbj0, iszi0, iszj0 )
1009         IF(lwp) THEN
1010            WRITE(numout,*)
1011            WRITE(numout,*)  '  -----------------------------------------------------------'
1012         ENDIF
1013         CALL mppsync
1014         CALL mppstop( ld_abort = .TRUE. )
1015      ENDIF
1016     
1017      DEALLOCATE( iszi0, iszj0 )
1018      inbij = inbijmax + 1        ! default: larger than possible
1019      ii = isz0+1                 ! start from the end of the list (smaller subdomains)
1020      DO WHILE( inbij > knbij )   ! while the number of ocean subdomains exceed the number of procs
1021         ii = ii -1 
1022         ALLOCATE( llisoce(inbi0(ii), inbj0(ii)) )
1023         CALL mpp_init_isoce( inbi0(ii), inbj0(ii), llisoce )            ! must be done by all core
1024         inbij = COUNT(llisoce)
1025         DEALLOCATE( llisoce )
1026      END DO
1027      knbi = inbi0(ii)
1028      knbj = inbj0(ii)
1029      IF(PRESENT(knbcnt))   knbcnt = knbi * knbj - inbij
1030      DEALLOCATE( inbi0, inbj0 )
1031      !
1032   END SUBROUTINE mpp_init_bestpartition
1033   
1034   
1035   SUBROUTINE mpp_init_landprop( propland )
1036      !!----------------------------------------------------------------------
1037      !!                  ***  ROUTINE mpp_init_landprop  ***
1038      !!
1039      !! ** Purpose : the the proportion of land points in the surface land-sea mask
1040      !!
1041      !! ** Method  : read iproc strips (of length jpiglo) of the land-sea mask
1042      !!----------------------------------------------------------------------
1043      REAL(wp), INTENT(  out) :: propland    ! proportion of land points in the global domain (between 0 and 1)
1044      !
1045      INTEGER, DIMENSION(jpni*jpnj) ::   kusedom_1d
1046      INTEGER :: inboce, iarea
1047      INTEGER :: iproc, idiv, ijsz
1048      INTEGER :: ijstr
1049      LOGICAL, ALLOCATABLE, DIMENSION(:,:) ::   lloce
1050      !!----------------------------------------------------------------------
1051      ! do nothing if there is no land-sea mask
1052      IF( numbot == -1 .and. numbdy == -1 ) THEN
1053         propland = 0.
1054         RETURN
1055      ENDIF
1056
1057      ! number of processes reading the bathymetry file
1058      iproc = MINVAL( (/mppsize, jpjglo/2, 100/) )  ! read a least 2 lines, no more that 100 processes reading at the same time
1059     
1060      ! we want to read iproc strips of the land-sea mask. -> pick up iproc processes every idiv processes starting at 1
1061      IF( iproc == 1 ) THEN   ;   idiv = mppsize
1062      ELSE                    ;   idiv = ( mppsize - 1 ) / ( iproc - 1 )
1063      ENDIF
1064
1065      iarea = (narea-1)/idiv   ! involed process number (starting counting at 0)
1066      IF( MOD( narea-1, idiv ) == 0 .AND. iarea < iproc ) THEN   ! beware idiv can be = to 1
1067         !
1068         ijsz = jpjglo / iproc                                               ! width of the stripe to read
1069         IF( iarea < MOD(jpjglo,iproc) ) ijsz = ijsz + 1
1070         ijstr = iarea*(jpjglo/iproc) + MIN(iarea, MOD(jpjglo,iproc)) + 1    ! starting j position of the reading
1071         !
1072         ALLOCATE( lloce(jpiglo, ijsz) )                                     ! allocate the strip
1073         CALL mpp_init_readbot_strip( ijstr, ijsz, lloce )
1074         inboce = COUNT(lloce)                                               ! number of ocean point in the stripe
1075         DEALLOCATE(lloce)
1076         !
1077      ELSE
1078         inboce = 0
1079      ENDIF
1080      CALL mpp_sum( 'mppini', inboce )   ! total number of ocean points over the global domain
1081      !
1082      propland = REAL( jpiglo*jpjglo - inboce, wp ) / REAL( jpiglo*jpjglo, wp ) 
1083      !
1084   END SUBROUTINE mpp_init_landprop
1085   
1086   
1087   SUBROUTINE mpp_init_isoce( knbi, knbj, ldisoce )
1088      !!----------------------------------------------------------------------
1089      !!                  ***  ROUTINE mpp_init_nboce  ***
1090      !!
1091      !! ** Purpose : check for a mpi domain decomposition knbi x knbj which
1092      !!              subdomains contain at least 1 ocean point
1093      !!
1094      !! ** Method  : read knbj strips (of length jpiglo) of the land-sea mask
1095      !!----------------------------------------------------------------------
1096      INTEGER,                       INTENT(in   ) ::   knbi, knbj     ! domain decomposition
1097      LOGICAL, DIMENSION(knbi,knbj), INTENT(  out) ::   ldisoce        ! .true. if a sub domain constains 1 ocean point
1098      !
1099      INTEGER, DIMENSION(knbi,knbj) ::   inboce                        ! number oce oce pint in each mpi subdomain
1100      INTEGER, DIMENSION(knbi*knbj) ::   inboce_1d
1101      INTEGER :: idiv, iimax, ijmax, iarea
1102      INTEGER :: ji, jn
1103      LOGICAL, ALLOCATABLE, DIMENSION(:,:) ::   lloce                  ! lloce(i,j) = .true. if the point (i,j) is ocean
1104      INTEGER, ALLOCATABLE, DIMENSION(:,:) ::   iimppt, ilci
1105      INTEGER, ALLOCATABLE, DIMENSION(:,:) ::   ijmppt, ilcj
1106      !!----------------------------------------------------------------------
1107      ! do nothing if there is no land-sea mask
1108      IF( numbot == -1 .AND. numbdy == -1 ) THEN
1109         ldisoce(:,:) = .TRUE.
1110         RETURN
1111      ENDIF
1112
1113      ! we want to read knbj strips of the land-sea mask. -> pick up knbj processes every idiv processes starting at 1
1114      IF           ( knbj == 1 ) THEN   ;   idiv = mppsize
1115      ELSE IF ( mppsize < knbj ) THEN   ;   idiv = 1
1116      ELSE                              ;   idiv = ( mppsize - 1 ) / ( knbj - 1 )
1117      ENDIF
1118      inboce(:,:) = 0          ! default no ocean point found
1119
1120      DO jn = 0, (knbj-1)/mppsize   ! if mppsize < knbj : more strips than mpi processes (because of potential land domains)
1121         !
1122         iarea = (narea-1)/idiv + jn * mppsize   ! involed process number (starting counting at 0)
1123         IF( MOD( narea-1, idiv ) == 0 .AND. iarea < knbj ) THEN   ! beware idiv can be = to 1
1124            !
1125            ALLOCATE( iimppt(knbi,knbj), ijmppt(knbi,knbj), ilci(knbi,knbj), ilcj(knbi,knbj) )
1126            CALL mpp_basic_decomposition( knbi, knbj, iimax, ijmax, iimppt, ijmppt, ilci, ilcj )
1127            !
1128            ALLOCATE( lloce(jpiglo, ilcj(1,iarea+1)) )                                         ! allocate the strip
1129            CALL mpp_init_readbot_strip( ijmppt(1,iarea+1), ilcj(1,iarea+1), lloce )           ! read the strip
1130            DO  ji = 1, knbi
1131               inboce(ji,iarea+1) = COUNT( lloce(iimppt(ji,1):iimppt(ji,1)+ilci(ji,1)-1,:) )   ! number of ocean point in subdomain
1132            END DO
1133            !
1134            DEALLOCATE(lloce)
1135            DEALLOCATE(iimppt, ijmppt, ilci, ilcj)
1136            !
1137         ENDIF
1138      END DO
1139   
1140      inboce_1d = RESHAPE(inboce, (/ knbi*knbj /))
1141      CALL mpp_sum( 'mppini', inboce_1d )
1142      inboce = RESHAPE(inboce_1d, (/knbi, knbj/))
1143      ldisoce(:,:) = inboce(:,:) /= 0
1144      !
1145   END SUBROUTINE mpp_init_isoce
1146   
1147   
1148   SUBROUTINE mpp_init_readbot_strip( kjstr, kjcnt, ldoce )
1149      !!----------------------------------------------------------------------
1150      !!                  ***  ROUTINE mpp_init_readbot_strip  ***
1151      !!
1152      !! ** Purpose : Read relevant bathymetric information in order to
1153      !!              provide a land/sea mask used for the elimination
1154      !!              of land domains, in an mpp computation.
1155      !!
1156      !! ** Method  : read stipe of size (jpiglo,...)
1157      !!----------------------------------------------------------------------
1158      INTEGER                         , INTENT(in   ) :: kjstr       ! starting j position of the reading
1159      INTEGER                         , INTENT(in   ) :: kjcnt       ! number of lines to read
1160      LOGICAL, DIMENSION(jpiglo,kjcnt), INTENT(  out) :: ldoce       ! ldoce(i,j) = .true. if the point (i,j) is ocean
1161      !
1162      INTEGER                           ::   inumsave                ! local logical unit
1163      REAL(wp), DIMENSION(jpiglo,kjcnt) ::   zbot, zbdy 
1164      !!----------------------------------------------------------------------
1165      !
1166      inumsave = numout   ;   numout = numnul   !   redirect all print to /dev/null
1167      !
1168      IF( numbot /= -1 ) THEN
1169         CALL iom_get( numbot, jpdom_unknown, 'bottom_level', zbot, kstart = (/1,kjstr/), kcount = (/jpiglo, kjcnt/) )
1170      ELSE
1171         zbot(:,:) = 1.                         ! put a non-null value
1172      ENDIF
1173
1174       IF( numbdy /= -1 ) THEN                  ! Adjust with bdy_msk if it exists   
1175         CALL iom_get ( numbdy, jpdom_unknown, 'bdy_msk', zbdy, kstart = (/1,kjstr/), kcount = (/jpiglo, kjcnt/) )
1176         zbot(:,:) = zbot(:,:) * zbdy(:,:)
1177      ENDIF
1178      !
1179      ldoce(:,:) = zbot(:,:) > 0.
1180      numout = inumsave
1181      !
1182   END SUBROUTINE mpp_init_readbot_strip
1183
1184
1185   SUBROUTINE mpp_init_ioipsl
1186      !!----------------------------------------------------------------------
1187      !!                  ***  ROUTINE mpp_init_ioipsl  ***
1188      !!
1189      !! ** Purpose :   
1190      !!
1191      !! ** Method  :   
1192      !!
1193      !! History :
1194      !!   9.0  !  04-03  (G. Madec )  MPP-IOIPSL
1195      !!   " "  !  08-12  (A. Coward)  addition in case of jpni*jpnj < jpnij
1196      !!----------------------------------------------------------------------
1197      INTEGER, DIMENSION(2) ::   iglo, iloc, iabsf, iabsl, ihals, ihale, idid
1198      !!----------------------------------------------------------------------
1199
1200      ! The domain is split only horizontally along i- or/and j- direction
1201      ! So we need at the most only 1D arrays with 2 elements.
1202      ! Set idompar values equivalent to the jpdom_local_noextra definition
1203      ! used in IOM. This works even if jpnij .ne. jpni*jpnj.
1204      iglo(1) = jpiglo
1205      iglo(2) = jpjglo
1206      iloc(1) = nlci
1207      iloc(2) = nlcj
1208      iabsf(1) = nimppt(narea)
1209      iabsf(2) = njmppt(narea)
1210      iabsl(:) = iabsf(:) + iloc(:) - 1
1211      ihals(1) = nldi - 1
1212      ihals(2) = nldj - 1
1213      ihale(1) = nlci - nlei
1214      ihale(2) = nlcj - nlej
1215      idid(1) = 1
1216      idid(2) = 2
1217
1218      IF(lwp) THEN
1219          WRITE(numout,*)
1220          WRITE(numout,*) 'mpp_init_ioipsl :   iloc  = ', iloc (1), iloc (2)
1221          WRITE(numout,*) '~~~~~~~~~~~~~~~     iabsf = ', iabsf(1), iabsf(2)
1222          WRITE(numout,*) '                    ihals = ', ihals(1), ihals(2)
1223          WRITE(numout,*) '                    ihale = ', ihale(1), ihale(2)
1224      ENDIF
1225      !
1226      CALL flio_dom_set ( jpnij, nproc, idid, iglo, iloc, iabsf, iabsl, ihals, ihale, 'BOX', nidom)
1227      !
1228   END SUBROUTINE mpp_init_ioipsl 
1229
1230
1231   SUBROUTINE mpp_init_nfdcom
1232      !!----------------------------------------------------------------------
1233      !!                     ***  ROUTINE  mpp_init_nfdcom  ***
1234      !! ** Purpose :   Setup for north fold exchanges with explicit
1235      !!                point-to-point messaging
1236      !!
1237      !! ** Method :   Initialization of the northern neighbours lists.
1238      !!----------------------------------------------------------------------
1239      !!    1.0  ! 2011-10  (A. C. Coward, NOCS & J. Donners, PRACE)
1240      !!    2.0  ! 2013-06 Setup avoiding MPI communication (I. Epicoco, S. Mocavero, CMCC)
1241      !!----------------------------------------------------------------------
1242      INTEGER  ::   sxM, dxM, sxT, dxT, jn
1243      INTEGER  ::   njmppmax
1244      !!----------------------------------------------------------------------
1245      !
1246      njmppmax = MAXVAL( njmppt )
1247      !
1248      !initializes the north-fold communication variables
1249      isendto(:) = 0
1250      nsndto     = 0
1251      !
1252      IF ( njmpp == njmppmax ) THEN      ! if I am a process in the north
1253         !
1254         !sxM is the first point (in the global domain) needed to compute the north-fold for the current process
1255         sxM = jpiglo - nimppt(narea) - nlcit(narea) + 1
1256         !dxM is the last point (in the global domain) needed to compute the north-fold for the current process
1257         dxM = jpiglo - nimppt(narea) + 2
1258         !
1259         ! loop over the other north-fold processes to find the processes
1260         ! managing the points belonging to the sxT-dxT range
1261         !
1262         DO jn = 1, jpni
1263            !
1264            sxT = nfiimpp(jn, jpnj)                            ! sxT = 1st  point (in the global domain) of the jn process
1265            dxT = nfiimpp(jn, jpnj) + nfilcit(jn, jpnj) - 1    ! dxT = last point (in the global domain) of the jn process
1266            !
1267            IF    ( sxT < sxM  .AND.  sxM < dxT ) THEN
1268               nsndto          = nsndto + 1
1269               isendto(nsndto) = jn
1270            ELSEIF( sxM <= sxT  .AND.  dxM >= dxT ) THEN
1271               nsndto          = nsndto + 1
1272               isendto(nsndto) = jn
1273            ELSEIF( dxM <  dxT  .AND.  sxT <  dxM ) THEN
1274               nsndto          = nsndto + 1
1275               isendto(nsndto) = jn
1276            ENDIF
1277            !
1278         END DO
1279         nfsloop = 1
1280         nfeloop = nlci
1281         DO jn = 2,jpni-1
1282            IF( nfipproc(jn,jpnj) == (narea - 1) ) THEN
1283               IF( nfipproc(jn-1,jpnj) == -1 )   nfsloop = nldi
1284               IF( nfipproc(jn+1,jpnj) == -1 )   nfeloop = nlei
1285            ENDIF
1286         END DO
1287         !
1288      ENDIF
1289      l_north_nogather = .TRUE.
1290      !
1291   END SUBROUTINE mpp_init_nfdcom
1292
1293
1294#endif
1295
1296   !!======================================================================
1297END MODULE mppini
Note: See TracBrowser for help on using the repository browser.