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 2364 for branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC – NEMO

Ignore:
Timestamp:
2010-11-05T16:22:12+01:00 (13 years ago)
Author:
acc
Message:

Added basic NetCDF4 chunking and compression support (key_netcdf4). See ticket #754

Location:
branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DIA/diaptr.F90

    r2287 r2364  
    728728            ! Horizontal grid : zphi() 
    729729            CALL histbeg(clhstnam, 1, zfoo, jpj, zphi,   & 
    730                1, 1, 1, jpj, niter, zjulian, zdt*nf_ptr, nhoridz, numptr, domain_id=nidom_ptr) 
     730               1, 1, 1, jpj, niter, zjulian, zdt*nf_ptr, nhoridz, numptr, domain_id=nidom_ptr, snc4chunks=snc4set) 
    731731            ! Vertical grids : gdept_0, gdepw_0 
    732732            CALL histvert( numptr, "deptht", "Vertical T levels",   & 
     
    880880            ENDIF 
    881881 
    882             CALL histend( numptr ) 
     882            CALL histend( numptr, snc4set ) 
    883883 
    884884         END IF 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DIA/diawri.F90

    r2329 r2364  
    273273         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
    274274            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       & 
    275             &          nit000-1, zjulian, zdt, nh_T, nid_T, domain_id=nidom ) 
     275            &          nit000-1, zjulian, zdt, nh_T, nid_T, domain_id=nidom, snc4chunks=snc4set ) 
    276276         CALL histvert( nid_T, "deptht", "Vertical T levels",      &  ! Vertical grid: gdept 
    277277            &           "m", ipk, gdept_0, nz_T, "down" ) 
     
    286286         CALL histbeg( clhstnam, jpi, glamu, jpj, gphiu,           &  ! Horizontal grid: glamu and gphiu 
    287287            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       & 
    288             &          nit000-1, zjulian, zdt, nh_U, nid_U, domain_id=nidom ) 
     288            &          nit000-1, zjulian, zdt, nh_U, nid_U, domain_id=nidom, snc4chunks=snc4set ) 
    289289         CALL histvert( nid_U, "depthu", "Vertical U levels",      &  ! Vertical grid: gdept 
    290290            &           "m", ipk, gdept_0, nz_U, "down" ) 
     
    299299         CALL histbeg( clhstnam, jpi, glamv, jpj, gphiv,           &  ! Horizontal grid: glamv and gphiv 
    300300            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       & 
    301             &          nit000-1, zjulian, zdt, nh_V, nid_V, domain_id=nidom ) 
     301            &          nit000-1, zjulian, zdt, nh_V, nid_V, domain_id=nidom, snc4chunks=snc4set ) 
    302302         CALL histvert( nid_V, "depthv", "Vertical V levels",      &  ! Vertical grid : gdept 
    303303            &          "m", ipk, gdept_0, nz_V, "down" ) 
     
    312312         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
    313313            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       & 
    314             &          nit000-1, zjulian, zdt, nh_W, nid_W, domain_id=nidom ) 
     314            &          nit000-1, zjulian, zdt, nh_W, nid_W, domain_id=nidom, snc4chunks=snc4set ) 
    315315         CALL histvert( nid_W, "depthw", "Vertical W levels",      &  ! Vertical grid: gdepw 
    316316            &          "m", ipk, gdepw_0, nz_W, "down" ) 
     
    404404#endif  
    405405 
    406          CALL histend( nid_T ) 
     406         CALL histend( nid_T, snc4chunks=snc4set ) 
    407407 
    408408         !                                                                                      !!! nid_U : 3D 
     
    417417            &          jpi, jpj, nh_U, 1  , 1, 1  , - 99, 32, clop, zsto, zout ) 
    418418 
    419          CALL histend( nid_U ) 
     419         CALL histend( nid_U, snc4chunks=snc4set ) 
    420420 
    421421         !                                                                                      !!! nid_V : 3D 
     
    430430            &          jpi, jpj, nh_V, 1  , 1, 1  , - 99, 32, clop, zsto, zout ) 
    431431 
    432          CALL histend( nid_V ) 
     432         CALL histend( nid_V, snc4chunks=snc4set ) 
    433433 
    434434         !                                                                                      !!! nid_W : 3D 
     
    458458#endif 
    459459 
    460          CALL histend( nid_W ) 
     460         CALL histend( nid_W, snc4chunks=snc4set ) 
    461461 
    462462         IF(lwp) WRITE(numout,*) 
     
    624624      zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment 
    625625      CALL histbeg( clname, jpi, glamt, jpj, gphit,   & 
    626           1, jpi, 1, jpj, nit000-1, zjulian, zdt, nh_i, id_i, domain_id=nidom )          ! Horizontal grid : glamt and gphit 
     626          1, jpi, 1, jpj, nit000-1, zjulian, zdt, nh_i, id_i, domain_id=nidom, snc4chunks=snc4set ) ! Horizontal grid : glamt and gphit 
    627627      CALL histvert( id_i, "deptht", "Vertical T levels",   &    ! Vertical grid : gdept 
    628628          "m", jpk, gdept_0, nz_i, "down") 
     
    658658      CALL lim_wri_state_2( kt, id_i, nh_i ) 
    659659#else 
    660       CALL histend( id_i ) 
     660      CALL histend( id_i, snc4chunks=snc4set ) 
    661661#endif 
    662662 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r2287 r2364  
    106106      !!              - namdom namelist 
    107107      !!              - namcla namelist 
     108      !!              - namnc4 namelist   ! "key_netcdf4" only 
    108109      !!---------------------------------------------------------------------- 
    109110      USE ioipsl 
     
    115116         &             rn_rdtmax, rn_rdth     , nn_baro     , nn_closea 
    116117      NAMELIST/namcla/ nn_cla 
     118#if defined key_netcdf4 
     119      NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip 
     120#endif 
    117121      !!---------------------------------------------------------------------- 
    118122 
     
    232236      IF( lk_mpp_rep .AND. n_cla /= 0 )   CALL ctl_stop( ' Reproductibility tests (nbit_cmp=1) require n_cla = 0' ) 
    233237      ! 
     238 
     239#if defined key_netcdf4 
     240 
     241      REWIND( numnam )              ! Namelist namnc4 : netcdf4 chunking parameters 
     242      READ  ( numnam, namnc4 ) 
     243      IF(lwp) THEN 
     244         WRITE(numout,*) 
     245         WRITE(numout,*) '   Namelist namnc4 - Netcdf4 chunking parameters' 
     246         WRITE(numout,*) '      number of chunks in i-dimension      nn_nchunks_i   = ', nn_nchunks_i 
     247         WRITE(numout,*) '      number of chunks in j-dimension      nn_nchunks_j   = ', nn_nchunks_j 
     248         WRITE(numout,*) '      number of chunks in k-dimension      nn_nchunks_k   = ', nn_nchunks_k 
     249         WRITE(numout,*) '      apply netcdf4/hdf5 chunking & compression ln_nc4zip = ', ln_nc4zip 
     250      ENDIF 
     251 
     252      ! Put the netcdf4 settings into a simple structure (snc4set, defined in in_out_manager module) 
     253      ! Note the chunk size in the unlimited (time) dimension will be fixed at 1 
     254      snc4set%ni   = nn_nchunks_i 
     255      snc4set%nj   = nn_nchunks_j 
     256      snc4set%nk   = nn_nchunks_k 
     257      snc4set%luse = ln_nc4zip 
     258 
     259#else 
     260 
     261      snc4set%luse = .FALSE. 
     262  
     263#endif 
    234264   END SUBROUTINE dom_nam 
    235265 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r2287 r2364  
    4545   LOGICAL            ::   ln_clobber    = .FALSE.     !: clobber (overwrite) an existing file 
    4646   INTEGER            ::   nn_chunksz    = 0           !: chunksize (bytes) for NetCDF file (working only with iom_nf90 routines) 
     47#if defined key_netcdf4 
     48   !!---------------------------------------------------------------------- 
     49   !!                   namnc4 namelist parameters 
     50   !!---------------------------------------------------------------------- 
     51                                                       !: ========================================================================= 
     52                                                       !: The following four values determine the partitioning of the output fields 
     53                                                       !: into netcdf4 chunks. They are unrelated to the nn_chunk_sz setting which is 
     54                                                       !: for runtime optimisation. The individual netcdf4 chunks can be optionally  
     55                                                       !: gzipped (recommended) leading to significant reductions in I/O volumes  
     56   INTEGER            ::   nn_nchunks_i  = 1           !: number of chunks required in the i-dimension (only with iom_nf90 routines and key_netcdf4) 
     57   INTEGER            ::   nn_nchunks_j  = 1           !: number of chunks required in the j-dimension (only with iom_nf90 routines and key_netcdf4) 
     58   INTEGER            ::   nn_nchunks_k  = 1           !: number of chunks required in the k-dimension (only with iom_nf90 routines and key_netcdf4) 
     59   INTEGER            ::   nn_nchunks_t  = 1           !: number of chunks required in the t-dimension (only with iom_nf90 routines and key_netcdf4) 
     60   LOGICAL            ::   ln_nc4zip     = .TRUE.      !: netcdf4 usage. (T): chunk and compress output datasets using the HDF5 sublayers of netcdf4 
     61                                                       !:                (F): ignore chunking request and use the netcdf4 library to produce netcdf3-compatible files  
     62#endif 
     63 
     64!$AGRIF_DO_NOT_TREAT 
     65   TYPE, PUBLIC :: snc4_ctl                            !: netcdf4 chunking control structure (always needed for decision making) 
     66      SEQUENCE 
     67      INTEGER :: ni 
     68      INTEGER :: nj 
     69      INTEGER :: nk 
     70      LOGICAL :: luse 
     71   END TYPE snc4_ctl 
     72 
     73   TYPE(snc4_ctl) :: snc4set                          !: netcdf4 chunking control structure (always needed for decision making) 
     74!$AGRIF_END_DO_NOT_TREAT 
     75 
    4776 
    4877   !! conversion of DOCTOR norm namelist name into model name 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/IOM/iom_nf90.F90

    r2351 r2364  
    3939      MODULE PROCEDURE iom_nf90_rp0123d 
    4040   END INTERFACE 
     41 
     42#if ! defined key_netcdf4 
     43   !!-------------------------------------------------------------------- 
     44   !! NOT 'key_netcdf4' Defines dummy routines for netcdf4 
     45   !!                   calls when compiling without netcdf4 libraries 
     46   !!-------------------------------------------------------------------- 
     47   PUBLIC NF90_DEF_VAR_CHUNKING, NF90_DEF_VAR_DEFLATE ! contained below 
     48   INTEGER :: NF90_HDF5 
     49#endif 
    4150   !!---------------------------------------------------------------------- 
    4251   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     
    6776      INTEGER            ::   jl               ! loop variable 
    6877      INTEGER            ::   ichunk           ! temporary storage of nn_chunksz 
    69       INTEGER            ::   imode            ! creation mode flag: NF90_CLOBBER or NF90_NOCLOBBER 
     78      INTEGER            ::   imode            ! creation mode flag: NF90_CLOBBER or NF90_NOCLOBBER or NF90_HDF5 
    7079      LOGICAL            ::   llclobber        ! local definition of ln_clobber 
    7180      !--------------------------------------------------------------------- 
     
    8291         IF( ldwrt ) THEN  ! ... in write mode 
    8392            IF(lwp) WRITE(numout,*) TRIM(clinfo)//' open existing file: '//TRIM(cdname)//' in WRITE mode' 
    84             CALL iom_nf90_check(NF90_OPEN( TRIM(cdname), NF90_WRITE  , if90id, chunksize = ichunk ), clinfo) 
     93            IF( snc4set%luse ) THEN 
     94               CALL iom_nf90_check(NF90_OPEN( TRIM(cdname), NF90_WRITE  , if90id ), clinfo) 
     95            ELSE 
     96               CALL iom_nf90_check(NF90_OPEN( TRIM(cdname), NF90_WRITE  , if90id, chunksize = ichunk ), clinfo) 
     97            ENDIF 
    8598            CALL iom_nf90_check(NF90_SET_FILL( if90id, NF90_NOFILL, idmy                          ), clinfo) 
    8699         ELSE              ! ... in read mode 
     
    101114            ELSE                   ;   imode = IOR( NF90_64BIT_OFFSET, NF90_NOCLOBBER )  
    102115            ENDIF 
    103             CALL iom_nf90_check(NF90_CREATE( TRIM(cdname), imode, if90id, chunksize = ichunk ), clinfo) 
     116            IF( snc4set%luse ) THEN 
     117               IF(lwp) WRITE(numout,*) TRIM(clinfo)//' creating file: '//TRIM(cdname)//' in hdf5 (netcdf4) mode' 
     118               IF( llclobber ) THEN   ;   imode = IOR(NF90_HDF5, NF90_CLOBBER) 
     119               ELSE                   ;   imode = IOR(NF90_HDF5, NF90_NOCLOBBER) 
     120               ENDIF 
     121               CALL iom_nf90_check(NF90_CREATE( TRIM(cdname), imode, if90id ), clinfo) 
     122            ELSE 
     123               CALL iom_nf90_check(NF90_CREATE( TRIM(cdname), imode, if90id, chunksize = ichunk ), clinfo) 
     124            ENDIF 
    104125            CALL iom_nf90_check(NF90_SET_FILL( if90id, NF90_NOFILL, idmy                     ), clinfo) 
    105126            ! define dimensions 
     
    378399      INTEGER               :: idmy                 ! dummy variable 
    379400      INTEGER               :: itype                ! variable type 
     401      INTEGER, DIMENSION(4) :: ichunksz             ! NetCDF4 chunk sizes. Will be computed using 
     402                                                    ! nn_nchunks_[i,j,k,t] namelist parameters 
     403      INTEGER               :: ichunkalg, ishuffle,& 
     404                               ideflate, ideflate_level 
     405                                                    ! NetCDF4 internally fixed parameters 
     406      LOGICAL               :: lchunk               ! logical switch to activate chunking and compression 
     407                                                    ! when appropriate (currently chunking is applied to 4d fields only) 
    380408      !--------------------------------------------------------------------- 
    381409      ! 
     
    408436      ! =============== 
    409437      IF( kvid <= 0 ) THEN 
     438         ! 
     439         ! NetCDF4 chunking and compression fixed settings 
     440         ichunkalg = 0 
     441         ishuffle = 1 
     442         ideflate = 1 
     443         ideflate_level = 1 
     444         ! 
    410445         idvar = iom_file(kiomid)%nvars + 1 
    411446         ! are we in define mode? 
     
    438473                 &                            iom_file(kiomid)%nvid(idvar) ), clinfo) 
    439474         ENDIF 
     475         lchunk = .false. 
     476         IF( snc4set%luse .AND. idims.eq.4 ) lchunk = .true. 
    440477         ! update informations structure related the new variable we want to add... 
    441478         iom_file(kiomid)%nvars         = idvar 
     
    449486         DO jd = 1, idims 
    450487            CALL iom_nf90_check(NF90_INQUIRE_DIMENSION( if90id, idimid(jd), len = iom_file(kiomid)%dimsz(jd,idvar) ), clinfo) 
     488            IF ( lchunk ) ichunksz(jd) = iom_file(kiomid)%dimsz(jd,idvar) 
    451489         END DO 
     490         IF ( lchunk ) THEN 
     491            ! Calculate chunk sizes by partitioning each dimension as requested in namnc4 namelist 
     492            ! Disallow very small chunk sizes and prevent chunk sizes larger than each individual dimension 
     493            ichunksz(1) = MIN( ichunksz(1),MAX( (ichunksz(1)-1)/snc4set%ni + 1 ,16 ) ) ! Suggested default nc4set%ni=4 
     494            ichunksz(2) = MIN( ichunksz(2),MAX( (ichunksz(2)-1)/snc4set%nj + 1 ,16 ) ) ! Suggested default nc4set%nj=2 
     495            ichunksz(3) = MIN( ichunksz(3),MAX( (ichunksz(3)-1)/snc4set%nk + 1 , 1 ) ) ! Suggested default nc4set%nk=6 
     496            ichunksz(4) = 1                                                            ! Do not allow chunks to span the 
     497                                                                                       ! unlimited dimension 
     498            CALL iom_nf90_check(NF90_DEF_VAR_CHUNKING(if90id, idvar, ichunkalg, ichunksz), clinfo) 
     499            CALL iom_nf90_check(NF90_DEF_VAR_DEFLATE(if90id, idvar, ishuffle, ideflate, ideflate_level), clinfo) 
     500            IF(lwp) WRITE(numout,*) TRIM(clinfo)//' chunked ok. Chunks sizes: ', ichunksz 
     501         ENDIF 
    452502         IF(lwp) WRITE(numout,*) TRIM(clinfo)//' defined ok' 
    453503      ELSE 
     
    529579   END SUBROUTINE iom_nf90_check 
    530580 
     581#if ! defined key_netcdf4 
     582 
     583      !!-------------------------------------------------------------------- 
     584      !! NOT 'key_netcdf4' Defines dummy routines for netcdf4 
     585      !!                   calls when compiling without netcdf4 libraries 
     586      !!-------------------------------------------------------------------- 
     587 
     588   INTEGER FUNCTION NF90_DEF_VAR_CHUNKING(idum1, idum2, idum3, iarr1) 
     589      !!-------------------------------------------------------------------- 
     590      !!                   ***  SUBROUTINE NF90_DEF_VAR_CHUNKING  *** 
     591      !! 
     592      !! ** Purpose :   Dummy NetCDF4 routine to enable compiling with NetCDF3 libraries 
     593      !!-------------------------------------------------------------------- 
     594      INTEGER,               INTENT(in) :: idum1, idum2, idum3 
     595      INTEGER, DIMENSION(4), INTENT(in) :: iarr1 
     596      IF(lwp) WRITE(numout,*) 'Warning: Attempt to chunk output variable without NetCDF4 support' 
     597      NF90_DEF_VAR_CHUNKING = -1 
     598   END FUNCTION NF90_DEF_VAR_CHUNKING 
     599 
     600   INTEGER FUNCTION NF90_DEF_VAR_DEFLATE(idum1, idum2, idum3, idum4, idum5) 
     601      !!-------------------------------------------------------------------- 
     602      !!                   ***  SUBROUTINE NF90_DEF_VAR_DEFLATE  *** 
     603      !! 
     604      !! ** Purpose :   Dummy NetCDF4 routine to enable compiling with NetCDF3 libraries 
     605      !!-------------------------------------------------------------------- 
     606      INTEGER,               INTENT(in) :: idum1, idum2, idum3, idum4, idum5 
     607      IF(lwp) WRITE(numout,*) 'Warning: Attempt to compress output variable without NetCDF4 support' 
     608      NF90_DEF_VAR_DEFLATE = -1 
     609   END FUNCTION NF90_DEF_VAR_DEFLATE 
     610#endif 
    531611 
    532612   !!====================================================================== 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r2287 r2364  
    9595            CASE DEFAULT         ;   WRITE(numout,*) '             open ocean restart NetCDF file: '//clname 
    9696            END SELECT 
     97            IF ( snc4set%luse )      WRITE(numout,*) '             opened for NetCDF4 chunking and compression' 
    9798            IF( kt == nitrst - 1 ) THEN   ;   WRITE(numout,*) '             kt = nitrst - 1 = ', kt 
    9899            ELSE                          ;   WRITE(numout,*) '             kt = '             , kt 
     
    178179         CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file' 
    179180         END SELECT 
     181         IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support' 
    180182         WRITE(numout,*) '~~~~~~~~' 
    181183      ENDIF 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRD/trdmld.F90

    r2287 r2364  
    873873      IF(lwp) WRITE(numout,*) ' Name of NETCDF file ', clhstnam 
    874874      CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,                                            & 
    875       &             1, jpi, 1, jpj, nit000-1, zjulian, rdt, nh_t, nidtrd, domain_id=nidom ) 
     875      &             1, jpi, 1, jpj, nit000-1, zjulian, rdt, nh_t, nidtrd, domain_id=nidom, snc4chunks=snc4set ) 
    876876 
    877877      !-- Define the ML depth variable 
     
    925925 
    926926      !-- Leave IOIPSL/NetCDF define mode 
    927       CALL histend( nidtrd ) 
     927      CALL histend( nidtrd, snc4set ) 
    928928 
    929929#endif        /* key_dimgout */ 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/TRD/trdvor.F90

    r2287 r2364  
    568568      IF(lwp) WRITE(numout,*) ' Name of NETCDF file ', clhstnam 
    569569      CALL histbeg( clhstnam, jpi, glamf, jpj, gphif,1, jpi,   &  ! Horizontal grid : glamt and gphit 
    570          &          1, jpj, nit000-1, zjulian, rdt, nh_t, nidvor, domain_id=nidom ) 
     570         &          1, jpj, nit000-1, zjulian, rdt, nh_t, nidvor, domain_id=nidom, snc4chunks=snc4set ) 
    571571      CALL wheneq( jpi*jpj, fmask, 1, 1., ndexvor1, ndimvor1 )    ! surface 
    572572 
     
    598598      CALL histdef( nidvor, "sovorgap", cvort//"gap", "s-2",             & ! gap between 1st and 2 nd mbre 
    599599         &          jpi,jpj,nh_t,1,1,1,-99,32,clop,zsto,zout) 
    600       CALL histend( nidvor ) 
     600      CALL histend( nidvor, snc4set ) 
    601601 
    602602      IF( idebug /= 0 ) THEN 
Note: See TracChangeset for help on using the changeset viewer.