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

Changeset 10522


Ignore:
Timestamp:
2019-01-16T09:35:15+01:00 (5 years ago)
Author:
smasson
Message:

trunk: replace iom_gettime by iom_getszuld, see #2212

Location:
NEMO/trunk/src
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/IOM/iom.F90

    r10425 r10522  
    1717   !!   iom_close      : close a file or all files opened by iom 
    1818   !!   iom_get        : read a field (interfaced to several routines) 
    19    !!   iom_gettime    : read the time axis cdvar in the file 
    2019   !!   iom_varid      : get the id of a variable in a file 
    2120   !!   iom_rstput     : write a field in a restart file (interfaced to several routines) 
     
    5857#endif 
    5958   PUBLIC iom_init, iom_swap, iom_open, iom_close, iom_setkt, iom_varid, iom_get 
    60    PUBLIC iom_chkatt, iom_getatt, iom_putatt, iom_gettime, iom_rstput, iom_delay_rst, iom_put 
     59   PUBLIC iom_chkatt, iom_getatt, iom_putatt, iom_getszuld, iom_rstput, iom_delay_rst, iom_put 
    6160   PUBLIC iom_use, iom_context_finalize 
    6261 
     
    13421341 
    13431342 
    1344    SUBROUTINE iom_gettime( kiomid, ptime, cdvar, kntime, cdunits, cdcalendar ) 
    1345       !!-------------------------------------------------------------------- 
    1346       !!                   ***  SUBROUTINE iom_gettime  *** 
    1347       !! 
    1348       !! ** Purpose : read the time axis cdvar in the file  
    1349       !!-------------------------------------------------------------------- 
    1350       INTEGER                    , INTENT(in   ) ::   kiomid     ! file Identifier 
    1351       REAL(wp), DIMENSION(:)     , INTENT(  out) ::   ptime      ! the time axis 
    1352       CHARACTER(len=*), OPTIONAL , INTENT(in   ) ::   cdvar      ! time axis name 
    1353       INTEGER         , OPTIONAL , INTENT(  out) ::   kntime     ! number of times in file 
    1354       CHARACTER(len=*), OPTIONAL , INTENT(  out) ::   cdunits    ! units attribute of time coordinate 
    1355       CHARACTER(len=*), OPTIONAL , INTENT(  out) ::   cdcalendar ! calendar attribute of  
    1356       ! 
    1357       INTEGER, DIMENSION(1) :: kdimsz 
    1358       INTEGER            ::   idvar    ! id of the variable 
    1359       CHARACTER(LEN=32)  ::   tname    ! local name of time coordinate 
    1360       CHARACTER(LEN=100) ::   clinfo   ! info character 
    1361       !--------------------------------------------------------------------- 
    1362       ! 
    1363       IF ( PRESENT(cdvar) ) THEN 
    1364          tname = cdvar 
    1365       ELSE 
    1366          tname = iom_file(kiomid)%uldname 
    1367       ENDIF 
     1343   FUNCTION iom_getszuld ( kiomid )   
     1344      !!----------------------------------------------------------------------- 
     1345      !!                  ***  FUNCTION  iom_getszuld  *** 
     1346      !! 
     1347      !! ** Purpose : get the size of the unlimited dimension in a file 
     1348      !!              (return -1 if not found) 
     1349      !!----------------------------------------------------------------------- 
     1350      INTEGER, INTENT(in   ) ::   kiomid   ! file Identifier 
     1351      ! 
     1352      INTEGER                ::   iom_getszuld 
     1353      !!----------------------------------------------------------------------- 
     1354      iom_getszuld = -1 
    13681355      IF( kiomid > 0 ) THEN 
    1369          clinfo = 'iom_gettime, file: '//trim(iom_file(kiomid)%name)//', var: '//trim(tname) 
    1370          IF ( PRESENT(kntime) ) THEN 
    1371             idvar  = iom_varid( kiomid, tname, kdimsz = kdimsz ) 
    1372             kntime = kdimsz(1) 
    1373          ELSE 
    1374             idvar = iom_varid( kiomid, tname ) 
     1356         IF( iom_file(kiomid)%iduld .GE. 0 ) THEN 
     1357            iom_getszuld = iom_file(kiomid)%lenuld 
    13751358         ENDIF 
    1376          ! 
    1377          ptime(:) = 0. ! default definition 
    1378          IF( idvar > 0 ) THEN 
    1379             IF( iom_file(kiomid)%ndims(idvar) == 1 ) THEN 
    1380                IF( iom_file(kiomid)%luld(idvar) ) THEN 
    1381                   IF( iom_file(kiomid)%dimsz(1,idvar) <= size(ptime) ) THEN 
    1382                      CALL iom_nf90_gettime(   kiomid, idvar, ptime, cdunits, cdcalendar ) 
    1383                   ELSE 
    1384                      WRITE(ctmp1,*) 'error with the size of ptime ',size(ptime),iom_file(kiomid)%dimsz(1,idvar) 
    1385                      CALL ctl_stop( trim(clinfo), trim(ctmp1) ) 
    1386                   ENDIF 
    1387                ELSE 
    1388                   CALL ctl_stop( trim(clinfo), 'variable dimension is not unlimited... use iom_get' ) 
    1389                ENDIF 
    1390             ELSE 
    1391                CALL ctl_stop( trim(clinfo), 'the variable has more than 1 dimension' ) 
    1392             ENDIF 
    1393          ELSE 
    1394             CALL ctl_stop( trim(clinfo), 'variable not found in '//iom_file(kiomid)%name ) 
    1395          ENDIF 
    1396       ENDIF 
    1397       ! 
    1398    END SUBROUTINE iom_gettime 
     1359      ENDIF 
     1360   END FUNCTION iom_getszuld 
     1361    
    13991362 
    14001363   !!---------------------------------------------------------------------- 
  • NEMO/trunk/src/OCE/IOM/iom_nf90.F90

    r10521 r10522  
    1515   !!   iom_close      : close a file or all files opened by iom 
    1616   !!   iom_get        : read a field (interfaced to several routines) 
    17    !!   iom_gettime    : read the time axis kvid in the file 
    1817   !!   iom_varid      : get the id of a variable in a file 
    1918   !!   iom_rstput     : write a field in a restart file (interfaced to several routines) 
     
    2928   PRIVATE 
    3029 
    31    PUBLIC iom_nf90_open  , iom_nf90_close, iom_nf90_varid, iom_nf90_get, iom_nf90_gettime, iom_nf90_rstput 
     30   PUBLIC iom_nf90_open  , iom_nf90_close, iom_nf90_varid, iom_nf90_get, iom_nf90_rstput 
    3231   PUBLIC iom_nf90_chkatt, iom_nf90_getatt, iom_nf90_putatt 
    3332 
     
    493492 
    494493 
    495    SUBROUTINE iom_nf90_gettime( kiomid, kvid, ptime, cdunits, cdcalendar ) 
    496       !!-------------------------------------------------------------------- 
    497       !!                   ***  SUBROUTINE iom_gettime  *** 
    498       !! 
    499       !! ** Purpose : read the time axis kvid in the file with NF90 
    500       !!-------------------------------------------------------------------- 
    501       INTEGER                   , INTENT(in   ) ::   kiomid     ! file Identifier 
    502       INTEGER                   , INTENT(in   ) ::   kvid       ! variable id 
    503       REAL(wp), DIMENSION(:)    , INTENT(  out) ::   ptime      ! the time axis 
    504       CHARACTER(len=*), OPTIONAL, INTENT(  out) ::   cdunits    ! units attribute 
    505       CHARACTER(len=*), OPTIONAL, INTENT(  out) ::   cdcalendar ! calendar attribute 
    506       ! 
    507       CHARACTER(LEN=100) ::   clinfo     ! info character 
    508       !--------------------------------------------------------------------- 
    509       clinfo = 'iom_nf90_gettime, file: '//TRIM(iom_file(kiomid)%name)//', var: '//TRIM(iom_file(kiomid)%cn_var(kvid)) 
    510       CALL iom_nf90_check(NF90_GET_VAR(iom_file(kiomid)%nfid, iom_file(kiomid)%nvid(kvid), ptime(:),   & 
    511             &                           start=(/ 1 /), count=(/ iom_file(kiomid)%dimsz(1, kvid) /)), clinfo) 
    512       IF ( PRESENT(cdunits) ) THEN  
    513          CALL iom_nf90_check(NF90_GET_ATT(iom_file(kiomid)%nfid, iom_file(kiomid)%nvid(kvid), "units", & 
    514             &                           values=cdunits), clinfo) 
    515       ENDIF 
    516       IF ( PRESENT(cdcalendar) ) THEN  
    517          CALL iom_nf90_check(NF90_GET_ATT(iom_file(kiomid)%nfid, iom_file(kiomid)%nvid(kvid), "calendar", & 
    518             &                           values=cdcalendar), clinfo) 
    519       ENDIF 
    520       ! 
    521    END SUBROUTINE iom_nf90_gettime 
    522  
    523  
    524494   SUBROUTINE iom_nf90_rp0123d( kt, kwrite, kiomid, cdvar , kvid  , ktype,   & 
    525495         &                                  pv_r0d, pv_r1d, pv_r2d, pv_r3d ) 
  • NEMO/trunk/src/OCE/SBC/sbcrnf.F90

    r10425 r10522  
    240240      INTEGER           ::   nbrec         ! temporary integer 
    241241      REAL(wp)          ::   zacoef   
    242       REAL(wp), DIMENSION(12)                 :: zrec             ! times records 
    243242      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zrnfcl     
    244243      REAL(wp), DIMENSION(:,:  ), ALLOCATABLE :: zrnf 
     
    372371 
    373372         CALL iom_open( TRIM( sn_rnf%clname ), inum )    !  open runoff file 
    374          CALL iom_gettime( inum, zrec, kntime=nbrec) 
     373         nbrec = iom_getszuld( inum ) 
    375374         ALLOCATE( zrnfcl(jpi,jpj,nbrec) )     ;      ALLOCATE( zrnf(jpi,jpj) ) 
    376375         DO jm = 1, nbrec 
  • NEMO/trunk/src/TOP/PISCES/P4Z/p4zopt.F90

    r10425 r10522  
    389389      !!---------------------------------------------------------------------- 
    390390      INTEGER :: numpar, ierr, ios   ! Local integer  
    391       REAL(wp), DIMENSION(nbtimes) ::   zsteps   ! times records 
    392391      ! 
    393392      CHARACTER(len=100) ::  cn_dir          ! Root directory for location of ssr files 
     
    434433 
    435434         CALL iom_open (  TRIM( sn_par%clname ) , numpar ) 
    436          CALL iom_gettime( numpar, zsteps, kntime=ntimes_par)  ! get number of record in file 
     435         ntimes_par = iom_getszuld( numpar )   ! get number of record in file 
    437436      ENDIF 
    438437      ! 
  • NEMO/trunk/src/TOP/PISCES/P4Z/p4zsbc.F90

    r10425 r10522  
    211211      REAL(wp) :: zexpide, zdenitide, zmaskt, zsurfc, zsurfp,ze3t, ze3t2, zcslp 
    212212      REAL(wp) :: ztimes_dust, ztimes_riv, ztimes_ndep  
    213       REAL(wp), DIMENSION(nbtimes) :: zsteps                 ! times records 
    214213      REAL(wp), DIMENSION(:), ALLOCATABLE :: rivinput 
    215214      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zriver, zcmask 
     
    309308            ! Get total input dust ; need to compute total atmospheric supply of Si in a year 
    310309            CALL iom_open (  TRIM( sn_dust%clname ) , numdust ) 
    311             CALL iom_gettime( numdust, zsteps, kntime=ntimes_dust)  ! get number of record in file 
     310            ntimes_dust = iom_getszuld( numdust )   ! get number of record in file 
    312311         END IF 
    313312      END IF 
     
    331330         ! get number of record in file 
    332331         CALL iom_open (  TRIM( sn_solub%clname ) , numsolub ) 
    333          CALL iom_gettime( numsolub, zsteps, kntime=ntimes_solub)  ! get number of record in file 
     332         ntimes_solub = iom_getszuld( numsolub )   ! get number of record in file 
    334333         CALL iom_close( numsolub ) 
    335334      ENDIF 
     
    360359            DO ifpr = 1, jpriv 
    361360               CALL iom_open ( TRIM( slf_river(ifpr)%clname ), numriv ) 
    362                CALL iom_gettime( numriv, zsteps, kntime=ntimes_riv) 
     361               ntimes_riv = iom_getszuld( numriv ) 
    363362               ALLOCATE( zriver(jpi,jpj,ntimes_riv) ) 
    364363               DO jm = 1, ntimes_riv 
     
    407406            ! Get total input dust ; need to compute total atmospheric supply of N in a year 
    408407            CALL iom_open ( TRIM( sn_ndepo%clname ), numdepo ) 
    409             CALL iom_gettime( numdepo, zsteps, kntime=ntimes_ndep) 
     408            ntimes_ndep = iom_getszuld( numdepo ) 
    410409         ENDIF 
    411410      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.