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 10131 – NEMO

Changeset 10131


Ignore:
Timestamp:
2018-09-14T15:58:40+02:00 (6 years ago)
Author:
mathiot
Message:

add option to manage compression in rebuild_nemo, add compression and chunking in rebuild_nemo.F90

Location:
NEMO/branches/UKMO/dev_rebuild_nemo_compression/REBUILD_NEMO
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/dev_rebuild_nemo_compression/REBUILD_NEMO/rebuild_nemo

    r9048 r10131  
    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 -s] filebase ndomain [rebuild dimensions]" 
    1313   echo 
    1414   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" 
     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 chunsize along x "  
     24   echo "            -y chunsize along y "  
     25   echo "            -z chunsize along z "  
     26   echo "            -t chunsize along t "  
     27   echo "            -s chunsize " 
    2128   echo 
    2229   exit 1 
    2330} 
    2431 
    25 while getopts c:n:t:d:r:lm opt 
     32while getopts l:p:s:m:n:r:d:x:y:z:t:s opt 
    2633do 
    2734  case ${opt} in 
     
    3239         echo "Submitting job to compute node" 
    3340      ;; 
    34       t) 
     41      p) 
    3542         OMP_NUM_THREADS=${OPTARG} 
    3643      ;; 
    37       c) 
    38          NCHUNKSIZE=${OPTARG} 
     44      s) 
     45         NSLICESIZE=${OPTARG} 
    3946      ;; 
    4047      m)  
     
    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      s) 
     73         CHUNKSIZE=${OPTARG} 
    5274      ;; 
    5375  esac 
     
    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 
  • NEMO/branches/UKMO/dev_rebuild_nemo_compression/REBUILD_NEMO/src/rebuild_nemo.F90

    r9048 r10131  
    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 
     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 
     
    154169   LOGICAL :: l_maskout = .false. 
    155170 
    156    NAMELIST/nam_rebuild/ filebase, ndomain, dims, nchunksize, l_maskout, deflate_level 
     171   NAMELIST/nam_rebuild/ filebase, ndomain, dims, nslicesize, l_maskout, deflate_level, & 
     172                       & nc4_xchunk, nc4_ychunk, nc4_zchunk, nc4_tchunk, fchunksize          
    157173 
    158174   external      :: getarg 
    159    integer, external :: iargc 
    160    integer   :: found_num_args = 0 
    161    character(256) :: namelist_path 
    162175 
    163176   !End of definitions  
     
    174187  
    175188!-------------------------------------------------------------------------------- 
     189!1.0 Check netcdf version for warning 
     190   clibnc = TRIM(nf90_inq_libvers()) 
     191   IF (ICHAR(clibnc(1:1)) <= 3) THEN 
     192      PRINT *, '==========================================================' 
     193      PRINT *, 'You are using old netcdf library (',TRIM(clibnc),').' 
     194      PRINT *, 'REBUILD_NEMO support of old netcdf library will end soon' 
     195      PRINT *, 'please consider moving to netcdf 4 or higher' 
     196      PRINT *, '==========================================================' 
     197   END IF 
     198 
    176199!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 
     200   !Determine the number of arguments on the command line 
     201   nargs=iargc() 
     202   !Check that the required argument is present, if it is not then set it to the default value: nam_rebuild 
     203   IF (nargs == 0) THEN 
     204      WRITE(numout,*) 'Namelist path not supplied as command line argument. Using default, nam_rebuild.' 
     205      cnampath='nam_rebuild' 
     206   ELSE IF (nargs == 1) THEN 
     207      CALL getarg(1, cnampath) 
     208   ELSE  
     209      WRITE(numerr,*) 'ERROR! : Incorrect number of command line arguments. Please supply only' 
     210      WRITE(numerr,*) '         the path to the namelist file, or no arguments to use default value' 
     211      STOP 1 
     212   END IF 
    190213 
    191214!1.2 Read in the namelist  
    192215 
    193216   dims(:) = "" 
    194    nchunksize = 0 
     217   nslicesize = 0 
    195218   deflate_level = 0 
    196    OPEN( UNIT=numnam, FILE=TRIM(namelist_path), FORM='FORMATTED', STATUS='OLD' ) 
     219   OPEN( UNIT=numnam, FILE=TRIM(cnampath), FORM='FORMATTED', STATUS='OLD' ) 
    197220   READ( numnam, nam_rebuild ) 
    198221   CLOSE( numnam ) 
    199222   IF( .NOT. ALL(dims(:) == "") ) l_findDims = .false. 
    200   
    201 !1.1 Set up the filenames and fileids 
     223 
     224!1.3 Set up the filenames and fileids 
    202225 
    203226   ALLOCATE(filenames(ndomain)) 
     
    227250   
    228251!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 
     252#if defined key_netcdf4 
     253   CALL check_nf90( nf90_create( TRIM(filebase)//'.nc', nf90_netcdf4, outid, chunksize=fchunksize ) ) 
     254#else 
     255   CALL check_nf90( nf90_create( TRIM(filebase)//'.nc', nf90_64bit_offset, outid, chunksize=fchunksize ) ) 
     256#endif 
    234257 
    235258!2.2 Set up dimensions in output file 
     
    291314      outdimlens(idim) = dimlen 
    292315   END DO 
    293    ! nmax_unlimited is only used for time-chunking so we set it to be at least 1 to  
     316   ! nmax_unlimited is only used for time-slicing so we set it to be at least 1 to  
    294317   ! account for files with no record dimension or zero length record dimension(!) 
    295318   nmax_unlimited = max(nmax_unlimited,1) 
     
    340363      CALL check_nf90( nf90_inquire_variable( ncid, jv, varname, xtype, ndims, dimids, natts ) ) 
    341364      ALLOCATE(outdimids(ndims)) 
    342       DO idim = 1, ndims 
    343          outdimids(idim) = dimids(idim) 
    344       END DO 
     365      ALLOCATE(chunksizes(ndims)) 
     366      IF( ndims > 0 ) then 
     367        DO idim = 1, ndims 
     368           outdimids(idim) = dimids(idim) 
     369           chunksizes(idim) = outdimlens(dimids(idim)) 
     370           if( TRIM(indimnames(dimids(idim))) == 'x' )             & 
     371    &                             chunksizes(idim) = min(outdimlens(dimids(idim)), max(nc4_xchunk,1)) 
     372           if( TRIM(indimnames(dimids(idim))) == 'y' )             & 
     373    &                             chunksizes(idim) = min(outdimlens(dimids(idim)), max(nc4_ychunk,1)) 
     374! trick to find var in a list of suggestion (var0 and var1 : INDEX(|var0|var1|,|var|) 
     375           if( INDEX('|depth|z|nav_lev|','|'//TRIM(indimnames(dimids(idim)))//'|') > 0 ) & 
     376    &                             chunksizes(idim) = min(outdimlens(dimids(idim)), max(nc4_zchunk,1)) 
     377           if( INDEX('|time|time_counter|','|'//TRIM(indimnames(dimids(idim)))//'|') > 0 ) & 
     378    &                             chunksizes(idim) = min(outdimlens(dimids(idim)), max(nc4_tchunk,1)) 
     379        END DO 
    345380#if defined key_netcdf4 
    346       CALL check_nf90( nf90_def_var( outid, varname, xtype, outdimids, varid, & 
    347                                      deflate_level=deflate_level ) ) 
     381        CALL check_nf90( nf90_def_var( outid, varname, xtype, outdimids, varid, & 
     382                                       deflate_level=deflate_level ) ) 
     383        IF (l_verbose) WRITE(numout,*) 'Dims    : ',ndims, outdimids(1:ndims) 
     384        IF (l_verbose) WRITE(numout,*) 'names   : ',(TRIM(indimnames(dimids(idim)))//' ',idim=1,ndims) 
     385        IF (l_verbose) WRITE(numout,*) 'lens   : ',(outdimlens(dimids(idim)),idim=1,ndims) 
     386        IF (l_verbose) WRITE(numout,*) 'Chunking: ',chunkalg, chunksizes 
     387        CALL check_nf90( nf90_def_var_chunking( outid, varid, chunkalg, & 
     388   &                                 chunksizes ) ) 
     389      ELSE 
     390        CALL check_nf90( nf90_def_var( outid, varname, xtype, outdimids, varid ) ) 
    348391#else 
    349392      CALL check_nf90( nf90_def_var( outid, varname, xtype, outdimids, varid ) ) 
    350393#endif 
     394      ENDIF 
    351395      DEALLOCATE(outdimids) 
     396      DEALLOCATE(chunksizes) 
    352397      IF (l_verbose) WRITE(numout,*) 'Defining variable '//TRIM(varname)//'...'  
    353398      IF( natts > 0 ) THEN 
     
    375420 
    376421   IF (l_verbose) WRITE(numout,*) 'Opening input files...' 
     422 
     423   ! Set a file chunk cache size for the processor-domain files that scales with the number of processors 
     424   patchchunk = max(8192, fchunksize/ndomain) 
     425 
     426   ! open files  
    377427   DO ifile = 2, ndomain 
    378       CALL check_nf90( nf90_open( TRIM(filenames(ifile)), nf90_share, ncid, chunksize=chunksize ) ) 
     428      CALL check_nf90( nf90_open( TRIM(filenames(ifile)), nf90_share, ncid, chunksize=patchchunk ) ) 
    379429      inncids(ifile) = ncid 
    380430   END DO 
     
    388438      istop = nf90_noerr 
    389439      nt = 1 
    390       ntchunk = nmax_unlimited 
    391       IF( nchunksize == 0 ) nchunksize = nmax_unlimited 
     440      ntslice = nmax_unlimited 
     441      IF( nslicesize == 0 ) nslicesize = nmax_unlimited 
    392442 
    393443!3.2 Inquire variable to find out name and how many dimensions it has 
     
    403453      ENDIF 
    404454 
    405 !3.2.0 start while loop for time chunking 
     455!3.2.0 start while loop for time slicing 
    406456 
    407457      DO WHILE( nt <= nmax_unlimited ) 
    408458 
    409459         IF( ndims > 3 ) THEN 
    410             ntchunk = MIN( nchunksize, nmax_unlimited + 1 - nt ) 
     460            ntslice = MIN( nslicesize, nmax_unlimited + 1 - nt ) 
    411461         ENDIF 
    412462 
    413463      IF (l_noRebuild) THEN 
    414464 
    415          IF( nchunksize == nmax_unlimited .OR. ndims <= 3 ) THEN 
     465         IF( nslicesize == nmax_unlimited .OR. ndims <= 3 ) THEN 
    416466            IF (l_verbose) WRITE(numout,*) 'Copying data from variable '//TRIM(varname)//'...' 
    417467         ELSE 
    418468            IF (l_verbose) WRITE(numout,'(A,I3,A,I3,A)') ' Copying data from variable '  & 
    419             &                 //TRIM(varname)//' for chunks ',nt,' to ',nt+ntchunk-1,' ...' 
     469            &                 //TRIM(varname)//' for slices ',nt,' to ',nt+ntslice-1,' ...' 
    420470         ENDIF 
    421471 
     
    519569               CASE( NF90_BYTE ) 
    520570                  ALLOCATE(globaldata_4d_i1(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    521                      &                      indimlens(dimids(3)),ntchunk)) 
     571                     &                      indimlens(dimids(3)),ntslice)) 
    522572                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i1, start=(/1,1,1,nt/) ) ) 
    523573               CASE( NF90_SHORT ) 
    524574                  ALLOCATE(globaldata_4d_i2(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    525                      &                      indimlens(dimids(3)),ntchunk)) 
     575                     &                      indimlens(dimids(3)),ntslice)) 
    526576                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i2, start=(/1,1,1,nt/) ) ) 
    527577               CASE( NF90_INT ) 
    528578                  ALLOCATE(globaldata_4d_i4(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    529                      &                      indimlens(dimids(3)),ntchunk)) 
     579                     &                      indimlens(dimids(3)),ntslice)) 
    530580                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_i4, start=(/1,1,1,nt/) ) ) 
    531581               CASE( NF90_FLOAT ) 
    532582                  ALLOCATE(globaldata_4d_sp(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    533                      &                      indimlens(dimids(3)),ntchunk)) 
     583                     &                      indimlens(dimids(3)),ntslice)) 
    534584                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_sp, start=(/1,1,1,nt/) ) ) 
    535585               CASE( NF90_DOUBLE ) 
    536586                  ALLOCATE(globaldata_4d_dp(indimlens(dimids(1)),indimlens(dimids(2)),       & 
    537                      &                      indimlens(dimids(3)),ntchunk)) 
     587                     &                      indimlens(dimids(3)),ntslice)) 
    538588                  CALL check_nf90( nf90_get_var( ncid, jv, globaldata_4d_dp, start=(/1,1,1,nt/) ) ) 
    539589               CASE DEFAULT 
     
    548598!3.2.2 For variables that require rebuilding we need to read in from all ndomain files 
    549599!      Here we allocate global variables ahead of looping over files 
    550          IF( nchunksize == nmax_unlimited .OR. ndims <= 3 ) THEN 
     600         IF( nslicesize == nmax_unlimited .OR. ndims <= 3 ) THEN 
    551601            IF (l_verbose) WRITE(numout,*) 'Rebuilding data from variable '//TRIM(varname)//'...' 
    552602         ELSE 
    553603            IF (l_verbose) WRITE(numout,'(A,I3,A,I3,A)') ' Rebuilding data from variable '  & 
    554             &                 //TRIM(varname)//' for chunks ',nt,' to ',nt+ntchunk-1,' ...' 
     604            &                 //TRIM(varname)//' for slices ',nt,' to ',nt+ntslice-1,' ...' 
    555605         ENDIF 
    556606         IF( ndims == 1 ) THEN 
     
    633683               CASE( NF90_BYTE ) 
    634684                  ALLOCATE(globaldata_4d_i1(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    635                      &                      outdimlens(dimids(3)),ntchunk)) 
     685                     &                      outdimlens(dimids(3)),ntslice)) 
    636686                  IF (l_maskout) globaldata_4d_i1(:,:,:,:)=mdiVals(jv) 
    637687               CASE( NF90_SHORT ) 
    638688                  ALLOCATE(globaldata_4d_i2(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    639                      &                      outdimlens(dimids(3)),ntchunk)) 
     689                     &                      outdimlens(dimids(3)),ntslice)) 
    640690                  IF (l_maskout) globaldata_4d_i2(:,:,:,:)=mdiVals(jv) 
    641691               CASE( NF90_INT ) 
    642692                  ALLOCATE(globaldata_4d_i4(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    643                      &                      outdimlens(dimids(3)),ntchunk)) 
     693                     &                      outdimlens(dimids(3)),ntslice)) 
    644694                  IF (l_maskout) globaldata_4d_i4(:,:,:,:)=mdiVals(jv) 
    645695               CASE( NF90_FLOAT ) 
    646696                  ALLOCATE(globaldata_4d_sp(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    647                      &                      outdimlens(dimids(3)),ntchunk)) 
     697                     &                      outdimlens(dimids(3)),ntslice)) 
    648698                  IF (l_maskout) globaldata_4d_sp(:,:,:,:)=mdiVals(jv) 
    649699               CASE( NF90_DOUBLE ) 
    650700                  ALLOCATE(globaldata_4d_dp(outdimlens(dimids(1)),outdimlens(dimids(2)),     & 
    651                      &                      outdimlens(dimids(3)),ntchunk)) 
     701                     &                      outdimlens(dimids(3)),ntslice)) 
    652702                  IF (l_maskout) globaldata_4d_dp(:,:,:,:)=mdiVals(jv) 
    653703               CASE DEFAULT 
     
    670720!$OMP&         localdata_1d_i1,localdata_2d_i1,localdata_3d_i1,localdata_4d_i1)           & 
    671721!$OMP& SHARED(jv,nvars,varname,filenames,ValMin,ValMax,indimlens,outdimlens,rbdims,       & 
    672 !$OMP&        ndomain,outid,chunksize,istop,l_valid,nthreads,inncids,rebuild_dims,        & 
     722!$OMP&        ndomain,outid,fchunksize,istop,l_valid,nthreads,inncids,rebuild_dims,       & 
    673723!$OMP&        globaldata_1d_i2,globaldata_1d_i4,globaldata_1d_sp,globaldata_1d_dp,        & 
    674724!$OMP&        globaldata_2d_i2,globaldata_2d_i4,globaldata_2d_sp,globaldata_2d_dp,        & 
     
    676726!$OMP&        globaldata_4d_i2,globaldata_4d_i4,globaldata_4d_sp,globaldata_4d_dp,        & 
    677727!$OMP&        globaldata_1d_i1,globaldata_2d_i1,globaldata_3d_i1,globaldata_4d_i1,        & 
    678 !$OMP&        ntchunk,nt,nmax_unlimited,indimnames,dims) 
     728!$OMP&        ntslice,nt,nmax_unlimited,indimnames,dims,patchchunk) 
    679729 
    680730         DO ifile = 1, ndomain 
     
    932982                  CASE( NF90_BYTE ) 
    933983                     ALLOCATE(localdata_4d_i1(local_sizes(di),local_sizes(dj),               & 
    934                          &                     indimlens(dimids(3)),ntchunk)) 
     984                         &                     indimlens(dimids(3)),ntslice)) 
    935985                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i1, start=(/1,1,1,nt/) ), istop ) 
    936986!$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 
     987!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i1,localdata_4d_i1,di,dj,nt,ntslice) 
     988                     DO jl = 1, ntslice 
    939989!$OMP DO  
    940990                        DO jk = 1, indimlens(dimids(3)) 
     
    9511001                  CASE( NF90_SHORT ) 
    9521002                     ALLOCATE(localdata_4d_i2(local_sizes(di),local_sizes(dj),               & 
    953                         &                     indimlens(dimids(3)),ntchunk)) 
     1003                        &                     indimlens(dimids(3)),ntslice)) 
    9541004                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i2, start=(/1,1,1,nt/) ), istop ) 
    9551005!$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 
     1006!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i2,localdata_4d_i2,di,dj,nt,ntslice) 
     1007                     DO jl = 1, ntslice 
    9581008!$OMP DO  
    9591009                        DO jk = 1, indimlens(dimids(3)) 
     
    9701020                  CASE( NF90_INT ) 
    9711021                     ALLOCATE(localdata_4d_i4(local_sizes(di),local_sizes(dj),               & 
    972                         &                     indimlens(dimids(3)),ntchunk)) 
     1022                        &                     indimlens(dimids(3)),ntslice)) 
    9731023                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_i4, start=(/1,1,1,nt/) ), istop ) 
    9741024!$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 
     1025!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_i4,localdata_4d_i4,di,dj,nt,ntslice) 
     1026                     DO jl = 1, ntslice 
    9771027!$OMP DO 
    9781028                        DO jk = 1, indimlens(dimids(3)) 
     
    9891039                  CASE( NF90_FLOAT ) 
    9901040                     ALLOCATE(localdata_4d_sp(local_sizes(di),local_sizes(dj),               & 
    991                         &                     indimlens(dimids(3)),ntchunk)) 
     1041                        &                     indimlens(dimids(3)),ntslice)) 
    9921042                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_sp, start=(/1,1,1,nt/) ), istop ) 
    9931043!$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 
     1044!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_sp,localdata_4d_sp,di,dj,nt,ntslice)  
     1045                     DO jl = 1, ntslice 
    9961046!$OMP DO 
    9971047                        DO jk = 1, indimlens(dimids(3)) 
     
    10081058                  CASE( NF90_DOUBLE ) 
    10091059                     ALLOCATE(localdata_4d_dp(local_sizes(di),local_sizes(dj),               & 
    1010                         &                     indimlens(dimids(3)),ntchunk)) 
     1060                        &                     indimlens(dimids(3)),ntslice)) 
    10111061                     CALL check_nf90( nf90_get_var( ncid, jv, localdata_4d_dp, start=(/1,1,1,nt/) ), istop ) 
    10121062!$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 
     1063!$OMP& SHARED(idomain,jdomain,indimlens,dimids,start_pos,globaldata_4d_dp,localdata_4d_dp,di,dj,nt,ntslice)  
     1064                     DO jl = 1, ntslice 
    10151065!$OMP DO 
    10161066                        DO jk = 1, indimlens(dimids(3)) 
     
    10991149            CASE( NF90_DOUBLE ) 
    11001150               CALL check_nf90( nf90_put_var( outid, jv, globaldata_0d_dp ) ) 
     1151            CASE DEFAULT    
     1152               WRITE(numerr,*) '0d Unknown nf90 type: ', xtype 
     1153               STOP 4 
    11011154         END SELECT 
    11021155 
     
    11191172               CALL check_nf90( nf90_put_var( outid, jv, globaldata_1d_dp ) ) 
    11201173               DEALLOCATE(globaldata_1d_dp) 
     1174            CASE DEFAULT    
     1175               WRITE(numerr,*) '1d Unknown nf90 type: ', xtype 
     1176               STOP 4 
    11211177         END SELECT 
    11221178 
     
    11401196               DEALLOCATE(globaldata_2d_dp) 
    11411197            CASE DEFAULT    
    1142                WRITE(numerr,*) 'Unknown nf90 type: ', xtype 
     1198               WRITE(numerr,*) '2d Unknown nf90 type: ', xtype 
    11431199               STOP 4 
    11441200         END SELECT      
     
    11631219               DEALLOCATE(globaldata_3d_dp) 
    11641220            CASE DEFAULT    
    1165                WRITE(numerr,*) 'Unknown nf90 type: ', xtype 
     1221               WRITE(numerr,*) '3d Unknown nf90 type: ', xtype 
    11661222               STOP 4 
    11671223         END SELECT      
     
    11861242               DEALLOCATE(globaldata_4d_dp) 
    11871243            CASE DEFAULT    
    1188                WRITE(numerr,*) 'Unknown nf90 type: ', xtype 
     1244               WRITE(numerr,*) '4d Unknown nf90 type: ', xtype 
    11891245               STOP 4 
    11901246         END SELECT      
     1247         ! why only for big data set, test the cost. 
     1248         CALL check_nf90( nf90_sync( outid ) )    ! flush buffers to disk after writing big 4D datasets 
    11911249     
    11921250      ENDIF 
    11931251 
    1194          nt = nt + ntchunk 
     1252         nt = nt + ntslice 
    11951253 
    11961254      END DO ! WHILE loop 
     
    12371295            WRITE(numerr,*) "*** NEMO rebuild failed ***" 
    12381296            WRITE(numerr,*) 
    1239             STOP 4 
     1297            STOP 5 
    12401298         ENDIF 
    12411299      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.