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/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/LBC – NEMO

source: NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/LBC/mppini.F90 @ 13176

Last change on this file since 13176 was 13176, checked in by smasson, 4 years ago

Extra_Halo: rewrite prtctl, supress nn_print, see #2366

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