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 10380 for NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/OCE/IOM/iom_nf90.F90 – NEMO

Ignore:
Timestamp:
2018-12-11T09:27:54+01:00 (5 years ago)
Author:
smasson
Message:

dev_r10164_HPC09_ESIWACE_PREP_MERGE: iom cleaning: (1) get rid of jpnf90, jprstlib, jlibalt, iolib and (2) improve iom_getatt and iom_putatt, see #2133

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/OCE/IOM/iom_nf90.F90

    r10377 r10380  
    3434   INTERFACE iom_nf90_get 
    3535      MODULE PROCEDURE iom_nf90_g0d, iom_nf90_g123d 
    36    END INTERFACE 
    37    INTERFACE iom_nf90_getatt 
    38       MODULE PROCEDURE iom_nf90_giatt, iom_nf90_gratt, iom_nf90_gcatt 
    39    END INTERFACE 
    40    INTERFACE iom_nf90_putatt 
    41       MODULE PROCEDURE iom_nf90_piatt, iom_nf90_pratt, iom_nf90_pcatt 
    4236   END INTERFACE 
    4337   INTERFACE iom_nf90_rstput 
     
    163157         iom_file(kiomid)%name   = TRIM(cdname) 
    164158         iom_file(kiomid)%nfid   = if90id 
    165          iom_file(kiomid)%iolib  = jpnf90 
    166159         iom_file(kiomid)%nvars  = 0 
    167160         iom_file(kiomid)%irec   = -1   ! useless for NetCDF files, used to know if the file is in define mode  
     
    327320   END SUBROUTINE iom_nf90_g123d 
    328321 
    329    !!---------------------------------------------------------------------- 
    330    !!                   INTERFACE iom_nf90_getatt 
    331    !!---------------------------------------------------------------------- 
    332  
    333    SUBROUTINE iom_nf90_giatt( kiomid, cdatt, pv_i0d, cdvar) 
    334       !!----------------------------------------------------------------------- 
    335       !!                  ***  ROUTINE  iom_nf90_giatt  *** 
    336       !! 
    337       !! ** Purpose : read an integer attribute with NF90 
     322 
     323   SUBROUTINE iom_nf90_getatt( kiomid, cdatt, katt0d, katt1d, patt0d, patt1d, cdatt0d, cdvar) 
     324      !!----------------------------------------------------------------------- 
     325      !!                  ***  ROUTINE  iom_nf90_getatt  *** 
     326      !! 
     327      !! ** Purpose : read an attribute with NF90 
    338328      !!              (either a global attribute (default) or a variable 
    339329      !!               attribute if optional variable name is supplied (cdvar)) 
    340330      !!----------------------------------------------------------------------- 
    341       INTEGER         , INTENT(in   ) ::   kiomid   ! Identifier of the file 
    342       CHARACTER(len=*), INTENT(in   ) ::   cdatt    ! attribute name 
    343       INTEGER         , INTENT(  out) ::   pv_i0d   ! read field 
    344       CHARACTER(len=*), INTENT(in   ), OPTIONAL     & 
    345                       &               ::   cdvar    ! name of the variable 
     331      INTEGER               , INTENT(in   )           ::   kiomid   ! Identifier of the file 
     332      CHARACTER(len=*)      , INTENT(in   )           ::   cdatt    ! attribute name 
     333      INTEGER               , INTENT(  out), OPTIONAL ::   katt0d   ! read scalar integer 
     334      INTEGER, DIMENSION(:) , INTENT(  out), OPTIONAL ::   katt1d   ! read 1d array integer 
     335      REAL(wp)              , INTENT(  out), OPTIONAL ::   patt0d   ! read scalar  real 
     336      REAL(wp), DIMENSION(:), INTENT(  out), OPTIONAL ::   patt1d   ! read 1d array real 
     337      CHARACTER(len=*)      , INTENT(  out), OPTIONAL ::   cdatt0d  ! read character 
     338      CHARACTER(len=*)      , INTENT(in   ), OPTIONAL ::   cdvar    ! name of the variable 
    346339      ! 
    347340      INTEGER                         ::   if90id   ! temporary integer 
     
    359352            llok = NF90_Inquire_attribute(if90id, ivarid, cdatt) == nf90_noerr 
    360353         ELSE 
    361             CALL ctl_warn('iom_nf90_getatt: no variable '//cdvar//' found') 
     354            CALL ctl_warn('iom_nf90_getatt: no variable '//TRIM(cdvar)//' found') 
    362355         ENDIF 
    363356      ELSE 
     
    367360      ! 
    368361      IF( llok) THEN 
    369          clinfo = 'iom_nf90_getatt, file: '//TRIM(iom_file(kiomid)%name)//', giatt: '//TRIM(cdatt) 
    370          CALL iom_nf90_check(NF90_GET_ATT(if90id, ivarid, cdatt, values=pv_i0d), clinfo) 
     362         clinfo = 'iom_nf90_getatt, file: '//TRIM(iom_file(kiomid)%name)//', att: '//TRIM(cdatt) 
     363         IF(PRESENT( katt0d))   CALL iom_nf90_check(NF90_GET_ATT(if90id, ivarid, cdatt, values =  katt0d), clinfo) 
     364         IF(PRESENT( katt1d))   CALL iom_nf90_check(NF90_GET_ATT(if90id, ivarid, cdatt, values =  katt1d), clinfo) 
     365         IF(PRESENT( patt0d))   CALL iom_nf90_check(NF90_GET_ATT(if90id, ivarid, cdatt, values =  patt0d), clinfo) 
     366         IF(PRESENT( patt1d))   CALL iom_nf90_check(NF90_GET_ATT(if90id, ivarid, cdatt, values =  patt1d), clinfo) 
     367         IF(PRESENT(cdatt0d))   CALL iom_nf90_check(NF90_GET_ATT(if90id, ivarid, cdatt, values = cdatt0d), clinfo) 
    371368      ELSE 
    372          CALL ctl_warn('iom_nf90_getatt: no attribute '//cdatt//' found') 
    373          pv_i0d = -999 
    374       ENDIF 
    375       ! 
    376    END SUBROUTINE iom_nf90_giatt 
    377  
    378  
    379    SUBROUTINE iom_nf90_gratt( kiomid, cdatt, pv_r0d, cdvar ) 
    380       !!----------------------------------------------------------------------- 
    381       !!                  ***  ROUTINE  iom_nf90_gratt  *** 
    382       !! 
    383       !! ** Purpose : read a real attribute with NF90 
     369         CALL ctl_warn('iom_nf90_getatt: no attribute '//TRIM(cdatt)//' found') 
     370         IF(PRESENT( katt0d))    katt0d    = -999 
     371         IF(PRESENT( katt1d))    katt1d(:) = -999 
     372         IF(PRESENT( patt0d))    patt0d    = -999._wp 
     373         IF(PRESENT( patt1d))    patt1d(:) = -999._wp 
     374         IF(PRESENT(cdatt0d))   cdatt0d    = '!' 
     375      ENDIF 
     376      ! 
     377   END SUBROUTINE iom_nf90_getatt 
     378 
     379 
     380   SUBROUTINE iom_nf90_putatt( kiomid, cdatt, katt0d, katt1d, patt0d, patt1d, cdatt0d, cdvar) 
     381      !!----------------------------------------------------------------------- 
     382      !!                  ***  ROUTINE  iom_nf90_putatt  *** 
     383      !! 
     384      !! ** Purpose : write an attribute with NF90 
    384385      !!              (either a global attribute (default) or a variable 
    385386      !!               attribute if optional variable name is supplied (cdvar)) 
    386387      !!----------------------------------------------------------------------- 
    387       INTEGER                   , INTENT(in   ) ::   kiomid   ! Identifier of the file 
    388       CHARACTER(len=*)          , INTENT(in   ) ::   cdatt    ! attribute name 
    389       REAL(wp)                  , INTENT(  out) ::   pv_r0d   ! read field 
    390       CHARACTER(len=*), OPTIONAL, INTENT(in   ) ::   cdvar    ! name of the variable 
    391       ! 
    392       INTEGER            ::   if90id   ! temporary integer 
    393       INTEGER            ::   ivarid   ! NetCDF variable Id 
    394       LOGICAL            ::   llok     ! temporary logical 
    395       CHARACTER(LEN=100) ::   clinfo   ! info character 
    396       !--------------------------------------------------------------------- 
    397       ! 
    398       if90id = iom_file(kiomid)%nfid 
    399       IF( PRESENT(cdvar) ) THEN 
    400          ! check the variable exists in the file 
    401          llok = NF90_INQ_VARID( if90id, TRIM(cdvar), ivarid ) == nf90_noerr 
    402          IF( llok ) THEN 
    403             ! check the variable has the attribute required 
    404             llok = NF90_Inquire_attribute(if90id, ivarid, cdatt) == nf90_noerr 
    405          ELSE 
    406             CALL ctl_warn('iom_nf90_getatt: no variable '//cdvar//' found') 
    407          ENDIF 
    408       ELSE 
    409          llok = NF90_Inquire_attribute(if90id, NF90_GLOBAL, cdatt) == nf90_noerr 
    410          ivarid = NF90_GLOBAL 
    411       ENDIF 
    412       ! 
    413       IF( llok) THEN 
    414          clinfo = 'iom_nf90_getatt, file: '//TRIM(iom_file(kiomid)%name)//', gratt: '//TRIM(cdatt) 
    415          CALL iom_nf90_check(NF90_GET_ATT(if90id, ivarid, cdatt, values=pv_r0d), clinfo) 
    416       ELSE 
    417          CALL ctl_warn('iom_nf90_getatt: no attribute '//cdatt//' found') 
    418          pv_r0d = -999._wp 
    419       ENDIF 
    420       ! 
    421    END SUBROUTINE iom_nf90_gratt 
    422  
    423  
    424    SUBROUTINE iom_nf90_gcatt( kiomid, cdatt, pv_c0d, cdvar ) 
    425       !!----------------------------------------------------------------------- 
    426       !!                  ***  ROUTINE  iom_nf90_gcatt  *** 
    427       !! 
    428       !! ** Purpose : read a character attribute with NF90 
    429       !!              (either a global attribute (default) or a variable 
    430       !!               attribute if optional variable name is supplied (cdvar)) 
    431       !!----------------------------------------------------------------------- 
    432       INTEGER                   , INTENT(in   ) ::   kiomid   ! Identifier of the file 
    433       CHARACTER(len=*)          , INTENT(in   ) ::   cdatt    ! attribute name 
    434       CHARACTER(len=*)          , INTENT(  out) ::   pv_c0d   ! read field 
    435       CHARACTER(len=*), OPTIONAL, INTENT(in   ) ::   cdvar    ! name of the variable 
    436       ! 
    437       INTEGER            ::   if90id   ! temporary integer 
    438       INTEGER            ::   ivarid   ! NetCDF variable Id 
    439       LOGICAL            ::   llok     ! temporary logical 
    440       CHARACTER(LEN=100) ::   clinfo   ! info character 
    441       !--------------------------------------------------------------------- 
    442       ! 
    443       if90id = iom_file(kiomid)%nfid 
    444       IF( PRESENT(cdvar) ) THEN 
    445          ! check the variable exists in the file 
    446          llok = NF90_INQ_VARID( if90id, TRIM(cdvar), ivarid ) == nf90_noerr 
    447          IF( llok ) THEN 
    448             ! check the variable has the attribute required 
    449             llok = NF90_Inquire_attribute(if90id, ivarid, cdatt) == nf90_noerr 
    450          ELSE 
    451             CALL ctl_warn('iom_nf90_getatt: no variable '//cdvar//' found') 
    452          ENDIF 
    453       ELSE 
    454          llok = NF90_Inquire_attribute(if90id, NF90_GLOBAL, cdatt) == nf90_noerr 
    455          ivarid = NF90_GLOBAL 
    456       ENDIF 
    457 ! 
    458       IF( llok) THEN 
    459          clinfo = 'iom_nf90_getatt, file: '//TRIM(iom_file(kiomid)%name)//', gcatt: '//TRIM(cdatt) 
    460          CALL iom_nf90_check(NF90_GET_ATT(if90id, ivarid, cdatt, values=pv_c0d), clinfo) 
    461       ELSE 
    462          CALL ctl_warn('iom_nf90_getatt: no attribute '//cdatt//' found') 
    463          pv_c0d = '!' 
    464       ENDIF 
    465       ! 
    466    END SUBROUTINE iom_nf90_gcatt 
    467  
    468  
    469    !!---------------------------------------------------------------------- 
    470    !!                   INTERFACE iom_nf90_putatt 
    471    !!---------------------------------------------------------------------- 
    472  
    473    SUBROUTINE iom_nf90_piatt( kiomid, cdatt, pv_i0d, cdvar) 
    474       !!----------------------------------------------------------------------- 
    475       !!                  ***  ROUTINE  iom_nf90_piatt  *** 
    476       !! 
    477       !! ** Purpose : write an integer attribute with NF90 
    478       !!              (either a global attribute (default) or a variable 
    479       !!               attribute if optional variable name is supplied (cdvar)) 
    480       !!----------------------------------------------------------------------- 
    481       INTEGER         , INTENT(in   ) ::   kiomid   ! Identifier of the file 
    482       CHARACTER(len=*), INTENT(in   ) ::   cdatt    ! attribute name 
    483       INTEGER         , INTENT(in   ) ::   pv_i0d   ! write field 
    484       CHARACTER(len=*), INTENT(in   ), OPTIONAL     & 
    485                       &               ::   cdvar    ! name of the variable 
     388      INTEGER               , INTENT(in   )           ::   kiomid   ! Identifier of the file 
     389      CHARACTER(len=*)      , INTENT(in   )           ::   cdatt    ! attribute name 
     390      INTEGER               , INTENT(in   ), OPTIONAL ::   katt0d   ! read scalar integer 
     391      INTEGER, DIMENSION(:) , INTENT(in   ), OPTIONAL ::   katt1d   ! read 1d array integer 
     392      REAL(wp)              , INTENT(in   ), OPTIONAL ::   patt0d   ! read scalar  real 
     393      REAL(wp), DIMENSION(:), INTENT(in   ), OPTIONAL ::   patt1d   ! read 1d array real 
     394      CHARACTER(len=*)      , INTENT(in   ), OPTIONAL ::   cdatt0d  ! read character 
     395      CHARACTER(len=*)      , INTENT(in   ), OPTIONAL ::   cdvar    ! name of the variable 
    486396      ! 
    487397      INTEGER                         ::   if90id   ! temporary integer 
     
    498408         llok = NF90_INQ_VARID( if90id, TRIM(cdvar), ivarid ) == nf90_noerr 
    499409         IF( .NOT. llok ) THEN 
    500             CALL ctl_warn('iom_nf90_putatt: no variable '//cdvar//' found') 
     410            CALL ctl_warn('iom_nf90_putatt: no variable '//TRIM(cdvar)//' found') 
    501411         ENDIF 
    502412      ELSE 
     
    506416      ! 
    507417      IF( llok) THEN 
    508          clinfo = 'iom_nf90_putatt, file: '//TRIM(iom_file(kiomid)%name)//', piatt: '//TRIM(cdatt) 
     418         clinfo = 'iom_nf90_putatt, file: '//TRIM(iom_file(kiomid)%name)//', att: '//TRIM(cdatt) 
    509419         IF( iom_file(kiomid)%irec /= -1 ) THEN    
    510420            ! trick: irec used to know if the file is in define mode or not 
     
    514424         ENDIF 
    515425         ! 
    516          CALL iom_nf90_check(NF90_PUT_ATT(if90id, ivarid, cdatt, values=pv_i0d), clinfo) 
     426         IF(PRESENT( katt0d))   CALL iom_nf90_check(NF90_PUT_ATT(if90id, ivarid, cdatt, values =  katt0d), clinfo) 
     427         IF(PRESENT( katt1d))   CALL iom_nf90_check(NF90_PUT_ATT(if90id, ivarid, cdatt, values =  katt1d), clinfo) 
     428         IF(PRESENT( patt0d))   CALL iom_nf90_check(NF90_PUT_ATT(if90id, ivarid, cdatt, values =  patt0d), clinfo) 
     429         IF(PRESENT( patt1d))   CALL iom_nf90_check(NF90_PUT_ATT(if90id, ivarid, cdatt, values =  patt1d), clinfo) 
     430         IF(PRESENT(cdatt0d))   CALL iom_nf90_check(NF90_PUT_ATT(if90id, ivarid, cdatt, values = cdatt0d), clinfo) 
    517431         ! 
    518          IF( lenddef ) THEN    
    519             ! file was in data mode on entry; put it back in that mode 
     432         IF( lenddef ) THEN   ! file was in data mode on entry; put it back in that mode 
    520433            CALL iom_nf90_check(NF90_ENDDEF( if90id ), clinfo) 
    521434         ENDIF 
    522435      ELSE 
    523          CALL ctl_warn('iom_nf90_putatt: no attribute '//cdatt//' written') 
    524       ENDIF 
    525       ! 
    526    END SUBROUTINE iom_nf90_piatt 
    527  
    528  
    529    SUBROUTINE iom_nf90_pratt( kiomid, cdatt, pv_r0d, cdvar ) 
    530       !!----------------------------------------------------------------------- 
    531       !!                  ***  ROUTINE  iom_nf90_pratt  *** 
    532       !! 
    533       !! ** Purpose : write a real attribute with NF90 
    534       !!              (either a global attribute (default) or a variable 
    535       !!               attribute if optional variable name is supplied (cdvar)) 
    536       !!----------------------------------------------------------------------- 
    537       INTEGER                   , INTENT(in   ) ::   kiomid   ! Identifier of the file 
    538       CHARACTER(len=*)          , INTENT(in   ) ::   cdatt    ! attribute name 
    539       REAL(wp)                  , INTENT(in   ) ::   pv_r0d   ! write field 
    540       CHARACTER(len=*), OPTIONAL, INTENT(in   ) ::   cdvar    ! name of the variable 
    541       ! 
    542       INTEGER            ::   if90id   ! temporary integer 
    543       INTEGER            ::   ivarid   ! NetCDF variable Id 
    544       LOGICAL            ::   llok     ! temporary logical 
    545       LOGICAL            ::   lenddef  ! temporary logical 
    546       CHARACTER(LEN=100) ::   clinfo   ! info character 
    547       !--------------------------------------------------------------------- 
    548       ! 
    549       if90id = iom_file(kiomid)%nfid 
    550       lenddef = .false. 
    551       IF( PRESENT(cdvar) ) THEN 
    552          ! check the variable exists in the file 
    553          llok = NF90_INQ_VARID( if90id, TRIM(cdvar), ivarid ) == nf90_noerr 
    554          IF( .NOT. llok ) THEN 
    555             CALL ctl_warn('iom_nf90_putatt: no variable '//cdvar//' found') 
    556          ENDIF 
    557       ELSE 
    558          llok = .true. 
    559          ivarid = NF90_GLOBAL 
    560       ENDIF 
    561       ! 
    562       IF( llok) THEN 
    563          clinfo = 'iom_nf90_putatt, file: '//TRIM(iom_file(kiomid)%name)//', pratt: '//TRIM(cdatt) 
    564          IF( iom_file(kiomid)%irec /= -1 ) THEN    
    565             ! trick: irec used to know if the file is in define mode or not 
    566             ! if it is not then temporarily put it into define mode 
    567             CALL iom_nf90_check(NF90_REDEF( if90id ), clinfo) 
    568             lenddef = .true. 
    569          ENDIF 
    570          ! 
    571          CALL iom_nf90_check(NF90_PUT_ATT(if90id, ivarid, cdatt, values=pv_r0d), clinfo) 
    572          ! 
    573          IF( lenddef ) THEN    
    574             ! file was in data mode on entry; put it back in that mode 
    575             CALL iom_nf90_check(NF90_ENDDEF( if90id ), clinfo) 
    576          ENDIF 
    577       ELSE 
    578          CALL ctl_warn('iom_nf90_putatt: no attribute '//cdatt//' written') 
    579       ENDIF 
    580       ! 
    581    END SUBROUTINE iom_nf90_pratt 
    582  
    583  
    584    SUBROUTINE iom_nf90_pcatt( kiomid, cdatt, pv_c0d, cdvar ) 
    585       !!----------------------------------------------------------------------- 
    586       !!                  ***  ROUTINE  iom_nf90_pcatt  *** 
    587       !! 
    588       !! ** Purpose : write a character attribute with NF90 
    589       !!              (either a global attribute (default) or a variable 
    590       !!               attribute if optional variable name is supplied (cdvar)) 
    591       !!----------------------------------------------------------------------- 
    592       INTEGER                   , INTENT(in   ) ::   kiomid   ! Identifier of the file 
    593       CHARACTER(len=*)          , INTENT(in   ) ::   cdatt    ! attribute name 
    594       CHARACTER(len=*)          , INTENT(in   ) ::   pv_c0d   ! write field 
    595       CHARACTER(len=*), OPTIONAL, INTENT(in   ) ::   cdvar    ! name of the variable 
    596       ! 
    597       INTEGER            ::   if90id   ! temporary integer 
    598       INTEGER            ::   ivarid   ! NetCDF variable Id 
    599       LOGICAL            ::   llok     ! temporary logical 
    600       LOGICAL            ::   lenddef  ! temporary logical 
    601       CHARACTER(LEN=100) ::   clinfo   ! info character 
    602       !--------------------------------------------------------------------- 
    603       ! 
    604       if90id = iom_file(kiomid)%nfid 
    605       lenddef = .false. 
    606       IF( PRESENT(cdvar) ) THEN 
    607          ! check the variable exists in the file 
    608          llok = NF90_INQ_VARID( if90id, TRIM(cdvar), ivarid ) == nf90_noerr 
    609          IF( .NOT. llok ) THEN 
    610             CALL ctl_warn('iom_nf90_putatt: no variable '//cdvar//' found') 
    611          ENDIF 
    612       ELSE 
    613          llok = .true. 
    614          ivarid = NF90_GLOBAL 
    615       ENDIF 
    616       ! 
    617       IF( llok) THEN 
    618          clinfo = 'iom_nf90_putatt, file: '//TRIM(iom_file(kiomid)%name)//', pcatt: '//TRIM(cdatt) 
    619          IF( iom_file(kiomid)%irec /= -1 ) THEN    
    620             ! trick: irec used to know if the file is in define mode or not 
    621             ! if it is not then temporarily put it into define mode 
    622             CALL iom_nf90_check(NF90_REDEF( if90id ), clinfo) 
    623             lenddef = .true. 
    624          ENDIF 
    625          ! 
    626          CALL iom_nf90_check(NF90_PUT_ATT(if90id, ivarid, cdatt, values=pv_c0d), clinfo) 
    627          ! 
    628          IF( lenddef ) THEN    
    629             ! file was in data mode on entry; put it back in that mode 
    630             CALL iom_nf90_check(NF90_ENDDEF( if90id ), clinfo) 
    631          ENDIF 
    632       ELSE 
    633          CALL ctl_warn('iom_nf90_putatt: no attribute '//cdatt//' written') 
    634       ENDIF 
    635       ! 
    636    END SUBROUTINE iom_nf90_pcatt 
     436         CALL ctl_warn('iom_nf90_putatt: no attribute '//TRIM(cdatt)//' written') 
     437      ENDIF 
     438      ! 
     439   END SUBROUTINE iom_nf90_putatt 
    637440 
    638441 
Note: See TracChangeset for help on using the changeset viewer.