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/2021/ticket2680_C1D_PAPA/src/OCE/LBC – NEMO

source: NEMO/branches/2021/ticket2680_C1D_PAPA/src/OCE/LBC/mppini.F90 @ 14984

Last change on this file since 14984 was 14984, checked in by smasson, 3 years ago

ticket2680_C1D_PAPA: fix to work with key_mpi_off, #2680

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