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.
mpp_optimiz_zoom_nc.f90 in NEMO/branches/UKMO/dev_fix_mpp_prep/MPP_PREP/src – NEMO

source: NEMO/branches/UKMO/dev_fix_mpp_prep/MPP_PREP/src/mpp_optimiz_zoom_nc.f90 @ 10265

Last change on this file since 10265 was 10265, checked in by mathiot, 5 years ago

update src/mpp_optimiz_zoom_nc.f90 and namelist to NEMO4 beta + add README.rst + add python script to scan the processor.layout output

  • Property svn:keywords set to Id
File size: 24.4 KB
Line 
1PROGRAM mpp_optimize
2   !!======================================================================
3   !!                     ***  PROGRAM  mpp_optimize  ***
4   !!=====================================================================
5   !!  ** Purpose : Propose possible domain decompositions for a given
6   !!               bathymetric file, which is particularly intersting when
7   !!               we want to eliminate land-only domain.
8   !!               All solution are proposed and written to output file.
9   !!               The ratio between the effective number of computed
10   !!               point and the total number of points in the domain is
11   !!               given and is probably a major criteria for choosing a
12   !!               domain decomposition.
13   !!
14   !!  ** Method  : Use mpp_init like code for seting up the decomposition
15   !!               and evaluate the efficiency of the decomposition.
16   !! History
17   !!       original  : 95-12 (Imbard M) for OPA8.1, CLIPPER
18   !!       f90       : 03-06 (Molines JM), namelist as input
19   !!                 : 05-05 (Molines JM), bathy in ncdf
20   !!                 : 13-03 (Molines JM), Nemo-like coding and license.
21   !!                 : 18-10 (Mathiot  P), upgrade the NEMO 4.0
22   !!----------------------------------------------------------------------
23   !!----------------------------------------------------------------------
24   !!   routines      : description
25   !!----------------------------------------------------------------------
26
27
28   !!----------------------------------------------------------------------
29   !! MPP-PREP, MEOM 2013
30   !! $Id$
31   !! Copyright (c) 2013, J.-M. Molines
32   !! Software governed by the CeCILL licence (Licence/MPP-PREPCeCILL.txt)
33   !!----------------------------------------------------------------------
34   USE netcdf
35
36   IMPLICIT NONE
37
38   INTEGER, PARAMETER :: jpreci=1 ,jprecj=1   !: overlap between processors
39
40   ! Namelist declaration and definition
41   ! -----------------------------------
42   INTEGER ::  nn_procmax  =250    !: maximum number of proc. (Read from namelist)
43   INTEGER ::  nn_procmin  = 1     !: maximum number of proc. (Read from namelist)
44   LOGICAL ::  ln_memchk = .FALSE. ! add a memory constraint if true (obsolete)
45   NAMELIST /namproc/ nn_procmax, nn_procmin, ln_memchk
46   !
47   INTEGER ::  nn_jpk = 46   !: vertical levels
48   INTEGER ::  nn_izoom = 1  !: I zoom indicator
49   INTEGER ::  nn_jzoom = 1  !: J zoom indicator
50   NAMELIST /namspace/ nn_jpk, nn_izoom, nn_jzoom
51   !
52   ! Following variables are used only if ln_memchk=.true.
53   REAL(KIND=4) ::  required_memory, rppmpt !: not in namelist working array
54   REAL(KIND=4) ::  rn_ppmcal = 225000000. !: maximum memory of one processor for a
55   !: given machine (in 8 byte words)
56   REAL(KIND=4) ::  rn_ppmin  = 0.4        !: minimum ratio to fill the memory
57   REAL(KIND=4) ::  rn_ppmax = 0.9         !: maximum ratio to fill the memory
58   NAMELIST /namparam/ rn_ppmcal, rn_ppmin, rn_ppmax
59   !
60   CHARACTER(LEN=80) :: cn_var='none'   !: Variable name of the bathymetry
61   CHARACTER(LEN=80) :: cn_x='x'        !: X dimension name
62   CHARACTER(LEN=80) :: cn_y='y'        !: Y dimension name
63   CHARACTER(LEN=80) :: cn_fbathy       !: File name of the netcdf bathymetry (namelist)
64   LOGICAL           :: ln_zps=.FALSE.  !: Logical flag for partial cells.
65   NAMELIST /namfile/ cn_fbathy, cn_var, cn_x, cn_y,  ln_zps
66   !
67   CHARACTER(LEN=80) :: cn_fovdta     !: root file name for keep output
68   NAMELIST /namkeep/ cn_fovdta
69   !
70   INTEGER            :: numnam = 4       ! logical unit for namelist
71   INTEGER            :: numout = 10        ! logical unit for output
72   INTEGER            :: npiglo, npjglo   ! domain size
73   INTEGER            :: npidta, npjdta   ! domain size
74
75   INTEGER            :: ji, jj, jni, jnj ! dummy loop index
76   INTEGER            :: ii, ij, jjc  ! dummy loop index
77   INTEGER            :: narg, iargc, ijarg      ! browsing command line
78
79   ! Decomposition related arrays (using same meaning than in NEMO)
80   INTEGER, DIMENSION(:,:), ALLOCATABLE :: ilci, ilcj ,iimppt, ijmppt
81   INTEGER, DIMENSION(:)  , ALLOCATABLE :: nlei_ocea, nldi_ocea
82   INTEGER, DIMENSION(:)  , ALLOCATABLE :: nlej_ocea, nldj_ocea
83   INTEGER, DIMENSION(:)  , ALLOCATABLE :: nlei_land, nldi_land
84   INTEGER, DIMENSION(:)  , ALLOCATABLE :: nlej_land, nldj_land
85   INTEGER                              :: nimpp, njmpp
86   INTEGER                              :: nreci, nrecj
87   INTEGER                              :: ili, ilj
88   INTEGER                              :: jarea, iarea, iarea0
89   INTEGER                              :: iresti, irestj
90   !
91   INTEGER :: ioce, isurf             !: number of ocean points cumulated, per_proc
92   INTEGER :: ioce_opt                !: number of ocean points cumulated for optimal case
93   INTEGER :: nland, nocea, nvalid    !: number of land, ocean, memory_valid  procs
94   INTEGER :: nland_opt               !: optimal number of land procs
95   INTEGER :: ii1, ii2, ij1, ij2      !: limit of subdomain in global domain
96   INTEGER :: jpimax,     jpjmax            !: size of sub domain
97   INTEGER :: jpimax_opt, jpjmax_opt        !: size of sub domain for optimal case
98   INTEGER :: inf10,     inf30,     inf50      !:
99   INTEGER :: inf10_opt, inf30_opt, inf50_opt  !:  in optimal case
100   INTEGER :: npni_opt, npnj_opt      !: optimal domain decomposition
101
102   INTEGER :: iminproci, imaxproci    !: limits of the processor loop
103   INTEGER :: iminprocj, imaxprocj    !: can be reduded to  nkeepi, nkeepj
104
105   ! Saving criteria
106   REAL(KIND=4) :: ratio_min=99999.   !: keep only decomposition with ration less than ratio_min
107   INTEGER      :: nocea_min = 1      !: minimum number of ocean procs for saving
108   INTEGER      :: nmodulo = 1        !: Only keep solution multiple of nmodulo
109   LOGICAL      :: ll_criteria=.TRUE. !:
110   !
111   REAL(KIND=4)                              ::  oce_cover
112   REAL(KIND=4)                              ::  oce_cover_min,     oce_cover_max,     ratio
113   REAL(KIND=4)                              ::  oce_cover_min_opt, oce_cover_max_opt, ratio_opt
114   REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE ::  tmask     ! npiglo x npjglo
115   REAL(KIND=4), DIMENSION(:,:), ALLOCATABLE ::  bathy     ! npidta x npjdta
116
117   ! CDF stuff
118   INTEGER :: ncid, istatus, id
119   LOGICAL ::  ll_good = .FALSE.
120
121   CHARACTER(LEN=80) :: cf_namlist='namelist'
122   CHARACTER(LEN=80) :: cf_out='processor.layout'
123   CHARACTER(LEN=80) :: cdum                       ! dummy character variable
124
125   ! Keep stuff     
126   LOGICAL ::  ll_keep = .FALSE.
127   INTEGER :: nkeepi, nkeepj          !: for option -keep : the retained decomposition
128  !
129
130   !!----------------------------------------------------------------------
131   narg=iargc()
132   ijarg=1
133   IF ( narg == 0 ) THEN
134      PRINT *,' try mpp_optimize -h for instructions !'
135      STOP
136   ENDIF
137   !
138   DO WHILE ( ijarg <= narg )
139      CALL getarg(ijarg,cdum) ; ijarg=ijarg+1
140      SELECT CASE ( cdum )
141      CASE ('-h') 
142         PRINT *,'  usage : mpp_optimize [ -h ]  [-keep jpni jpnj] [ -o file out ] '
143         PRINT *,'               [ -modulo val ] [-r ratio] [-minocean procs] -n namelist'
144         PRINT *,'      '
145         PRINT *,'     PURPOSE :'
146         PRINT *,'         This program is build to optimize the domain beakdown into'
147         PRINT *,'         subdomain for mpp computing.'
148         PRINT *,'         Once the grid size, and the land/sea mask is known, it looks'
149         PRINT *,'         for all the possibilities within a range of setting parameters'
150         PRINT *,'         and determine the optimal.'
151         PRINT *,''
152         PRINT *,'         Optimization is done with respect to the maximum number of'
153         PRINT *,'         sea processors and to the maximum numbers of procs (nn_procmax)'
154         PRINT *,'                '
155         PRINT *,'         Optional optimization can be performed taking into account'
156         PRINT *,'         the maximum available processor memory rn_ppmcal. This is'
157         PRINT *,'         activated if ln_memchk is set true in the namelist'
158         PRINT *,'      '
159         PRINT *,'         Additional criteria can be given on the command line to reduce'
160         PRINT *,'         the amount of possible choices.'
161         PRINT *,'      '
162         PRINT *,'     ARGUMENTS :'
163         PRINT *,'         -n namelist : indicate the name of the namelist to use'
164         PRINT *,'      '
165         PRINT *,'     OPTIONS :'
166         PRINT *,'         -h : print this help message'
167         PRINT *,'         -keep jpni jpnj : print a file suitable for plotting,'
168         PRINT *,'                 corresponding to the given decomposition'
169         PRINT *,'         -o output file : give the name of the output file'
170         PRINT *,'                 default is ',TRIM(cf_out)
171         PRINT *,'         -modulo val : only retain decomposition whose total number'
172         PRINT *,'                 of util processors (sea) are a multiple of val'
173         PRINT *,'         -r ratio : only retain decomposition with a ratio computed/global'
174         PRINT *,'                 less or equal to the given ratio'
175         PRINT *,'         -minocean procs : only retain decomposition with a number of '
176         PRINT *,'                 ocean procs greater of equal to procs'
177         PRINT *,'      '
178         PRINT *,'     REQUIRED FILES :'
179         PRINT *,'       A bathymetric file and an ad-hoc namelist are required.'
180         PRINT *,'       The file name of the bathymetry is specified in the namelist'
181         PRINT *,'      '
182         PRINT *,'     OUTPUT : '
183         PRINT *,'       ',TRIM(cf_out),' : an ascii file with all found possibilities'
184         PRINT *,'      '
185         STOP
186      CASE ('-n' )
187         CALL getarg(ijarg,cf_namlist) ; ijarg=ijarg+1
188      CASE ('-o' )
189         CALL getarg(ijarg,cf_out) ; ijarg=ijarg+1
190      CASE ('-keep' )
191         ll_keep=.TRUE.
192         CALL getarg(ijarg,cdum) ; ijarg=ijarg+1 ; READ( cdum,*) nkeepi
193         CALL getarg(ijarg,cdum) ; ijarg=ijarg+1 ; READ( cdum,*) nkeepj
194      CASE ('-modulo' )
195         CALL getarg(ijarg,cdum) ; ijarg=ijarg+1 ; READ( cdum,*) nmodulo
196      CASE ('-r' )
197         CALL getarg(ijarg,cdum) ; ijarg=ijarg+1 ; READ( cdum,*) ratio_min
198      CASE ('-minocean' )
199         CALL getarg(ijarg,cdum) ; ijarg=ijarg+1 ; READ( cdum,*) nocea_min
200      END SELECT
201   ENDDO
202
203   ! Open and read the namelist
204   OPEN(numnam,FILE=cf_namlist)
205   REWIND(numnam)
206   READ(numnam,namspace)
207
208   REWIND(numnam)
209   READ(numnam,namfile)
210
211   REWIND(numnam)
212   READ(numnam,namparam)
213
214   REWIND(numnam)
215   READ(numnam,namproc)
216
217   REWIND(numnam)
218   READ(numnam,namkeep)  ! only used for -keep option but still ...
219   CLOSE(numnam)
220
221   ! estimated code size expressed in number of 3D arrays (valid for OPA8.1) to be tuned for OPA9.0/Nemo
222   rppmpt = 55.+73./nn_jpk
223
224   ! Open bathy file an allocate required memory
225   INQUIRE( FILE=cn_fbathy, EXIST=ll_good )
226   IF( ll_good ) THEN
227      istatus = NF90_OPEN(cn_fbathy, NF90_NOWRITE, ncid)
228      istatus = NF90_INQ_DIMID(ncid, cn_x, id) ; istatus = NF90_INQUIRE_DIMENSION(ncid, id, len=npiglo)
229      istatus = NF90_INQ_DIMID(ncid, cn_y, id) ; istatus = NF90_INQUIRE_DIMENSION(ncid, id, len=npjglo)
230      npidta  = npiglo ; npjdta=npjglo
231   ELSE
232      PRINT *,' File missing : ', TRIM(cn_fbathy)
233      STOP 42
234   ENDIF
235
236   ALLOCATE (tmask(npiglo,npjglo), bathy(npidta,npjdta) )
237   ALLOCATE (ilci(nn_procmax,nn_procmax), ilcj(nn_procmax,nn_procmax) )
238   ALLOCATE (iimppt(nn_procmax,nn_procmax), ijmppt(nn_procmax,nn_procmax) )
239
240   ! Open output file for results
241   IF ( ll_keep ) THEN
242      nn_procmax = nkeepi*nkeepj  ! reduce nn_procmax
243      ! File will be open later
244   ELSE
245      OPEN(numout,FILE=cf_out)
246      WRITE(numout,*)
247      WRITE(numout,*) ' Domain decomposition optimization '
248      WRITE(numout,*) ' ----------------------------------'
249      WRITE(numout,*)
250   ENDIF
251   !
252   ALLOCATE ( nlei_ocea(nn_procmax), nldi_ocea(nn_procmax), nlej_ocea(nn_procmax), nldj_ocea(nn_procmax) )
253   ALLOCATE ( nlei_land(nn_procmax), nldi_land(nn_procmax), nlej_land(nn_procmax), nldj_land(nn_procmax) )
254   !
255   ! Read cdf bathy file
256   IF ( cn_var == 'none' ) THEN  ! automatic detection of variable name according to partial step
257      IF ( ln_zps ) THEN           ! partial steps
258         cn_var = 'Bathymetry'
259      ELSE
260         cn_var = 'Bathy_level'    ! full steps
261      ENDIF
262   ENDIF
263   PRINT *,''
264   PRINT *,' ocean/land file used is: ', TRIM(cn_fbathy)
265   PRINT *,' variable used to find ocean domain is: ', TRIM(cn_var)
266   PRINT *,' Dimensions (jpi x jpj) are: ',npiglo,'x',npjglo
267   PRINT *,''
268
269   istatus = NF90_INQ_VARID (ncid, cn_var, id)
270   istatus = NF90_GET_VAR   (ncid, id,   bathy)
271   istatus = NF90_CLOSE     (ncid)
272   !
273   ! Building the mask ( eventually on a smaller domain than the bathy)
274   tmask(:,:) = bathy(nn_izoom:nn_izoom+npiglo -1,  nn_jzoom:nn_jzoom+npjglo -1)
275
276   WHERE ( tmask > 0 ) 
277      tmask = 1.
278   ELSEWHERE
279      tmask = 0.
280   ENDWHERE
281
282   !  Main loop on processors
283   ! ------------------------
284   ! initialization of working variables
285   npni_opt=1       ; npnj_opt=1
286   jpimax_opt=npiglo ; jpjmax_opt=npjglo
287   nland_opt=0   
288   ioce_opt=0
289   oce_cover_min_opt=0. ; oce_cover_max_opt=0.
290   inf10_opt=0 ; inf30_opt=0 ; inf50_opt=0
291   ratio_opt=1.
292
293   nvalid=0       ! counter for valid case ( ln_memchk true )
294   IF ( ll_keep ) THEN
295      iminproci = nkeepi    ; imaxproci = iminproci
296      iminprocj = nkeepj    ; imaxprocj = iminprocj
297   ELSE
298      iminproci = 1    ; imaxproci = MIN( nn_procmax, npiglo )
299      iminprocj = 1    ; imaxprocj = MIN( nn_procmax, npjglo )
300   ENDIF
301
302   ! loop on all decomposition a priori
303   PRINT *, 'Loop over all the decomposition (can take a while) ...'
304   PRINT *, ''
305   DO jni=iminproci, imaxproci
306      DO jnj=iminprocj, imaxprocj
307         ! Limitation of the maxumun number of PE's
308         IF ( jni*jnj <=  nn_procmax .AND. jni*jnj >= nn_procmin )  THEN
309            !
310            !  1. Dimension arrays for subdomains
311            ! -----------------------------------
312            !
313            ! Partition : size of sub-domain
314            jpimax=(npiglo-2*jpreci + (jni-1))/jni + 2*jpreci
315            jpjmax=(npjglo-2*jprecj + (jnj-1))/jnj + 2*jprecj
316            !
317            ! Memory optimization ?
318            IF ( ln_memchk ) THEN
319               required_memory=rppmpt*jpimax*jpjmax*nn_jpk
320               IF( required_memory > rn_ppmcal ) EXIT
321               IF( required_memory > rn_ppmax*rn_ppmcal .OR. required_memory < rn_ppmin*rn_ppmcal) EXIT
322            ENDIF
323            nvalid=nvalid+1
324            !
325            ! Position of each sub domain   (jni x jni in total )
326            nreci  = 2*jpreci                      ; nrecj  = 2*jprecj
327            iresti = 1 + MOD ( npiglo - nreci - 1 , jni )  ; irestj = 1 + MOD ( npjglo - nrecj - 1 , jnj )
328            !
329            !
330            ilci(       1:iresti, 1:jnj) = jpimax
331            ilci(iresti+1:jni   , 1:jnj) = jpimax-1
332
333            ilcj(1:jni,       1:irestj) = jpjmax
334            ilcj(1:jni,irestj+1:jnj   ) = jpjmax-1
335
336            !  2. Index arrays for subdomains
337            ! -------------------------------
338            iimppt(1:jni, 1:jnj) =  1
339            ijmppt(1:jni, 1:jnj) =  1
340            IF( jni > 1 ) THEN
341               DO jj=1,jnj
342                  DO ji=2,jni
343                     iimppt(ji,jj)= iimppt(ji-1,jj) + ilci(ji-1,jj) - nreci
344                  END DO
345               END DO
346            ENDIF
347
348            IF( jnj > 1 ) THEN
349               DO jj=2,jnj
350                  DO ji=1,jni
351                     ijmppt(ji,jj)= ijmppt(ji,jj-1) + ilcj(ji,jj-1) - nrecj
352                  END DO
353               END DO
354            ENDIF
355            !
356            ! Loop on each subdomain to look for land proportion
357            nland = 0
358            nocea = 0
359            ioce  = 0
360            oce_cover_min = 1.e+20
361            oce_cover_max = -1.e+20
362            inf10=0
363            inf30=0
364            inf50=0
365            !
366            ! 3. Subdomain description in the Regular Case
367            ! --------------------------------------------
368            !
369            DO jarea = 1, jni*jnj
370                  iarea0 = jarea - 1
371                  ii = 1 + MOD(iarea0,jni)
372                  ij = 1 +     iarea0/jni
373                  ili = ilci(ii,ij)
374                  ilj = ilcj(ii,ij)
375
376                  isurf = 0
377                  ! loop on inner point of sub-domain
378                  DO jj=1, ilj
379                     DO  ji=1, ili
380                        IF( tmask(ji + iimppt(ii,ij) - 1, jj + ijmppt(ii,ij) - 1) == 1 ) isurf=isurf+1
381                     END DO
382                  END DO
383
384                  nimpp = iimppt(ii,ij)
385                  njmpp = ijmppt(ii,ij)
386                  ii1   = nimpp+jpreci      ; ii2 = nimpp+ili-1 -jpreci
387                  ij1   = njmpp+jprecj      ; ij2 = njmpp+ilj-1 -jprecj
388                  IF ( isurf == 0 ) THEN
389                     nland = nland+1
390                     nldi_land(nland) = ii1
391                     nlei_land(nland) = ii2
392                     nldj_land(nland) = ij1
393                     nlej_land(nland) = ij2
394                  ELSE
395                     nocea = nocea+1
396                     ioce  = ioce + isurf
397                     nldi_ocea(nocea) = ii1
398                     nlei_ocea(nocea) = ii2
399                     nldj_ocea(nocea) = ij1
400                     nlej_ocea(nocea) = ij2
401                  ENDIF
402
403                  ! ratio of wet points over total number of point per proc.
404                  oce_cover = float(isurf)/float(jpimax*jpjmax)
405
406                  IF(oce_cover_min > oce_cover .AND. isurf /= 0) oce_cover_min=oce_cover
407                  IF(oce_cover_max < oce_cover .AND. isurf /= 0) oce_cover_max=oce_cover
408                  IF(oce_cover     < 0.1       .AND. isurf /= 0) inf10=inf10+1
409                  IF(oce_cover     < 0.3       .AND. isurf /= 0) inf30=inf30+1
410                  IF(oce_cover     < 0.5       .AND. isurf /= 0) inf50=inf50+1
411                  !
412               !END DO  ! loop on processors
413            END DO     ! loop on processors
414            !
415            ratio=float(nocea)*float(jpimax*jpjmax)/float(npiglo*npjglo)
416
417            ! criteria for printing results
418            ll_criteria = ( ( MOD ( nocea, nmodulo ) == 0 ) .AND. &
419                 &          ( ratio <= ratio_min          ) .AND. &
420                 &          ( nocea >= nocea_min           )  )
421            IF ( ll_keep ) THEN   ! the loop in done only once !
422               WRITE(cdum,'(a,"-",i3.3,"x",i3.3,"_",i4.4)') TRIM(cn_fovdta), nkeepi, nkeepj, nocea
423               OPEN(numout, file=cdum )
424               WRITE(numout,'("# ocean ",i5)') nocea
425               DO jjc=1, nocea
426                  WRITE(numout,'("#",i5)') jjc
427                  WRITE(numout,'(2i5)') nldi_ocea(jjc)-1+nn_izoom-1, nldj_ocea(jjc)-1+nn_jzoom -1
428                  WRITE(numout,'(2i5)') nlei_ocea(jjc)+1+nn_izoom-1, nldj_ocea(jjc)-1+nn_jzoom -1
429                  WRITE(numout,'(2i5)') nlei_ocea(jjc)+1+nn_izoom-1, nlej_ocea(jjc)+1+nn_jzoom -1
430                  WRITE(numout,'(2i5)') nldi_ocea(jjc)-1+nn_izoom-1, nlej_ocea(jjc)+1+nn_jzoom -1
431                  WRITE(numout,'(2i5)') nldi_ocea(jjc)-1+nn_izoom-1, nldj_ocea(jjc)-1+nn_jzoom -1
432                  WRITE(numout,'(2i5)') 9999, 9999
433               ENDDO
434               !
435               WRITE(numout,'("# land ",i5)') nland
436               DO jjc=1, nland
437                  WRITE(numout,'("# land ",i5)') jjc
438                  WRITE(numout,'(2i5)') nldi_land(jjc)-1+nn_izoom-1, nldj_land(jjc)-1+nn_jzoom -1
439                  WRITE(numout,'(2i5)') nlei_land(jjc)+1+nn_izoom-1, nldj_land(jjc)-1+nn_jzoom -1
440                  WRITE(numout,'(2i5)') nlei_land(jjc)+1+nn_izoom-1, nlej_land(jjc)+1+nn_jzoom -1
441                  WRITE(numout,'(2i5)') nldi_land(jjc)-1+nn_izoom-1, nlej_land(jjc)+1+nn_jzoom -1
442                  WRITE(numout,'(2i5)') nldi_land(jjc)-1+nn_izoom-1, nldj_land(jjc)-1+nn_jzoom -1
443                  WRITE(numout,'(2i5)') nlei_land(jjc)+1+nn_izoom-1, nlej_land(jjc)+1+nn_jzoom -1
444                  WRITE(numout,'(2i5)') nldi_land(jjc)-1+nn_izoom-1, nlej_land(jjc)+1+nn_jzoom -1
445                  WRITE(numout,'(2i5)') nlei_land(jjc)+1+nn_izoom-1, nldj_land(jjc)-1+nn_jzoom -1
446                  WRITE(numout,'(2i5)') 9999, 9999
447               ENDDO
448               !
449            ELSE
450               IF ( ll_criteria ) THEN
451                  WRITE(numout,*) ' iresti=',iresti,' irestj=',irestj
452                  WRITE(numout,*) '--> Total number of domains ',jni*jnj
453                  WRITE(numout,*) ' '
454                  WRITE(numout,*) ' jpni=',jni ,' jpnj=',jnj
455                  WRITE(numout,*) ' jpi= ',jpimax ,' jpj= ',jpjmax
456                  WRITE(numout,*) ' Number of ocean processors       ', nocea
457                  WRITE(numout,*) ' Number of land processors        ', nland
458                  WRITE(numout,*) ' Mean ocean coverage per domain   ', float(ioce)/float(nocea)/float(jpimax*jpjmax)
459                  WRITE(numout,*) ' Minimum ocean coverage           ', oce_cover_min
460                  WRITE(numout,*) ' Maximum ocean coverage           ', oce_cover_max
461                  WRITE(numout,*) ' nb of proc with coverage         < 10 % ', inf10
462                  WRITE(numout,*) ' nb of proc with coverage 10 < nb < 30 % ', inf30 - inf10
463                  WRITE(numout,*) ' nb of proc with coverage 30 < nb < 50 % ', inf50 - inf30
464                  WRITE(numout,*) ' Number of computed points        ', nocea*jpimax*jpjmax
465                  WRITE(numout,*) ' Overhead of computed points      ', nocea*jpimax*jpjmax-npiglo*npjglo
466                  WRITE(numout,*) ' % sup (computed / global)        ', ratio
467                  WRITE(numout,*)
468               ENDIF   ! note that indication of optimum does not take modulo into account (for information)
469               !
470               ! Look for optimum
471               IF( nland > nland_opt ) THEN
472                  npni_opt          = jni
473                  npnj_opt          = jnj
474                  jpimax_opt           = jpimax
475                  jpjmax_opt           = jpjmax
476                  nland_opt         = nland
477                  ioce_opt          = ioce
478                  oce_cover_min_opt = oce_cover_min
479                  oce_cover_max_opt = oce_cover_max
480                  inf10_opt         = inf10
481                  inf30_opt         = inf30
482                  inf50_opt         = inf50
483                  ratio_opt         = ratio
484               ELSE IF( nland == nland_opt .AND. ratio_opt < ratio) THEN
485                  npni_opt          = jni
486                  npnj_opt          = jnj
487                  jpimax_opt           = jpimax
488                  jpjmax_opt           = jpjmax
489                  ioce_opt          = ioce
490                  oce_cover_min_opt = oce_cover_min
491                  oce_cover_max_opt = oce_cover_max
492                  inf10_opt         = inf10
493                  inf30_opt         = inf30
494                  inf50_opt         = inf50
495                  ratio_opt         = ratio
496               ENDIF
497            ENDIF
498         ENDIF
499      END DO
500   END DO
501   !
502   ! print optimal result
503   IF ( .NOT. ll_keep ) THEN
504      IF ( nvalid == 0 ) THEN
505         WRITE(numout,*) ' no possible choice ...'
506         WRITE(numout,*)
507         WRITE(numout,*) 'insufficient number of processors for the available memory'
508         STOP
509      ENDIF
510
511      WRITE(numout,*) ' Optimal choice'
512      WRITE(numout,*) ' =============='
513      WRITE(numout,*) 
514      WRITE(numout,*) '--> Total number of domains ',npni_opt*npnj_opt
515      WRITE(numout,*) ' '
516      WRITE(numout,*) ' jpni=',npni_opt ,' jpnj=',npnj_opt
517      WRITE(numout,*) ' jpi= ',jpimax_opt ,' jpj= ',jpjmax_opt
518      WRITE(numout,*) 
519      WRITE(numout,*) ' Number of ocean processors  ', npni_opt*npnj_opt-nland_opt
520      WRITE(numout,*) ' Number of land processors   ', nland_opt
521      WRITE(numout,*) ' Mean ocean coverage         ', float(ioce_opt)/float(npni_opt*npnj_opt-nland_opt)/float(jpimax_opt*jpjmax_opt)
522      WRITE(numout,*) ' Minimum ocean coverage      ', oce_cover_min_opt
523      WRITE(numout,*) ' Maximum ocean coverage      ', oce_cover_max_opt
524      WRITE(numout,*) ' nb of proc with coverage         < 10 % ', inf10_opt
525      WRITE(numout,*) ' nb of proc with coverage 10 < nb < 30 % ', inf30_opt - inf10_opt
526      WRITE(numout,*) ' nb of proc with coverage 30 < nb < 50 % ', inf50_opt - inf30_opt
527      WRITE(numout,*) ' Number of computed points   ', (npni_opt*npnj_opt-nland_opt)*jpimax_opt*jpjmax_opt
528      WRITE(numout,*) ' Overhead of computed points ', (npni_opt*npnj_opt-nland_opt)*jpimax_opt*jpjmax_opt-npiglo*npjglo
529      WRITE(numout,*) ' % sup (computed / global)   ', ratio_opt
530      WRITE(numout,*)
531   ENDIF
532   CLOSE(numout)
533   !
534   STOP
535END PROGRAM mpp_optimize
Note: See TracBrowser for help on using the repository browser.