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 @ 13251

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

Extra_Halo: bugfix following merge with trunk@13218, see #2366

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