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.
Changeset 10335 – NEMO

Changeset 10335


Ignore:
Timestamp:
2018-11-19T15:25:00+01:00 (5 years ago)
Author:
mathiot
Message:

Update of MPP_PREP. Fix #2164

Location:
utils/tools/MPP_PREP
Files:
2 added
2 edited

Legend:

Unmodified
Added
Removed
  • utils/tools/MPP_PREP/namelist

    r2143 r10335  
    11!>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    2 !  MPP_OPTIMIZ_ZOOM namelist 
    3 ! --------------------------- 
     2!  MPP_OPTIMIZE namelist template 
     3! ------------------------------- 
    44!>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    55! 
     
    77!       namspace  spatial indexes 
    88!,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, 
    9 ! NAMELIST /namspace/ jpiglo,jpjglo,jpidta,jpjdta,nizoom,njzoom 
    10 ! jpiglo = overall size of the zoomed region (i-direction) 
    11 ! jpjglo = overall size of the zoomed region (j-direction) 
    12 ! jpidta = overall size of the domain (i-direction) 
    13 ! jpjdta = overall size of the domain (j-direction) 
    14 ! nizoom = i -index of point (1,1) of the zoomed region/ jpidta 
    15 ! njzoom = j -index of point (1,1) of the zoomed region/ jpjdta 
    16 ! 
    17 &NAMSPACE 
    18     jpk=31 
    19     jpiglo =  182 
    20     jpjglo =  149 
    21     jpidta =  182 
    22     jpjdta =  149 
    23     nizoom = 1 
    24     njzoom = 1 
     9&namspace 
     10    nn_jpk   = 75           ! number of vertical level 
     11    nn_izoom = 1            ! i-index of point (1,1) of the zoomed region/ jpidta 
     12    nn_jzoom = 1            ! j-index of point (1,1) of the zoomed region/ jpjdta 
    2513/ 
    2614!''''''''''''''''''''''''''''''''''''' 
    2715!      namproc 
    2816!'''''''''''''''''''''''''''''''''''' 
    29 !   jprocx = maximum number of proc 
    30 !   jpmem = 0 : dont care about the use of memory 
    31 !           1 : try to optimize the use of memory 
    32 ! 
    33 &NAMPROC 
    34      jprocx= 80 
    35      jpmem = 0 
     17&namproc 
     18     nn_procmax = 4000      ! maximum number of proc to look for 
     19     nn_procmin = 100       ! minimum number of proc  
     20     ln_memchk  = .false.   ! optimization of memory 
    3621/ 
    3722!'''''''''''''''''''''''''''''''''''''' 
    3823!      namparam 
    3924!'''''''''''''''''''''''''''''''''''''' 
    40 !  ppmcal = memoire en octet d'un processeur 
    41 !  ppmin = ?? 
    42 !  ppmax = ?? 
    43 ! 
    44 &NAMPARAM 
    45    ppmcal = 225000000. 
    46    ppmin = 0.4 
    47    ppmax = 0.9 
     25&namparam 
     26   rn_ppmcal = 225000000.    ! maximum memory for 1 processor 
     27   rn_ppmin  = 0.4           ! minimum ratio for filling the available memory 
     28   rn_ppmax  = 0.9           ! maximum ratio for filling the available memory 
    4829/ 
    49 ! 
    5030!''''''''''''''''''''''''''''''''''''''' 
    5131!      namfile  of filename 
    5232!,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, 
    53 ! NAMELIST /namfile/ cbathy 
    54 ! cbathy = name of the  bathymetric file(nc) 
    55 ! ln_zps = false if bathy file is level 
    56 !          true  if bathy file is meter 
    57 ! 
    58 &NAMFILE 
    59      cbathy='bathymetry_depth_ORCA_R2_V3.nc' 
    60      ln_zps=.true. 
     33&namfile 
     34     cn_fbathy = 'domain_cfg.nc'  ! bathy file name 
     35     cn_var    = 'bottom_level'   ! Bathy variable name 
     36     cn_x      = 'x'              ! bathy x dimension name 
     37     cn_y      = 'y'              ! bathy y dimension name 
     38     ln_zps    = .true.           ! partial step flag 
    6139/ 
    6240! 
    6341!'''''''''''''''''''''''''''''''''''''' 
    64 !      namkeep  jpni jpnj  kept 
     42!      namkeep  option -keep.  Specify the root name of the overdata file 
    6543!,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,,, 
    66 ! NAMELIST /namkeep/ jpni,jpnj,covdta 
    67 !   jpni = number of procs. in the i-direction 
    68 !   jpnj = number of procs. in the j-direction 
    69 !   covdta = Root for the overdata file name . 
    70 !           Complete name will be {covdta}.{jpni}x{jpnj}_{jpnij} 
    71 &NAMKEEP 
    72     jpni = 7 
    73     jpnj =11  
    74     covdta = 'ORCA2-zahir' 
     44&namkeep 
     45    cn_fovdta = 'domain_cfg'   ! Root for the overdata file name 
     46                               ! complete name will be {covdta}.{jpni}x{jpnj}_{jpnij} 
    7547/ 
  • utils/tools/MPP_PREP/src/mpp_optimiz_zoom_nc.f90

    r6412 r10335  
    1 PROGRAM mpp_optimiz_nc 
    2  !!--------------------------------------------------------------------- 
    3  !! 
    4  !!                       PROGRAM MPP_OPTIMIZ_NC 
    5  !!                     *********************** 
    6  !! 
    7  !!  PURPOSE : 
    8  !!  --------- 
    9  !!              This program is build to optimize the domain beakdown into 
    10  !!              subdomain for mpp computing. 
    11  !!              Once the grid size, and the land/sea mask is known, it looks 
    12  !!              for all the possibilities within a range of setting parameters 
    13  !!              and determine the optimal. 
    14  !! 
    15  !!              Optimization is done with respect to the maximum number of 
    16  !!              sea processors and to the maximum numbers of procs (jprocx) 
    17  !!                      
    18  !!              Optional optimization can be performed takink into account 
    19  !!              the maximum available processor memory ppmcal. This is 
    20  !!              activated if jpmen =1 
    21  !! 
    22  !! history: 
    23  !! -------- 
    24  !!       original  : 95-12 (Imbard M) for OPA8.1, CLIPPER 
    25  !!       f90       : 03-06 (Molines JM), namelist as input 
    26  !!                 : 05-05 (Molines JM), bathy in ncdf 
    27  !!---------------------------------------------------------------------- 
    28  !! * modules used 
    29   USE netcdf 
    30  
    31   IMPLICIT NONE 
    32  
    33   INTEGER ::  jprocx=250   !: maximum number of proc. (Read from namelist) 
    34   INTEGER ::  jpmem=0      !: memory constraint (1) or no constraint (0) 
    35      !                     !  (use 1 with caution as the memory size of  
    36      !                     !   the code lays on OPA 8.1 estimates ...) 
    37      ! 
    38   INTEGER          ::  & 
    39        jpk    = 46  ,    & !: vertical levels (namelist) 
    40        jpiglo = 1442,    & !: I-size of the model (namelist) 
    41        jpjglo = 1021,    & !: J-size of the model (namelist) 
    42        jpidta = 1442,    & !: I-size of the data file (namelist) 
    43        jpjdta = 1021,   &  !: J-size of the data files (namelist) 
    44        nizoom = 1 ,     &  !: I zoom indicator (namelist) 
    45        njzoom = 1 ,     &  !: J zoom indicatori (namelist) 
    46        numnam = 4          !: logical unit for the namelist 
    47   NAMELIST /namspace/ jpk,jpiglo,jpjglo,jpidta,jpjdta,nizoom,njzoom 
    48   NAMELIST /namproc/ jprocx, jpmem 
    49  
    50   INTEGER ::  jpnix ,jpnjx   
     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 
    51128  ! 
    52   INTEGER,PARAMETER :: jpreci=1 ,jprecj=1 
    53   ! 
    54   ! Following variables are used only if jpmem=1 
    55   REAL(KIND=4) ::  ppmpt ,   & 
    56        ppmcal = 225000000., &  !: maximum memory of one processor for a given machine (in 8 byte words) 
    57        ppmin  = 0.4,         & !: minimum ratio to fill the memory 
    58        ppmax  = 0.9            !: maximum ration to fill the memory 
    59   ! Aleph 
    60   !     PARAMETER(ppmcal= 16000000.) 
    61   !Brodie 
    62   !     PARAMETER(ppmcal=250000000.) 
    63   ! Uqbar 
    64   !     PARAMETER(ppmcal=3750000000.) 
    65   ! Zahir 
    66   !     PARAMETER(ppmcal=225000000.) 
    67  
    68   CHARACTER(LEN=80) :: cbathy, &       !: File name of the netcdf bathymetry (namelist) 
    69       &                clvar           !: Variable name in netcdf for the bathy to be read 
    70   LOGICAL ::  ln_zps=.false.           !: Logical flag for partial cells. 
    71   NAMELIST /namfile/ cbathy, ln_zps 
    72   NAMELIST /namparam/ ppmcal, ppmin, ppmax 
    73   ! 
    74   INTEGER :: iumout = 1 
    75   INTEGER :: ji,jj,jn,jni,jnj,jni2,jnj2 
    76   INTEGER :: iumbat,ifreq,il1,il2 
    77   INTEGER :: ii,iim,ij,ijm,imoy,iost,iresti,irestj,isurf,ivide 
    78   INTEGER :: iilb,ijlb,ireci,irecj,in 
    79   INTEGER :: ipi,ipj 
    80   INTEGER :: inf10,inf30,inf50,iptx,isw 
    81   INTEGER :: iii,iij,iiii,iijj,iimoy,iinf10,iinf30,iinf50 
    82   ! 
    83   INTEGER,DIMENSION(:,:),ALLOCATABLE     ::  ibathy    ! jpidta -jpjdta 
    84   INTEGER,DIMENSION(:,:),ALLOCATABLE     ::  ippdi, ippdj ,iidom, ijdom 
    85   ! 
    86   REAL(KIND=4)                           ::  zmin,zmax,zper,zmem 
    87   REAL(KIND=4)                           ::  zzmin,zzmax,zperx 
    88   REAL(KIND=4),DIMENSION(:,:),ALLOCATABLE  ::  zmask ,&  ! jpiglo -jpjglo 
    89       &                                        zdta      ! jpidta -jpjdta 
    90  
    91  ! CDF stuff 
    92   INTEGER :: ncid, ivarid, istatus 
    93   LOGICAL ::  llbon=.false. 
    94   ! 
    95   ! 0. Initialisation 
    96   ! ----------------- 
    97   OPEN(numnam,FILE='namelist') 
    98   REWIND(numnam) 
    99   READ(numnam,namspace) 
    100  
    101   REWIND(numnam) 
    102   READ(numnam,namfile) 
    103  
    104   REWIND(numnam) 
    105   READ(numnam,namparam) 
    106  
    107   REWIND(numnam) 
    108   READ(numnam,namproc) 
    109  
    110   ! estimated  code size expressed in number of 3D arrays (valid for OPA8.1) 
    111   ppmpt = 55.+73./jpk 
    112   jpnix = jprocx ; jpnjx=jprocx 
    113  
    114   ALLOCATE ( ibathy(jpidta,jpjdta), zmask(jpiglo,jpjglo),zdta(jpidta,jpjdta) ) 
    115   ALLOCATE (ippdi(jpnix,jpnjx), ippdj(jpnix,jpnjx) ) 
    116   ALLOCATE (iidom(jpnix,jpnjx), ijdom(jpnix,jpnjx) ) 
    117  
    118   OPEN(iumout,FILE='processor.layout') 
    119   WRITE(iumout,*) 
    120   WRITE(iumout,*) ' optimisation de la partition' 
    121   WRITE(iumout,*) ' ----------------------------' 
    122   WRITE(iumout,*) 
    123   ! 
    124   ! * Read cdf bathy file 
    125   ! 
    126          IF ( ln_zps ) THEN        ! partial steps 
    127             clvar = 'Bathymetry' 
    128          ELSE  
    129             clvar = 'Bathy_level'  ! full steps 
     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 
    130498         ENDIF 
    131  
    132          INQUIRE( FILE=cbathy, EXIST=llbon ) 
    133       IF( llbon ) THEN 
    134             istatus=NF90_OPEN(cbathy,NF90_NOWRITE,ncid) 
    135             istatus=NF90_INQ_VARID(ncid,clvar,ivarid) 
    136             istatus=NF90_GET_VAR(ncid,ivarid,zdta) 
    137             istatus=NF90_CLOSE(ncid) 
    138       ELSE 
    139           PRINT *,' File missing : ', trim(cbathy) 
    140           STOP 
     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  
    141509      ENDIF 
    142   ibathy(:,:)=zdta(:,:) 
    143  
    144   ! 
    145   ! Building the mask 
    146   DO jj=1,jpjglo 
    147      DO ji=1,jpiglo 
    148         zmask(ji,jj) = float(ibathy(ji+nizoom - 1,jj+njzoom -1)) 
    149      END DO 
    150   END DO 
    151  
    152   DO jj=1,jpjglo 
    153      DO ji=1,jpiglo 
    154         zmask(ji,jj)=  min(REAL(1.,kind=4),max(REAL(0.,kind=4),zmask(ji,jj)))  ! Old vector coding rule ... 
    155      END DO 
    156   END DO 
    157   ! 
    158   !  Main loop on processors 
    159   ! ------------------------ 
    160   iii=1 ; iij=1 
    161   iiii=jpiglo ; iijj=jpjglo 
    162   iptx=0 
    163   iimoy=0 
    164   zzmin=0. ; zzmax=0. 
    165   iinf10=0 ; iinf30=0 ; iinf50=0 
    166   zperx=1. 
    167   in=0 
    168   DO jni=1,jpnix 
    169      DO jnj=1,jpnjx 
    170         ! 
    171         ! Limitation ob the maxumun number of PE's 
    172         IF(jni*jnj >  jprocx) goto 1000 
    173         ! 
    174         ! Partition 
    175         ipi=(jpiglo-2*jpreci + (jni-1))/jni + 2*jpreci 
    176         ipj=(jpjglo-2*jprecj + (jnj-1))/jnj + 2*jprecj 
    177         ! 
    178         ! Memory optimization ? 
    179         isw=0 
    180         zmem=ppmpt*ipi*ipj*jpk 
    181         IF(zmem > ppmcal) go to 1000 
    182         IF(jpmem == 1) THEN 
    183            IF(zmem.GT.ppmax*ppmcal.OR.zmem.LT.ppmin*ppmcal) isw=1 
    184         ENDIF 
    185         IF(isw.EQ.1) go to 1000 
    186         in=in+1 
    187         ! 
    188         WRITE(iumout,*) '--> nombre de processeurs ',jni*jnj 
    189         WRITE(iumout,*) ' ' 
    190         WRITE(iumout,*) " jpni=",jni ," jpnj=",jnj 
    191         WRITE(iumout,*) " jpi= ",ipi ," jpj= ",ipj 
    192         zper=(jni*jnj*ipi*ipj)/float(jpiglo*jpjglo) 
    193         WRITE(iumout,*) " rapport jpnij*domain/global domain ",zper 
    194         ! 
    195         ! Coin en bas a gauche de chaque processeur 
    196         ! 
    197         iilb=1 
    198         ijlb=1 
    199         ireci=2*jpreci 
    200         irecj=2*jprecj 
    201         iresti = MOD ( jpiglo - ireci , jni ) 
    202         irestj = MOD ( jpjglo - irecj , jnj ) 
    203         ! 
    204         IF (iresti.EQ.0) iresti = jni 
    205         DO jj=1,jnj 
    206            DO ji=1,iresti 
    207               ippdi(ji,jj) = ipi 
    208            END DO 
    209            DO ji=iresti+1,jni 
    210               ippdi(ji,jj) = ipi -1 
    211            END DO 
    212         END DO 
    213         IF (irestj.EQ.0) irestj = jnj 
    214         DO ji=1,jni 
    215            DO jj=1,irestj 
    216               ippdj(ji,jj) = ipj 
    217            END DO 
    218            DO jj=irestj+1,jnj 
    219               ippdj(ji,jj) = ipj -1 
    220            END DO 
    221         END DO 
    222         DO jj=1,jnj 
    223            DO ji=1,jni 
    224               iidom(ji,jj)=iilb 
    225               ijdom(ji,jj)=ijlb 
    226            END DO 
    227         END DO 
    228         WRITE(iumout,*) " iresti=",iresti," irestj=",irestj 
    229         ! 
    230         !  2. Boucle sur les processeurs 
    231         ! ------------------------------ 
    232         ! 
    233         ivide=0 
    234         imoy=0 
    235         zmin=1.e+20 
    236         zmax=-1.e+20 
    237         inf10=0 
    238         inf30=0 
    239         inf50=0 
    240         ! 
    241         DO jni2=1,jni 
    242            DO jnj2=1,jnj 
    243  
    244               IF(jni.GT.1)THEN 
    245                  DO jj=1,jnj 
    246                     DO ji=2,jni 
    247                        iidom(ji,jj)=iidom(ji-1,jj)+ippdi(ji-1,jj)-ireci 
    248                     END DO 
    249                  END DO 
    250                  iilb=iidom(jni2,jnj2) 
    251               ENDIF 
    252               IF(jnj.GT.1)THEN 
    253                  DO jj=2,jnj 
    254                     DO ji=1,jni 
    255                        ijdom(ji,jj)=ijdom(ji,jj-1)+ippdj(ji,jj-1)-irecj 
    256                     END DO 
    257                  END DO 
    258                  ijlb=ijdom(jni2,jnj2) 
    259               ENDIF 
    260  
    261               ! Check wet points over the entire domain to preserve the MPI communication stencil 
    262               isurf=0 
    263               DO jj=1,ippdj(jni2,jnj2) 
    264                  DO  ji=1,ippdi(jni2,jnj2) 
    265                     IF(zmask(ji+iilb-1,jj+ijlb-1).EQ.1.) isurf=isurf+1 
    266                  END DO 
    267               END DO 
    268  
    269               IF(isurf.EQ.0) THEN 
    270                  ivide=ivide+1 
    271               ELSE 
    272                  imoy=imoy+isurf 
    273               ENDIF 
    274               zper=float(isurf)/float(ipi*ipj) 
    275               IF(zmin.GT.zper.AND.isurf.NE.0) zmin=zper 
    276               IF(zmax.LT.zper.AND.isurf.NE.0) zmax=zper 
    277               IF(zper.LT.0.1.AND.isurf.NE.0) inf10=inf10+1 
    278               IF(zper.LT.0.3.AND.isurf.NE.0) inf30=inf30+1 
    279               IF(zper.LT.0.5.AND.isurf.NE.0) inf50=inf50+1 
    280               ! 
    281               ! 
    282               ! 3. Fin de boucle sur les processeurs, impression 
    283               ! ------------------------------------------------ 
    284               ! 
    285            END DO 
    286         END DO 
    287         WRITE(iumout,*) ' nombre de processeurs       ',jni*jnj 
    288         WRITE(iumout,*) ' nombre de processeurs mer   ',jni*jnj-ivide 
    289         WRITE(iumout,*) ' nombre de processeurs terre ',ivide 
    290         WRITE(iumout,*) ' moyenne de recouvrement     ',float(imoy)/float(jni*jnj-ivide)/float(ipi*ipj) 
    291         WRITE(iumout,*) ' minimum de recouvrement     ',zmin 
    292         WRITE(iumout,*) ' maximum de recouvrement     ',zmax 
    293         WRITE(iumout,*) ' nb de p recouvrement < 10 % ',inf10 
    294         WRITE(iumout,*) ' nb de p      10 < nb < 30 % ',inf30-inf10 
    295         WRITE(iumout,*) ' nb de p      30 < nb < 50 % ',inf50-inf10 -inf30 
    296         WRITE(iumout,*) ' nombre de points integres   ', (jni*jnj-ivide)*ipi*ipj 
    297         WRITE(iumout,*) ' nbr de pts supplementaires  ', (jni*jnj-ivide)*ipi*ipj-jpiglo*jpjglo 
    298         zper=float((jni*jnj-ivide))*float(ipi*ipj)/float(jpiglo*jpjglo) 
    299         WRITE(iumout,*) ' % sup                       ',zper 
    300         WRITE(iumout,*) 
    301         !  
    302         !  
    303         ! 4. Recherche de l optimum 
    304         ! ------------------------- 
    305         ! 
    306         IF(ivide.GT.iptx) THEN 
    307            iii=jni 
    308            iij=jnj 
    309            iiii=ipi 
    310            iijj=ipj 
    311            iptx=ivide 
    312            iimoy=imoy 
    313            zzmin=zmin 
    314            zzmax=zmax 
    315            iinf10=inf10 
    316            iinf30=inf30 
    317            iinf50=inf50 
    318            zperx=zper 
    319         ELSE IF(ivide.EQ.iptx.AND.zperx.LT.zper) THEN 
    320            iii=jni 
    321            iij=jnj 
    322            iiii=ipi 
    323            iijj=ipj 
    324            iimoy=imoy 
    325            zzmin=zmin 
    326            zzmax=zmax 
    327            iinf10=inf10 
    328            iinf30=inf30 
    329            iinf50=inf50 
    330            zperx=zper 
    331         ENDIF 
    332         ! 
    333         ! 5. Fin de boucle sur le nombre de processeurs 
    334         ! --------------------------------------------- 
    335         ! 
    336       1000 continue 
    337      END DO 
    338   END DO 
    339   ! 
    340   ! 
    341   ! 6. Affichage resultat 
    342   ! --------------------- 
    343   ! 
    344   IF(in.EQ.0) THEN 
    345      WRITE(iumout,*) ' le choix n'' a pas pu etre fait ' 
    346      WRITE(iumout,*) 
    347      WRITE(iumout,*) 'le nombre de processeurs maximum est insuffisant' 
    348      STOP  
    349   ENDIF 
    350   WRITE(iumout,*) ' choix optimum' 
    351   WRITE(iumout,*) ' =============' 
    352   WRITE(iumout,*)  
    353   WRITE(iumout,*) '--> nombre de processeurs ',iii*iij 
    354   WRITE(iumout,*) ' ' 
    355   WRITE(iumout,*) " jpni=",iii ," jpnj=",iij 
    356   WRITE(iumout,*) " jpi= ",iiii ," jpj= ",iijj 
    357   WRITE(iumout,*)  
    358   WRITE(iumout,*) ' nombre de processeurs mer   ',iii*iij-iptx 
    359   WRITE(iumout,*) ' nombre de processeurs terre ',iptx 
    360   WRITE(iumout,*) ' moyenne de recouvrement     ',float(iimoy)/float(iii*iij-iptx)/float(iiii*iijj) 
    361   WRITE(iumout,*) ' minimum de recouvrement     ',zzmin 
    362   WRITE(iumout,*) ' maximum de recouvrement     ',zzmax 
    363   WRITE(iumout,*) ' nb de p recouvrement < 10 % ',iinf10 
    364   WRITE(iumout,*) ' nb de p      10 < nb < 30 % ',iinf30-iinf10 
    365   WRITE(iumout,*) ' nb de p      30 < nb < 50 % ',iinf50-iinf10 -iinf30 
    366   WRITE(iumout,*) ' nombre de points integres   ', (iii*iij-iptx)*iiii*iijj 
    367   WRITE(iumout,*) ' nbr de pts supplementaires  ', (iii*iij-iptx)*iiii*iijj-jpiglo*jpjglo 
    368   WRITE(iumout,*) ' % sup                       ',zperx 
    369   WRITE(iumout,*) 
    370   CLOSE(iumout) 
    371   ! 
    372   ! 
    373   ! 
    374   STOP 
    375 END PROGRAM mpp_optimiz_nc 
     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 TracChangeset for help on using the changeset viewer.