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

source: NEMO/branches/2021/ticket2669_isf_fluxes/src/OCE/LBC/mppini.F90 @ 14994

Last change on this file since 14994 was 14994, checked in by mathiot, 3 years ago

ticket #2669: update to the head of trunk

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