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 10338 for utils/tools/REBUILD_NEMO – NEMO

Ignore:
Timestamp:
2018-11-19T17:40:09+01:00 (5 years ago)
Author:
mathiot
Message:

Add deflation/chunking to rebuild_nemo tool. Fix #2165

Location:
utils/tools/REBUILD_NEMO
Files:
3 added
2 edited

Legend:

Unmodified
Added
Removed
  • utils/tools/REBUILD_NEMO/rebuild_nemo

    r9048 r10338  
    1010   echo "  ************" 
    1111   echo 
    12    echo "  usage: ${0##*/} [-l -t -c -m -n] filebase ndomain [rebuild dimensions]" 
     12   echo "  usage: ${0##*/} [-l -p -s -m -n -r -d -x -y -z -t -c] filebase ndomain [rebuild dimensions]" 
    1313   echo 
    14    echo "  flags:    -l                 submit to compute node" 
    15    echo "            -t num             use num threads" 
    16    echo "            -c num             split 4D vars into time chuncks of size num" 
     14   echo "  flags:    -l arch            submit to compute node" 
     15   echo "            -p num             use num threads" 
     16   echo "            -s num             split 4D vars into time slice of size num" 
    1717   echo "            -m                 force masking of global arrays (zero if no mdi)" 
    18    echo "            -d deflate_level   deflate level for output files (key_netcdf4 only)" 
    1918   echo "            -n namelist        full path to namelist file to be created (otherwise default nam_rebuild+_process_id is used)" 
    2019   echo "            -r memory          Memory to request on compute node including units (Default = 10Gb)" 
     20   echo "" 
     21   echo "      key_netcdf4 only " 
     22   echo "            -d deflate_level     deflate level for output files" 
     23   echo "            -x chunksize along x "  
     24   echo "            -y chunksize along y "  
     25   echo "            -z chunksize along z "  
     26   echo "            -t chunksize along t "  
     27   echo "            -c total size of the chunk cache " 
    2128   echo 
    2229   exit 1 
    2330} 
    2431 
    25 while getopts c:n:t:d:r:lm opt 
     32while getopts l:p:s:n:r:d:x:y:z:t:c:m opt 
    2633do 
    2734  case ${opt} in 
    2835      l)  
    2936         BATCH="yes" 
    30          BATCH_CMD="qsub"  
    31          ARCH="XC40_METO" 
    32          echo "Submitting job to compute node" 
     37         ARCH=${OPTARG} 
    3338      ;; 
    34       t) 
     39      p) 
    3540         OMP_NUM_THREADS=${OPTARG} 
    3641      ;; 
    37       c) 
    38          NCHUNKSIZE=${OPTARG} 
     42      s) 
     43         NSLICESIZE=${OPTARG} 
    3944      ;; 
    4045      m)  
    4146         NMASK="TRUE" 
    42          echo "mask" 
     47         echo "" 
     48         echo "output is mask using netcdf missing value (_Fillvalue attribute) or 0 if missing value not in the netcdf." 
     49         echo "" 
    4350      ;; 
    4451      d) 
     
    5057      r) 
    5158         MEMORY=${OPTARG} 
     59      ;; 
     60      x) 
     61         NXCHUNK=${OPTARG} 
     62      ;; 
     63      y) 
     64         NYCHUNK=${OPTARG} 
     65      ;; 
     66      z) 
     67         NZCHUNK=${OPTARG} 
     68      ;; 
     69      t) 
     70         NTCHUNK=${OPTARG} 
     71      ;; 
     72      c) 
     73         CHUNKSIZE=${OPTARG} 
    5274      ;; 
    5375  esac 
     
    7294nopen=$(ulimit -n) 
    7395if [[ $ndomain -gt $nopen ]] ; then 
    74   nopen=$((ndomain+2)) 
     96  nopen=$((ndomain+4))   # +2 failed !!! 
    7597fi 
    7698 
     
    90112   echo ${dims} >> $nam_rebuild 
    91113fi 
    92 if [[ -n ${NCHUNKSIZE} ]] ; then 
    93    echo " nchunksize=${NCHUNKSIZE}" >> $nam_rebuild 
     114if [[ -n ${NCSLICESIZE} ]] ; then 
     115   echo " nslicesize=${NCSLICESIZE}" >> $nam_rebuild 
    94116fi 
    95117if [[ -n ${NMASK} ]] ; then 
     
    99121   echo " deflate_level=${DEFLATE}" >> $nam_rebuild 
    100122fi 
     123if [[ -n ${NXCHUNK} ]] ; then 
     124   echo " nc4_xchunk=${NXCHUNK}" >> $nam_rebuild 
     125fi 
     126if [[ -n ${NYCHUNK} ]] ; then 
     127   echo " nc4_ychunk=${NYCHUNK}" >> $nam_rebuild 
     128fi 
     129if [[ -n ${NZCHUNK} ]] ; then 
     130   echo " nc4_zchunk=${NZCHUNK}" >> $nam_rebuild 
     131fi 
     132if [[ -n ${NTCHUNK} ]] ; then 
     133   echo " nc4_tchunk=${NTCHUNK}" >> $nam_rebuild 
     134fi 
     135if [[ -n ${CHUNKSIZE} ]] ; then 
     136   echo " fchunksize=${CHUNKSIZE}" >> $nam_rebuild 
     137fi 
     138 
     139 
    101140 
    102141echo "/" >> $nam_rebuild 
    103142 
    104143if [[ ${BATCH} == "yes" ]] ; then 
     144 
     145   template_dir=${script_dir}/BATCH_TEMPLATES/ 
     146   param_file=${template_dir}/param_${ARCH} 
     147   if [ ! -f $param_file ]; then  
     148      echo '' 
     149      echo "E R R O R: $param_file is missing, stop 42" 
     150      echo '' 
     151      echo "check your arch name or add one $param_file file in BATCH_TEMPLATES" 
     152      echo '' 
     153      exit 42 
     154   fi 
     155   . $param_file 
     156 
    105157   batch_file=rebuild_nemo_batch_${ARCH} 
     158   if [ ! -f ${template_dir}/${batch_file} ]; then  
     159      echo '' 
     160      echo "E R R O R: $batch_file is missing, stop 42" 
     161      echo '' 
     162      echo "check your arch name or add one $batch_file file in BATCH_TEMPLATES" 
     163      echo '' 
     164      exit 42 
     165   fi 
    106166 
    107167   #Create a modified local copy of the batch submission file 
    108168   #The process ID is appended to the end of the file name so it is unique 
    109    cat ${script_dir}/BATCH_TEMPLATES/${batch_file} | sed -e"s/NTHREADS/${OMP_NUM_THREADS}/" \ 
     169   cat ${template_dir}/${batch_file} | sed -e"s/NTHREADS/${OMP_NUM_THREADS}/" \ 
    110170      -e"s/MEMORY/${MEMORY}/" \ 
    111171      -e"s:INDIR:${script_dir}:" \ 
     
    114174    
    115175   #Submit the job 
     176   echo "Submitting job to compute node" 
    116177   $BATCH_CMD ${batch_file}_$$.sh 
    117178 
  • utils/tools/REBUILD_NEMO/src/rebuild_nemo.F90

    r9048 r10338  
    11PROGRAM rebuild_nemo 
    2  
     2#define key_netcdf4 
    33   !!========================================================================= 
    44   !!                        ***  rebuild_nemo  *** 
     
    1414   !!     * works for 1,2,3 and 4d arrays or types for all valid NetCDF types 
    1515   !!     * utilises OMP shared memory parallelisation where applicable 
    16    !!     * time 'chunking' for lower memory use  
     16   !!     * time 'slicing' for lower memory use  
    1717   !!       (only for 4D vars with unlimited dimension) 
    1818   !! 
    1919   !!  Ed Blockley - August 2011 
    2020   !!  (based on original code by Matt Martin) 
     21   !!  Julien Palmieri and Andrew Coward - September 2018 (add compression and chunking) 
    2122   !! 
    2223   !!------------------------------------------------------------------------- 
     
    3839   !!  and errors are written to numerr (default 0 - stderr). 
    3940   !! 
    40    !!  If time chunking is specified the code will use less memory but take a little longer. 
     41   !!  If time slicing is specified the code will use less memory but take a little longer. 
    4142   !!  It does this by breaking down the 4D input variables over their 4th dimension  
    4243   !!  (generally time) by way of a while loop. 
     
    6667   CHARACTER(LEN=nf90_max_name), ALLOCATABLE :: filenames(:), indimnames(:) 
    6768   CHARACTER(LEN=nf90_max_name), DIMENSION(2) :: dims 
    68  
    69    INTEGER :: ndomain, ifile, ndomain_file, nchunksize, deflate_level 
     69   CHARACTER(LEN=256) :: cnampath, cdimlst, cdim 
     70   CHARACTER(LEN=50)  :: clibnc ! netcdf library version 
     71 
     72   INTEGER :: ndomain, ifile, ndomain_file, nslicesize, deflate_level 
    7073   INTEGER :: ncid, outid, idim, istop 
    7174   INTEGER :: natts, attid, xtype, varid, rbdims  
    7275   INTEGER :: jv, ndims, nvars, dimlen, dimids(4) 
    7376   INTEGER :: dimid, unlimitedDimId, di, dj, dr 
    74    INTEGER :: nmax_unlimited, nt, ntchunk  
    75    INTEGER :: chunksize = 3200000 
     77   INTEGER :: nmax_unlimited, nt, ntslice  
     78   INTEGER :: fchunksize = 32000000  ! NetCDF global file chunk cache size 
     79   INTEGER :: patchchunk             ! NetCDF processor-domain file chunk cache size 
    7680   INTEGER :: nthreads = 1 
     81   INTEGER :: chunkalg = 0          ! NetCDF4 variable chunking algorithm 
     82                                    ! Default variable chunksizes (typical ORCA025 
     83                                    ! recommendations which can be adjusted via namelist 
     84                                    ! or will be bounded if too large for domain.) 
     85   INTEGER :: nc4_xchunk = 206      ! Default x (longitude) variable chunk size 
     86   INTEGER :: nc4_ychunk = 135      ! Default y (latitude)  variable chunk size 
     87   INTEGER :: nc4_zchunk = 1        ! Default z (depth) variable chunk size (almost always 1) 
     88   INTEGER :: nc4_tchunk = 1        ! Default t (time)  variable chunk size (almost always 1) 
    7789   INTEGER, ALLOCATABLE  :: outdimids(:), outdimlens(:), indimlens(:), inncids(:) 
     90   INTEGER, ALLOCATABLE  :: chunksizes(:) 
    7891   INTEGER, ALLOCATABLE  :: global_sizes(:), rebuild_dims(:) 
    7992   INTEGER, DIMENSION(2) :: halo_start, halo_end, local_sizes 
    8093   INTEGER, DIMENSION(2) :: idomain, jdomain, rdomain, start_pos 
    8194   INTEGER :: ji, jj, jk, jl, jr 
     95   INTEGER :: nargs                 ! number of arguments 
     96   INTEGER, EXTERNAL :: iargc 
    8297  
    8398   REAL(sp) :: ValMin, ValMax, InMin, InMax, rmdi 
     
    149164   REAL(dp), ALLOCATABLE, DIMENSION(:,:,:,:) :: globaldata_4d_dp 
    150165 
    151    LOGICAL :: l_valid = .false. 
     166   LOGICAL :: l_valid     = .false. 
    152167   LOGICAL :: l_noRebuild = .false. 
    153    LOGICAL :: l_findDims = .true. 
    154    LOGICAL :: l_maskout = .false. 
    155  
    156    NAMELIST/nam_rebuild/ filebase, ndomain, dims, nchunksize, l_maskout, deflate_level 
     168   LOGICAL :: l_findDims  = .true. 
     169   LOGICAL :: l_maskout   = .false. 
     170   LOGICAL :: l_namexist  = .false. 
     171 
     172   NAMELIST/nam_rebuild/ filebase, ndomain, dims, nslicesize, l_maskout, deflate_level, & 
     173                       & nc4_xchunk, nc4_ychunk, nc4_zchunk, nc4_tchunk, fchunksize          
    157174 
    158175   external      :: getarg 
    159    integer, external :: iargc 
    160    integer   :: found_num_args = 0 
    161    character(256) :: namelist_path 
    162176 
    163177   !End of definitions  
     
    174188  
    175189!-------------------------------------------------------------------------------- 
     190!1.0 Check netcdf version for warning 
     191   clibnc = TRIM(nf90_inq_libvers()) 
     192   IF (ICHAR(clibnc(1:1)) <= 3) THEN 
     193      PRINT *, '==========================================================' 
     194      PRINT *, 'You are using old netcdf library (',TRIM(clibnc),').' 
     195      PRINT *, 'REBUILD_NEMO support of old netcdf library will end soon' 
     196      PRINT *, 'please consider moving to netcdf 4 or higher' 
     197      PRINT *, '==========================================================' 
     198   END IF 
     199 
    176200!1.1 Get the namelist path 
    177 !Determine the number of arguments on the command line 
    178 found_num_args=iargc() 
    179 !Check that the required argument is present, if it is not then set it to the default value: nam_rebuild 
    180 IF (found_num_args <= 0) THEN 
    181    WRITE(numout,*) 'Namelist path not supplied as command line argument. Using default, nam_rebuild.' 
    182    namelist_path='nam_rebuild' 
    183 ELSE IF (found_num_args == 1) THEN 
    184    CALL getarg(1, namelist_path) 
    185 ELSE  
    186    WRITE(numerr,*) 'ERROR! : Incorrect number of command line arguments. Please supply only' 
    187    WRITE(numerr,*) '         the path to the namelist file, or no arguments to use default value' 
    188    STOP 1 
    189 END IF 
     201   !Determine the number of arguments on the command line 
     202   nargs=iargc() 
     203   !Check that the required argument is present, if it is not then set it to the default value: nam_rebuild 
     204   IF (nargs == 0) THEN 
     205      WRITE(numout,*) 
     206      WRITE(numout,*) 'W A R N I N G : Namelist path not supplied as command line argument. Using default, nam_rebuild.' 
     207      cnampath='nam_rebuild' 
     208   ELSE IF (nargs == 1) THEN 
     209      CALL getarg(1, cnampath) 
     210   ELSE  
     211      WRITE(numerr,*) 'E R R O R ! : Incorrect number of command line arguments. Please supply only' 
     212      WRITE(numerr,*) '         the path to the namelist file, or no arguments to use default value' 
     213      STOP 1 
     214   END IF 
     215 
     216   ! check presence of namelist 
     217   INQUIRE(FILE=cnampath, EXIST=l_namexist) 
     218   IF (.NOT. l_namexist) THEN 
     219      WRITE(numout,*) 
     220      WRITE(numout,*) 'E R R O R : Namelist '//TRIM(cnampath)//' not present.' 
     221      STOP 42 
     222   END IF 
    190223 
    191224!1.2 Read in the namelist  
    192225 
    193226   dims(:) = "" 
    194    nchunksize = 0 
     227   nslicesize = 0 
    195228   deflate_level = 0 
    196    OPEN( UNIT=numnam, FILE=TRIM(namelist_path), FORM='FORMATTED', STATUS='OLD' ) 
     229   OPEN( UNIT=numnam, FILE=TRIM(cnampath), FORM='FORMATTED', STATUS='OLD' ) 
    197230   READ( numnam, nam_rebuild ) 
    198231   CLOSE( numnam ) 
    199232   IF( .NOT. ALL(dims(:) == "") ) l_findDims = .false. 
    200   
    201 !1.1 Set up the filenames and fileids 
     233 
     234!1.3 Set up the filenames and fileids 
    202235 
    203236   ALLOCATE(filenames(ndomain)) 
     
    227260   
    228261!2.1 Set up the output file 
    229 !#if defined key_netcdf4 
    230    CALL check_nf90( nf90_create( TRIM(filebase)//'.nc', nf90_netcdf4, outid, chunksize=chunksize ) ) 
    231 !#else 
    232 !   CALL check_nf90( nf90_create( TRIM(filebase)//'.nc', nf90_64bit_offset, outid, chunksize=chunksize ) ) 
    233 !#endif 
     262#if defined key_netcdf4 
     263   CALL check_nf90( nf90_create( TRIM(filebase)//'.nc', nf90_netcdf4, outid, chunksize=fchunksize ) ) 
     264#else 
     265   CALL check_nf90( nf90_create( TRIM(filebase)//'.nc', nf90_64bit_offset, outid, chunksize=fchunksize ) ) 
     266#endif 
    234267 
    235268!2.2 Set up dimensions in output file 
     
    291324      outdimlens(idim) = dimlen 
    292325   END DO 
    293    ! nmax_unlimited is only used for time-chunking so we set it to be at least 1 to  
     326   ! nmax_unlimited is only used for time-slicing so we set it to be at least 1 to  
    294327   ! account for files with no record dimension or zero length record dimension(!) 
    295328   nmax_unlimited = max(nmax_unlimited,1) 
     
    340373      CALL check_nf90( nf90_inquire_variable( ncid, jv, varname, xtype, ndims, dimids, natts ) ) 
    341374      ALLOCATE(outdimids(ndims)) 
    342       DO idim = 1, ndims 
    343          outdimids(idim) = dimids(idim) 
    344       END DO 
     375      ALLOCATE(chunksizes(ndims)) 
     376      IF( ndims > 0 ) then 
     377        DO idim = 1, ndims 
     378           outdimids(idim) = dimids(idim) 
     379           chunksizes(idim) = outdimlens(dimids(idim)) 
     380           cdim='|'//TRIM(indimnames(dimids(idim)))//'|' 
     381 
     382! trick to find var in a list of suggestion (var0 and var1 : INDEX(|var0|var1|,|var|) 
     383           cdimlst='|x|x_grid_T|x_grid_U|x_grid_V|x_grid_W|' 
     384           if( INDEX(TRIM(cdimlst),TRIM(cdim)) > 0 ) & 
     385    &                             chunksizes(idim) = min(outdimlens(dimids(idim)), max(nc4_xchunk,1)) 
     386 
     387           cdimlst='|y|y_grid_T|y_grid_U|y_grid_V|y_grid_W|' 
     388           if( INDEX(TRIM(cdimlst),TRIM(cdim)) > 0 ) & 
     389    &                             chunksizes(idim) = min(outdimlens(dimids(idim)), max(nc4_ychunk,1)) 
     390 
     391           cdimlst='|z|deptht|depthu|depthv|depthw|depth|nav_lev|' 
     392           if( INDEX(TRIM(cdimlst),TRIM(cdim)) > 0 ) & 
     393    &                             chunksizes(idim) = min(outdimlens(dimids(idim)), max(nc4_zchunk,1)) 
     394 
     395           cdimlst='|t|time|time_counter|' 
     396           if( INDEX(TRIM(cdimlst),TRIM(cdim)) > 0 ) & 
     397    &                             chunksizes(idim) = min(outdimlens(dimids(idim)), max(nc4_tchunk,1)) 
     398 
     399        END DO 
    345400#if defined key_netcdf4 
    346       CALL check_nf90( nf90_def_var( outid, varname, xtype, outdimids, varid, & 
    347                                      deflate_level=deflate_level ) ) 
     401        CALL check_nf90( nf90_def_var( outid, varname, xtype, outdimids, varid, & 
     402                                       deflate_level=deflate_level ) ) 
     403        IF (l_verbose) WRITE(numout,*) 'Dims    : ',ndims, outdimids(1:ndims) 
     404        IF (l_verbose) WRITE(numout,*) 'names   : ',(TRIM(indimnames(dimids(idim)))//' ',idim=1,ndims) 
     405        IF (l_verbose) WRITE(numout,*) 'lens    : ',(outdimlens(dimids(idim)),idim=1,ndims) 
     406        IF (l_verbose) WRITE(numout,*) 'Chunking: ',chunksizes 
     407        IF (l_verbose) WRITE(numout,*) 'Deflation : ',deflate_level 
     408        IF (l_verbose) WRITE(numout,*) 'Chunk algo: ',chunkalg 
     409        CALL check_nf90( nf90_def_var_chunking( outid, varid, chunkalg, & 
     410   &                                 chunksizes ) ) 
     411      ELSE 
     412        CALL check_nf90( nf90_def_var( outid, varname, xtype, outdimids, varid ) ) 
    348413#else 
    349414      CALL check_nf90( nf90_def_var( outid, varname, xtype, outdimids, varid ) ) 
    350415#endif 
     416      ENDIF 
    351417      DEALLOCATE(outdimids) 
     418      DEALLOCATE(chunksizes) 
    352419      IF (l_verbose) WRITE(numout,*) 'Defining variable '//TRIM(varname)//'...'  
    353420      IF( natts > 0 ) THEN 
     
    375442 
    376443   IF (l_verbose) WRITE(numout,*) 'Opening input files...' 
     444 
     445   ! Set a file chunk cache size for the processor-domain files that scales with the number of processors 
     446   patchchunk = max(8192, fchunksize/ndomain) 
     447 
     448   ! open files  
    377449   DO ifile = 2, ndomain 
    378       CALL check_nf90( nf90_open( TRIM(filenames(ifile)), nf90_share, ncid, chunksize=chunksize ) ) 
     450      CALL check_nf90( nf90_open( TRIM(filenames(ifile)), nf90_share, ncid, chunksize=patchchunk ) ) 
    379451      inncids(ifile) = ncid 
    380452   END DO 
     
    388460      istop = nf90_noerr 
    389461      nt = 1 
    390       ntchunk = nmax_unlimited 
    391       IF( nchunksize == 0 ) nchunksize = nmax_unlimited 
     462      ntslice = nmax_unlimited 
     463      IF( nslicesize == 0 ) nslicesize = nmax_unlimited 
    392464 
    393465!3.2 Inquire variable to find out name and how many dimensions it has 
     
    403475      ENDIF 
    404476 
    405 !3.2.0 start while loop for time chunking 
     477!3.2.0 start while loop for time slicing 
    406478 
    407479      DO WHILE( nt <= nmax_unlimited ) 
    408480 
    409481         IF( ndims > 3 ) THEN 
    410             ntchunk = MIN( nchunksize, nmax_unlimited + 1 - nt ) 
     482            ntslice = MIN( nslicesize, nmax_unlimited + 1 - nt ) 
    411483         ENDIF 
    412484 
    413485      IF (l_noRebuild) THEN 
    414486 
    415          IF( nchunksize == nmax_unlimited .OR. ndims <= 3 ) THEN 
     487         IF( nslicesize == nmax_unlimited .OR. ndims <= 3 ) THEN 
    416488            IF (l_verbose) WRITE(numout,*) 'Copying data from variable '//TRIM(varname)//'...' 
    417489         ELSE 
    418490            IF (l_verbose) WRITE(numout,'(A,I3,A,I3,A)') ' Copying data from variable '  & 
    419             &                 //TRIM(varname)//' for chunks ',nt,' to ',nt+ntchunk-1,' ...' 
     491            &                 //TRIM(varname)//' for slices ',nt,' to ',nt+ntslice-1,' ...' 
    420492         ENDIF 
    421493 
     
    519591               CASE( NF90_BYTE ) 
    520592                  ALLOCATE(globaldata_4d_i1(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    521                      &                      indimlens(dimids(3)),ntchunk)) 
     593                     &                      indimlens(dimids(3)),ntslice)) 
    522594                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i1, start=(/1,1,1,nt/) ) ) 
    523595               CASE( NF90_SHORT ) 
    524596                  ALLOCATE(globaldata_4d_i2(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    525                      &                      indimlens(dimids(3)),ntchunk)) 
     597                     &                      indimlens(dimids(3)),ntslice)) 
    526598                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i2, start=(/1,1,1,nt/) ) ) 
    527599               CASE( NF90_INT ) 
    528600                  ALLOCATE(globaldata_4d_i4(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    529                      &                      indimlens(dimids(3)),ntchunk)) 
     601                     &                      indimlens(dimids(3)),ntslice)) 
    530602                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i4, start=(/1,1,1,nt/) ) ) 
    531603               CASE( NF90_FLOAT ) 
    532604                  ALLOCATE(globaldata_4d_sp(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    533                      &                      indimlens(dimids(3)),ntchunk)) 
     605                     &                      indimlens(dimids(3)),ntslice)) 
    534606                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_sp, start=(/1,1,1,nt/) ) ) 
    535607               CASE( NF90_DOUBLE ) 
    536608                  ALLOCATE(globaldata_4d_dp(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    537                      &                      indimlens(dimids(3)),ntchunk)) 
     609                     &                      indimlens(dimids(3)),ntslice)) 
    538610                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_dp, start=(/1,1,1,nt/) ) ) 
    539611               CASE DEFAULT 
     
    548620!3.2.2 For variables that require rebuilding we need to read in from all ndomain files 
    549621!      Here we allocate global variables ahead of looping over files 
    550          IF( nchunksize == nmax_unlimited .OR. ndims <= 3 ) THEN 
     622         IF( nslicesize == nmax_unlimited .OR. ndims <= 3 ) THEN 
    551623            IF (l_verbose) WRITE(numout,*) 'Rebuilding data from variable '//TRIM(varname)//'...' 
    552624         ELSE 
    553625            IF (l_verbose) WRITE(numout,'(A,I3,A,I3,A)') ' Rebuilding data from variable '  & 
    554             &                 //TRIM(varname)//' for chunks ',nt,' to ',nt+ntchunk-1,' ...' 
     626            &                 //TRIM(varname)//' for slices ',nt,' to ',nt+ntslice-1,' ...' 
    555627         ENDIF 
    556628         IF( ndims == 1 ) THEN 
     
    633705               CASE( NF90_BYTE ) 
    634706                  ALLOCATE(globaldata_4d_i1(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    635                      &                      outdimlens(dimids(3)),ntchunk)) 
     707                     &                      outdimlens(dimids(3)),ntslice)) 
    636708                  IF (l_maskout) globaldata_4d_i1(:,:,:,:)=mdiVals(jv) 
    637709               CASE( NF90_SHORT ) 
    638710                  ALLOCATE(globaldata_4d_i2(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    639                      &                      outdimlens(dimids(3)),ntchunk)) 
     711                     &                      outdimlens(dimids(3)),ntslice)) 
    640712                  IF (l_maskout) globaldata_4d_i2(:,:,:,:)=mdiVals(jv) 
    641713               CASE( NF90_INT ) 
    642714                  ALLOCATE(globaldata_4d_i4(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    643                      &                      outdimlens(dimids(3)),ntchunk)) 
     715                     &                      outdimlens(dimids(3)),ntslice)) 
    644716                  IF (l_maskout) globaldata_4d_i4(:,:,:,:)=mdiVals(jv) 
    645717               CASE( NF90_FLOAT ) 
    646718                  ALLOCATE(globaldata_4d_sp(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    647                      &                      outdimlens(dimids(3)),ntchunk)) 
     719                     &                      outdimlens(dimids(3)),ntslice)) 
    648720                  IF (l_maskout) globaldata_4d_sp(:,:,:,:)=mdiVals(jv) 
    649721               CASE( NF90_DOUBLE ) 
    650722                  ALLOCATE(globaldata_4d_dp(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    651                      &                      outdimlens(dimids(3)),ntchunk)) 
     723                     &                      outdimlens(dimids(3)),ntslice)) 
    652724                  IF (l_maskout) globaldata_4d_dp(:,:,:,:)=mdiVals(jv) 
    653725               CASE DEFAULT 
     
    670742!$OMP&         localdata_1d_i1,localdata_2d_i1,localdata_3d_i1,localdata_4d_i1)           & 
    671743!$OMP& SHARED(jv,nvars,varname,filenames,ValMin,ValMax,indimlens,outdimlens,rbdims,       & 
    672 !$OMP&        ndomain,outid,chunksize,istop,l_valid,nthreads,inncids,rebuild_dims,        & 
     744!$OMP&        ndomain,outid,fchunksize,istop,l_valid,nthreads,inncids,rebuild_dims,       & 
    673745!$OMP&        globaldata_1d_i2,globaldata_1d_i4,globaldata_1d_sp,globaldata_1d_dp,        & 
    674746!$OMP&        globaldata_2d_i2,globaldata_2d_i4,globaldata_2d_sp,globaldata_2d_dp,        & 
     
    676748!$OMP&        globaldata_4d_i2,globaldata_4d_i4,globaldata_4d_sp,globaldata_4d_dp,        & 
    677749!$OMP&        globaldata_1d_i1,globaldata_2d_i1,globaldata_3d_i1,globaldata_4d_i1,        & 
    678 !$OMP&        ntchunk,nt,nmax_unlimited,indimnames,dims) 
     750!$OMP&        ntslice,nt,nmax_unlimited,indimnames,dims,patchchunk) 
    679751 
    680752         DO ifile = 1, ndomain 
     
    9321004                  CASE( NF90_BYTE ) 
    9331005                     ALLOCATE(localdata_4d_i1(local_sizes(di),local_sizes(dj),               & 
    934                          &                     indimlens(dimids(3)),ntchunk)) 
     1006                         &                     indimlens(dimids(3)),ntslice)) 
    9351007                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i1, start=(/1,1,1,nt/) ), istop ) 
    9361008!$OMP  PARALLEL DEFAULT(NONE) PRIVATE(ji,jj,jk,jl)   & 
    937 !$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i1,localdata_4d_i1,di,dj,nt,ntchunk) 
    938                      DO jl = 1, ntchunk 
     1009!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i1,localdata_4d_i1,di,dj,nt,ntslice) 
     1010                     DO jl = 1, ntslice 
    9391011!$OMP DO  
    9401012                        DO jk = 1, indimlens(dimids(3)) 
     
    9511023                  CASE( NF90_SHORT ) 
    9521024                     ALLOCATE(localdata_4d_i2(local_sizes(di),local_sizes(dj),               & 
    953                         &                     indimlens(dimids(3)),ntchunk)) 
     1025                        &                     indimlens(dimids(3)),ntslice)) 
    9541026                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i2, start=(/1,1,1,nt/) ), istop ) 
    9551027!$OMP  PARALLEL DEFAULT(NONE) PRIVATE(ji,jj,jk,jl)   & 
    956 !$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i2,localdata_4d_i2,di,dj,nt,ntchunk) 
    957                      DO jl = 1, ntchunk 
     1028!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i2,localdata_4d_i2,di,dj,nt,ntslice) 
     1029                     DO jl = 1, ntslice 
    9581030!$OMP DO  
    9591031                        DO jk = 1, indimlens(dimids(3)) 
     
    9701042                  CASE( NF90_INT ) 
    9711043                     ALLOCATE(localdata_4d_i4(local_sizes(di),local_sizes(dj),               & 
    972                         &                     indimlens(dimids(3)),ntchunk)) 
     1044                        &                     indimlens(dimids(3)),ntslice)) 
    9731045                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i4, start=(/1,1,1,nt/) ), istop ) 
    9741046!$OMP  PARALLEL DEFAULT(NONE) PRIVATE(ji,jj,jk,jl)   & 
    975 !$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i4,localdata_4d_i4,di,dj,nt,ntchunk) 
    976                      DO jl = 1, ntchunk 
     1047!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i4,localdata_4d_i4,di,dj,nt,ntslice) 
     1048                     DO jl = 1, ntslice 
    9771049!$OMP DO 
    9781050                        DO jk = 1, indimlens(dimids(3)) 
     
    9891061                  CASE( NF90_FLOAT ) 
    9901062                     ALLOCATE(localdata_4d_sp(local_sizes(di),local_sizes(dj),               & 
    991                         &                     indimlens(dimids(3)),ntchunk)) 
     1063                        &                     indimlens(dimids(3)),ntslice)) 
    9921064                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_sp, start=(/1,1,1,nt/) ), istop ) 
    9931065!$OMP  PARALLEL DEFAULT(NONE) PRIVATE(ji,jj,jk,jl)   & 
    994 !$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_sp,localdata_4d_sp,di,dj,nt,ntchunk)  
    995                      DO jl = 1, ntchunk 
     1066!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_sp,localdata_4d_sp,di,dj,nt,ntslice)  
     1067                     DO jl = 1, ntslice 
    9961068!$OMP DO 
    9971069                        DO jk = 1, indimlens(dimids(3)) 
     
    10081080                  CASE( NF90_DOUBLE ) 
    10091081                     ALLOCATE(localdata_4d_dp(local_sizes(di),local_sizes(dj),               & 
    1010                         &                     indimlens(dimids(3)),ntchunk)) 
     1082                        &                     indimlens(dimids(3)),ntslice)) 
    10111083                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_dp, start=(/1,1,1,nt/) ), istop ) 
    10121084!$OMP  PARALLEL DEFAULT(NONE) PRIVATE(ji,jj,jk,jl)   & 
    1013 !$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_dp,localdata_4d_dp,di,dj,nt,ntchunk)  
    1014                      DO jl = 1, ntchunk 
     1085!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_dp,localdata_4d_dp,di,dj,nt,ntslice)  
     1086                     DO jl = 1, ntslice 
    10151087!$OMP DO 
    10161088                        DO jk = 1, indimlens(dimids(3)) 
     
    10991171            CASE( NF90_DOUBLE ) 
    11001172               CALL check_nf90( nf90_put_var( outid, jv, globaldata_0d_dp ) ) 
     1173            CASE DEFAULT    
     1174               WRITE(numerr,*) '0d Unknown nf90 type: ', xtype 
     1175               STOP 4 
    11011176         END SELECT 
    11021177 
     
    11191194               CALL check_nf90( nf90_put_var( outid, jv, globaldata_1d_dp ) ) 
    11201195               DEALLOCATE(globaldata_1d_dp) 
     1196            CASE DEFAULT    
     1197               WRITE(numerr,*) '1d Unknown nf90 type: ', xtype 
     1198               STOP 4 
    11211199         END SELECT 
    11221200 
     
    11401218               DEALLOCATE(globaldata_2d_dp) 
    11411219            CASE DEFAULT    
    1142                WRITE(numerr,*) 'Unknown nf90 type: ', xtype 
     1220               WRITE(numerr,*) '2d Unknown nf90 type: ', xtype 
    11431221               STOP 4 
    11441222         END SELECT      
     
    11631241               DEALLOCATE(globaldata_3d_dp) 
    11641242            CASE DEFAULT    
    1165                WRITE(numerr,*) 'Unknown nf90 type: ', xtype 
     1243               WRITE(numerr,*) '3d Unknown nf90 type: ', xtype 
    11661244               STOP 4 
    11671245         END SELECT      
     
    11861264               DEALLOCATE(globaldata_4d_dp) 
    11871265            CASE DEFAULT    
    1188                WRITE(numerr,*) 'Unknown nf90 type: ', xtype 
     1266               WRITE(numerr,*) '4d Unknown nf90 type: ', xtype 
    11891267               STOP 4 
    11901268         END SELECT      
     1269         ! why only for big data set, test the cost. 
     1270         CALL check_nf90( nf90_sync( outid ) )    ! flush buffers to disk after writing big 4D datasets 
    11911271     
    11921272      ENDIF 
    11931273 
    1194          nt = nt + ntchunk 
     1274         nt = nt + ntslice 
    11951275 
    11961276      END DO ! WHILE loop 
     
    12371317            WRITE(numerr,*) "*** NEMO rebuild failed ***" 
    12381318            WRITE(numerr,*) 
    1239             STOP 4 
     1319            STOP 5 
    12401320         ENDIF 
    12411321      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.