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 for trunk/NEMO/OPA_SRC/IOM/iom_nf90.F90 – NEMO

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

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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) 
Note: See TracChangeset for help on using the changeset viewer.