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

Changeset 1488


Ignore:
Timestamp:
2009-07-16T11:19:46+02:00 (15 years ago)
Author:
smasson
Message:

Addition of clobber and chunksize when opening NetCDF files, see ticket:374

Location:
trunk
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • trunk/CONFIG/GYRE/EXP00/namelist

    r1456 r1488  
    4040   ln_dimgnnn  = .false.   !  DIMG file format: 1 file for all processors (F) or by processor (T) 
    4141   ln_mskland  = .false.   !  mask land points (1.e+20) in NetCDF outputs (costly: + ~15%) 
     42   ln_clobber  = .false.   ! clobber (overwrite) an existing file 
     43   nn_chunksz  = 0         ! chunksize (bytes) for NetCDF file (working only with iom_nf90 routines) 
    4244/ 
    4345!!====================================================================== 
  • trunk/CONFIG/GYRE_LOBSTER/EXP00/namelist

    r1456 r1488  
    4040   ln_dimgnnn  = .false.   !  DIMG file format: 1 file for all processors (F) or by processor (T) 
    4141   ln_mskland  = .false.   !  mask land points in NetCDF outputs (costly: + ~15%) 
     42   ln_clobber  = .false.   ! clobber (overwrite) an existing file 
     43   nn_chunksz  = 0         ! chunksize (bytes) for NetCDF file (working only with iom_nf90 routines) 
    4244/ 
    4345!!====================================================================== 
  • trunk/CONFIG/ORCA2_LIM/EXP00/1_namelist

    r1424 r1488  
    4040   ln_dimgnnn  = .false.   !  DIMG file format: 1 file for all processors (F) or by processor (T) 
    4141   ln_mskland  = .false.   !  mask land points in NetCDF outputs (costly: + ~15%) 
     42   ln_clobber  = .false.   ! clobber (overwrite) an existing file 
     43   nn_chunksz  = 0         ! chunksize (bytes) for NetCDF file (working only with iom_nf90 routines) 
    4244/ 
    4345!!====================================================================== 
  • trunk/CONFIG/ORCA2_LIM/EXP00/namelist

    r1456 r1488  
    4040   ln_dimgnnn  = .false.   !  DIMG file format: 1 file for all processors (F) or by processor (T) 
    4141   ln_mskland  = .false.   !  mask land points in NetCDF outputs (costly: + ~15%) 
     42   ln_clobber  = .false.   ! clobber (overwrite) an existing file 
     43   nn_chunksz  = 0         ! chunksize (bytes) for NetCDF file (working only with iom_nf90 routines) 
    4244/ 
    4345!!====================================================================== 
  • trunk/CONFIG/ORCA2_LIM_PISCES/EXP00/namelist

    r1456 r1488  
    4040   ln_dimgnnn  = .false.   !  DIMG file format: 1 file for all processors (F) or by processor (T) 
    4141   ln_mskland  = .false.   !  mask land points in NetCDF outputs (costly: + ~15%) 
     42   ln_clobber  = .false.   ! clobber (overwrite) an existing file 
     43   nn_chunksz  = 0         ! chunksize (bytes) for NetCDF file (working only with iom_nf90 routines) 
    4244/ 
    4345!!====================================================================== 
  • trunk/NEMO/OPA_SRC/DOM/domain.F90

    r1465 r1488  
    129129      NAMELIST/namrun/ no    , cexper, cn_ocerst_in, cn_ocerst_out, ln_rstart, nrstdt,   & 
    130130         &             nit000, nitend, ndate0      , nleapy       , ninist   , nstock,   & 
    131          &             nwrite, ln_dimgnnn, ln_mskland 
     131         &             nwrite, ln_dimgnnn, ln_mskland, ln_clobber, nn_chunksz 
    132132 
    133133      NAMELIST/namdom/ ntopo , e3zps_min, e3zps_rat, nmsh   ,   & 
     
    160160         WRITE(numout,*) '           multi file dimgout           ln_dimgnnn   = ', ln_dimgnnn 
    161161         WRITE(numout,*) '           mask land points             ln_mskland   = ', ln_mskland 
     162         WRITE(numout,*) '           overwrite an existing file   ln_clobber   = ', ln_clobber 
     163         WRITE(numout,*) '           NetCDF chunksize (bytes)     nn_chunksz   = ', nn_chunksz 
    162164      ENDIF 
    163165 
  • trunk/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r1481 r1488  
    4040                                                       !:                  (T): 1 file per proc 
    4141   LOGICAL            ::   ln_mskland    = .FALSE.     !: mask land points in NetCDF outputs (costly: + ~15%) 
     42   LOGICAL            ::   ln_clobber    = .FALSE.     !: clobber (overwrite) an existing file 
     43   INTEGER            ::   nn_chunksz    = 0           !: chunksize (bytes) for NetCDF file (working only with iom_nf90 routines) 
    4244   !!---------------------------------------------------------------------- 
    4345   !! was in restart but moved here because of the OFF line... better solution should be found... 
  • trunk/NEMO/OPA_SRC/IOM/iom_ioipsl.F90

    r1271 r1488  
    4848      !! ** Purpose :  open an input file with IOIPSL (only fliocom module) 
    4949      !!--------------------------------------------------------------------- 
    50       CHARACTER(len=*)       , INTENT(inout)           ::   cdname    ! File name 
    51       INTEGER                , INTENT(  out)           ::   kiomid    ! ioipsl identifier of the opened file 
    52       LOGICAL                , INTENT(in   )           ::   ldwrt     ! read or write the file? 
    53       LOGICAL                , INTENT(in   )           ::   ldok      ! check the existence  
    54       INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar   ! domain parameters:  
    55  
    56       CHARACTER(LEN=100) ::   clinfo     ! info character 
    57       INTEGER            ::   iln        ! lengths of character 
    58       INTEGER            ::   istop      ! temporary storage of nstop 
    59       INTEGER            ::   ifliodom   ! model domain identifier (see flio_dom_set) 
    60       INTEGER            ::   ioipslid   ! ioipsl identifier of the opened file 
    61       INTEGER            ::   jl         ! loop variable 
     50      CHARACTER(len=*)       , INTENT(inout)           ::   cdname      ! File name 
     51      INTEGER                , INTENT(  out)           ::   kiomid      ! ioipsl identifier of the opened file 
     52      LOGICAL                , INTENT(in   )           ::   ldwrt       ! read or write the file? 
     53      LOGICAL                , INTENT(in   )           ::   ldok        ! check the existence  
     54      INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar     ! domain parameters:  
     55 
     56      CHARACTER(LEN=100) ::   clinfo      ! info character 
     57      CHARACTER(LEN=10 ) ::   clstatus    ! status of opened file (REPLACE or NEW) 
     58      INTEGER            ::   iln         ! lengths of character 
     59      INTEGER            ::   istop       ! temporary storage of nstop 
     60      INTEGER            ::   ifliodom    ! model domain identifier (see flio_dom_set) 
     61      INTEGER            ::   ioipslid    ! ioipsl identifier of the opened file 
     62      INTEGER            ::   jl          ! loop variable 
     63      LOGICAL            ::   llclobber   ! local definition of ln_clobber 
    6264      !--------------------------------------------------------------------- 
    6365 
     
    6567      istop = nstop 
    6668      ! 
    67       IF( ldok ) THEN      ! Open existing file... 
     69      llclobber = ldwrt .AND. ln_clobber 
     70      IF( ldok .AND. .NOT. llclobber ) THEN      ! Open existing file... 
    6871         !                 ! ============= 
    6972         IF( ldwrt ) THEN  ! ... in write mode 
     
    7881         iln = INDEX( cdname, '.nc' ) 
    7982         IF( ldwrt ) THEN  ! the file should be open in write mode so we create it... 
     83            IF( llclobber ) THEN   ;   clstatus = 'REPLACE'  
     84            ELSE                   ;   clstatus = 'NEW' 
     85            ENDIF 
    8086            IF( jpnij > 1 ) THEN 
    8187               ! define the domain position regarding to the global domain (mainly useful in mpp) 
     
    8692               IF(lwp) WRITE(numout,*) TRIM(clinfo)//' create new file: '//cdname(1:iln-1)//'... in WRITE mode' 
    8793               CALL fliocrfd( cdname, (/'x'         , 'y'         , 'z', 't'/)   & 
    88                   &         , (/kdompar(1,1), kdompar(2,1), jpk, -1 /), ioipslid, ifliodom ) 
     94                  &         , (/kdompar(1,1), kdompar(2,1), jpk, -1 /), ioipslid, ifliodom, mode = clstatus ) 
    8995            ELSE              ! the file should be open for read mode so it must exist... 
    9096               IF(lwp) WRITE(numout,*) TRIM(clinfo)//' create new file: '//cdname//' in WRITE mode' 
    9197               CALL fliocrfd( cdname, (/'x'         , 'y'         , 'z', 't'/)   & 
    92                   &         , (/kdompar(1,1), kdompar(2,1), jpk, -1 /), ioipslid ) 
     98                  &         , (/kdompar(1,1), kdompar(2,1), jpk, -1 /), ioipslid,           mode = clstatus ) 
    9399            ENDIF 
    94100         ELSE              ! the file should be open for read mode so it must exist... 
  • trunk/NEMO/OPA_SRC/IOM/iom_nf90.F90

    r1271 r1488  
    4949      !! ** Purpose : open an input file with NF90 
    5050      !!--------------------------------------------------------------------- 
    51       CHARACTER(len=*)       , INTENT(inout)           ::   cdname    ! File name 
    52       INTEGER                , INTENT(  out)           ::   kiomid    ! nf90 identifier of the opened file 
    53       LOGICAL                , INTENT(in   )           ::   ldwrt     ! read or write the file? 
    54       LOGICAL                , INTENT(in   )           ::   ldok      ! check the existence  
    55       INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar   ! domain parameters:  
    56  
    57       CHARACTER(LEN=100) ::   clinfo   ! info character 
    58       CHARACTER(LEN=100) ::   cltmp    ! temporary character 
    59       INTEGER            ::   iln      ! lengths of character 
    60       INTEGER            ::   istop    ! temporary storage of nstop 
    61       INTEGER            ::   if90id   ! nf90 identifier of the opened file 
    62       INTEGER            ::   idmy     ! dummy variable 
    63       INTEGER            ::   jl       ! loop variable 
     51      CHARACTER(len=*)       , INTENT(inout)           ::   cdname      ! File name 
     52      INTEGER                , INTENT(  out)           ::   kiomid      ! nf90 identifier of the opened file 
     53      LOGICAL                , INTENT(in   )           ::   ldwrt       ! read or write the file? 
     54      LOGICAL                , INTENT(in   )           ::   ldok        ! check the existence  
     55      INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar     ! domain parameters:  
     56 
     57      CHARACTER(LEN=100) ::   clinfo           ! info character 
     58      CHARACTER(LEN=100) ::   cltmp            ! temporary character 
     59      INTEGER            ::   iln              ! lengths of character 
     60      INTEGER            ::   istop            ! temporary storage of nstop 
     61      INTEGER            ::   if90id           ! nf90 identifier of the opened file 
     62      INTEGER            ::   idmy             ! dummy variable 
     63      INTEGER            ::   jl               ! loop variable 
     64      INTEGER            ::   ichunk           ! temporary storage of nn_chunksz 
     65      INTEGER            ::   imode            ! creation mode flag: NF90_CLOBBER or NF90_NOCLOBBER 
     66      LOGICAL            ::   llclobber        ! local definition of ln_clobber 
    6467      !--------------------------------------------------------------------- 
    6568 
    6669      clinfo = '                    iom_nf90_open ~~~  ' 
    6770      istop = nstop   ! store the actual value of nstop 
    68       ! 
    69       IF( ldok ) THEN      ! Open existing file... 
     71      IF( nn_chunksz > 0 ) THEN   ;   ichunk = nn_chunksz 
     72      ELSE                        ;   ichunk = NF90_SIZEHINT_DEFAULT 
     73      ENDIF 
     74      ! 
     75      llclobber = ldwrt .AND. ln_clobber 
     76      IF( ldok .AND. .NOT. llclobber ) THEN      ! Open existing file... 
    7077         !                 ! ============= 
    7178         IF( ldwrt ) THEN  ! ... in write mode 
    7279            IF(lwp) WRITE(numout,*) TRIM(clinfo)//' open existing file: '//TRIM(cdname)//' in WRITE mode' 
    73             CALL iom_nf90_check(NF90_OPEN(TRIM(cdname), NF90_WRITE  , if90id), clinfo) 
    74             CALL iom_nf90_check(NF90_SET_FILL( if90id, NF90_NOFILL, idmy    ), clinfo) 
     80            CALL iom_nf90_check(NF90_OPEN( TRIM(cdname), NF90_WRITE  , if90id, chunksize = ichunk ), clinfo) 
     81            CALL iom_nf90_check(NF90_SET_FILL( if90id, NF90_NOFILL, idmy                          ), clinfo) 
    7582         ELSE              ! ... in read mode 
    7683            IF(lwp) WRITE(numout,*) TRIM(clinfo)//' open existing file: '//TRIM(cdname)//' in READ mode' 
    77             CALL iom_nf90_check(NF90_OPEN(TRIM(cdname), NF90_NOWRITE, if90id), clinfo) 
    78          ENDIF 
    79       ELSE                 ! the file does not exist 
     84            CALL iom_nf90_check(NF90_OPEN( TRIM(cdname), NF90_NOWRITE, if90id, chunksize = ichunk ), clinfo) 
     85         ENDIF 
     86      ELSE                                       ! the file does not exist (or we overwrite it) 
    8087         !                 ! ============= 
    8188         iln = INDEX( cdname, '.nc' ) 
     
    8693            ENDIF 
    8794            IF(lwp) WRITE(numout,*) TRIM(clinfo)//' create new file: '//TRIM(cdname)//' in WRITE mode' 
    88             CALL iom_nf90_check(NF90_CREATE( TRIM(cdname), NF90_NOCLOBBER, if90id ), clinfo) 
    89             CALL iom_nf90_check(NF90_SET_FILL( if90id, NF90_NOFILL, idmy          ), clinfo) 
     95 
     96            IF( llclobber ) THEN   ;   imode = NF90_CLOBBER  
     97            ELSE                   ;   imode = NF90_NOCLOBBER  
     98            ENDIF 
     99            CALL iom_nf90_check(NF90_CREATE( TRIM(cdname), imode, if90id, chunksize = ichunk ), clinfo) 
     100            CALL iom_nf90_check(NF90_SET_FILL( if90id, NF90_NOFILL, idmy                     ), clinfo) 
    90101            ! define dimensions 
    91102            CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'x', kdompar(1,1)  , idmy ), clinfo) 
  • trunk/NEMO/OPA_SRC/IOM/iom_rstdimg.F90

    r1152 r1488  
    4848      !! ** Purpose :  open an input file read only (return 0 if not found) 
    4949      !!--------------------------------------------------------------------- 
    50       CHARACTER(len=*)       , INTENT(inout)           ::   cdname   ! File name 
    51       INTEGER                , INTENT(  out)           ::   kiomid   ! iom identifier of the opened file 
    52       LOGICAL                , INTENT(in   )           ::   ldwrt    ! read or write the file? 
    53       LOGICAL                , INTENT(in   )           ::   ldok     ! check the existence  
    54       INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar  ! domain parameters:  
     50      CHARACTER(len=*)       , INTENT(inout)           ::   cdname      ! File name 
     51      INTEGER                , INTENT(  out)           ::   kiomid      ! iom identifier of the opened file 
     52      LOGICAL                , INTENT(in   )           ::   ldwrt       ! read or write the file? 
     53      LOGICAL                , INTENT(in   )           ::   ldok        ! check the existence  
     54      INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar     ! domain parameters:  
    5555 
    5656      CHARACTER(LEN=100)                      ::   clinfo                     ! info character 
    5757      CHARACTER(LEN=100)                      ::   cltmp                      ! temporary character 
     58      CHARACTER(LEN=10 )                      ::   clstatus                   ! status of opened file (REPLACE or NEW) 
    5859      INTEGER                                 ::   jv                         ! loop counter 
    5960      INTEGER                                 ::   istop                      ! temporary storage of nstop 
     
    7071      INTEGER                                 ::   iiglo, ijglo               ! domain global size  
    7172      INTEGER                                 ::   jl                         ! loop variable 
     73      LOGICAL                                 ::   llclobber                  ! local definition of ln_clobber 
    7274      CHARACTER(LEN=jpvnl), DIMENSION(jpmax_vars) ::   clna0d, clna1d, clna2d, clna3d     ! name of 0/1/2/3D variables 
    73       REAL(wp),         DIMENSION(jpmax_vars) ::   zval0d, zval1d, zval2d, zval3d     ! value of 0d variables or record 
    74       !                                                                               ! position for 1/2/3D variables 
     75      REAL(wp),             DIMENSION(jpmax_vars) ::   zval0d, zval1d, zval2d, zval3d     ! value of 0d variables or record 
     76      !                                                                                   ! position for 1/2/3D variables 
    7577      !--------------------------------------------------------------------- 
    7678      clinfo = '                    iom_rstdimg_open ~~~  ' 
     
    7880      ios = 0            ! default definition 
    7981      kiomid = 0         ! default definition 
     82      llclobber = ldwrt .AND. ln_clobber 
    8083      ! get a free unit 
    8184      idrst = getunit()  ! get a free logical unit for the restart file 
     
    8588      ! Open the file... 
    8689      ! ============= 
    87       IF( ldok ) THEN      ! Open existing file... 
     90      IF( ldok .AND. .NOT. llclobber ) THEN      ! Open existing file... 
    8891         ! find the record length 
    8992         OPEN( idrst, FILE = TRIM(cdname), FORM = 'unformatted', ACCESS = 'direct'   & 
     
    101104               &       , RECL = irecl8, STATUS = 'old', ACTION = 'read'     , IOSTAT = ios, ERR = 987 ) 
    102105         ENDIF 
    103       ELSE                 ! the file does not exist 
     106      ELSE                                       ! the file does not exist (or we overwrite it) 
    104107         iln = INDEX( cdname, '.dimg' ) 
    105108         IF( ldwrt ) THEN  ! the file should be open in readwrite mode so we create it... 
     
    110113            ENDIF 
    111114            IF(lwp) WRITE(numout,*) TRIM(clinfo)//' create new file: '//TRIM(cdname)//' in READWRITE mode' 
     115             
     116            IF( llclobber ) THEN   ;   clstatus = 'REPLACE'  
     117            ELSE                   ;   clstatus = 'NEW' 
     118            ENDIF 
    112119            OPEN( idrst, FILE = TRIM(cdname), FORM = 'UNFORMATTED', ACCESS = 'DIRECT'   & 
    113                &       , RECL = irecl8, STATUS = 'new', ACTION = 'readwrite', IOSTAT = ios, ERR = 987 ) 
     120               &       , RECL = irecl8, STATUS = TRIM(clstatus), ACTION = 'readwrite', IOSTAT = ios, ERR = 987 ) 
    114121         ELSE              ! the file should be open for read mode so it must exist... 
    115122            CALL ctl_stop( TRIM(clinfo), ' should be impossible case...' ) 
     
    118125      ! Performs checks on the file 
    119126      ! ============= 
    120       IF( ldok ) THEN      ! old file 
     127      IF( ldok .AND. .NOT. llclobber ) THEN      ! old file 
    121128         READ( idrst, REC = 1   , IOSTAT = ios, ERR = 987 )              & 
    122129              &   irecl8, inx, iny, inz, in0d, in1d, in2d, in3d, irhd,   & 
Note: See TracChangeset for help on using the changeset viewer.