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 15254 for branches/UKMO/dev_r5518_obs_oper_update/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90 – NEMO

Ignore:
Timestamp:
2021-09-14T13:37:21+02:00 (3 years ago)
Author:
jroberts
Message:

Changes manually merged from https://forge.ipsl.jussieu.fr/nemo/browser/branches/UKMO/dev_r5518_GO6_package_STARTHOUR?

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_obs_oper_update/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r14591 r15254  
    1212   !!   ini_date     : Compute the initial date YYYYMMDD.HHMMSS 
    1313   !!   fin_date     : Compute the final date YYYYMMDD.HHMMSS 
     14   !!   calc_date    : Get date in YYYYMMDD.HHMMSS format 
    1415   !!---------------------------------------------------------------------- 
    1516   !! * Modules used 
     
    4041   !! * Routine accessibility 
    4142   PRIVATE 
    42    PUBLIC dia_obs_init, &  ! Initialize and read observations 
    43       &   dia_obs,      &  ! Compute model equivalent to observations 
    44       &   dia_obs_wri,  &  ! Write model equivalent to observations 
    45       &   dia_obs_dealloc  ! Deallocate dia_obs data 
     43   PUBLIC dia_obs_init,    &  ! Initialize and read observations 
     44      &   dia_obs,         &  ! Compute model equivalent to observations 
     45      &   dia_obs_wri,     &  ! Write model equivalent to observations 
     46      &   dia_obs_dealloc, &  ! Deallocate dia_obs data 
     47      &   calc_date           ! Compute the date of a timestep 
    4648 
    4749   !! * Module variables 
     
    20142016   END SUBROUTINE dia_obs_dealloc 
    20152017 
    2016    SUBROUTINE ini_date( ddobsini ) 
     2018   SUBROUTINE calc_date( kstp, ddobs ) 
    20172019      !!---------------------------------------------------------------------- 
    2018       !!                    ***  ROUTINE ini_date  *** 
     2020      !!                    ***  ROUTINE calc_date  *** 
     2021      !!          
     2022      !! ** Purpose : Get date in double precision YYYYMMDD.HHMMSS format 
    20192023      !! 
    2020       !! ** Purpose : Get initial date in double precision YYYYMMDD.HHMMSS format 
     2024      !! ** Method  : Get date in double precision YYYYMMDD.HHMMSS format 
    20212025      !! 
    2022       !! ** Method  : Get initial date in double precision YYYYMMDD.HHMMSS format 
    2023       !! 
    2024       !! ** Action  : Get initial date in double precision YYYYMMDD.HHMMSS format 
     2026      !! ** Action  : Get date in double precision YYYYMMDD.HHMMSS format 
    20252027      !! 
    20262028      !! History : 
     
    20302032      !!        !  06-10  (G. Smith) Calculates initial date the same as method for final date 
    20312033      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
     2034      !!        !  2014-09  (D. Lea) New generic routine now deals with arbitrary initial time of day 
    20322035      !!---------------------------------------------------------------------- 
    20332036      USE phycst, ONLY : &            ! Physical constants 
    20342037         & rday 
     2038!      USE daymod, ONLY : &            ! Time variables 
     2039!         & nmonth_len            
    20352040      USE dom_oce, ONLY : &           ! Ocean space and time domain variables 
    20362041         & rdt 
    2037  
    20382042      IMPLICIT NONE 
    2039  
    20402043      !! * Arguments 
    2041       REAL(dp), INTENT(OUT) :: ddobsini  ! Initial date in YYYYMMDD.HHMMSS 
    2042  
     2044      REAL(KIND=dp), INTENT(OUT) :: ddobs                        ! Date in YYYYMMDD.HHMMSS 
     2045      INTEGER :: kstp 
    20432046      !! * Local declarations 
    20442047      INTEGER :: iyea        ! date - (year, month, day, hour, minute) 
     
    20472050      INTEGER :: ihou 
    20482051      INTEGER :: imin 
    2049       INTEGER :: imday       ! Number of days in month. 
    2050       INTEGER, DIMENSION(12) :: & 
    2051          &       imonth_len  ! Length in days of the months of the current year 
    2052       REAL(wp) :: zdayfrc    ! Fraction of day 
    2053  
    2054       !---------------------------------------------------------------------- 
    2055       ! Initial date initialization (year, month, day, hour, minute) 
    2056       ! (This assumes that the initial date is for 00z)) 
    2057       !---------------------------------------------------------------------- 
     2052      INTEGER :: imday         ! Number of days in month. 
     2053      REAL(KIND=wp) :: zdayfrc ! Fraction of day 
     2054      INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
     2055      !!---------------------------------------------------------------------- 
     2056      !! Initial date initialization (year, month, day, hour, minute) 
     2057      !!---------------------------------------------------------------------- 
    20582058      iyea =   ndate0 / 10000 
    20592059      imon = ( ndate0 - iyea * 10000 ) / 100 
    20602060      iday =   ndate0 - iyea * 10000 - imon * 100 
    2061       ihou = 0 
    2062       imin = 0 
    2063  
    2064       !---------------------------------------------------------------------- 
    2065       ! Compute number of days + number of hours + min since initial time 
    2066       !---------------------------------------------------------------------- 
    2067       iday = iday + ( nit000 -1 ) * rdt / rday 
    2068       zdayfrc = ( nit000 -1 ) * rdt / rday 
     2061      ihou =   nn_time0 / 100 
     2062      imin = ( nn_time0 - ihou * 100 )  
     2063      !!---------------------------------------------------------------------- 
     2064      !! Compute number of days + number of hours + min since initial time 
     2065      !!---------------------------------------------------------------------- 
     2066      zdayfrc = kstp * rdt / rday 
    20692067      zdayfrc = zdayfrc - aint(zdayfrc) 
    2070       ihou = int( zdayfrc * 24 ) 
    2071       imin = int( (zdayfrc * 24 - ihou) * 60 ) 
    2072  
    2073       !----------------------------------------------------------------------- 
    2074       ! Convert number of days (iday) into a real date 
    2075       !---------------------------------------------------------------------- 
    2076  
     2068      imin = imin + int( zdayfrc * 24 * 60 )  
     2069      DO WHILE (imin >= 60)  
     2070        imin=imin-60 
     2071        ihou=ihou+1 
     2072      END DO 
     2073      DO WHILE (ihou >= 24) 
     2074        ihou=ihou-24 
     2075        iday=iday+1 
     2076      END DO 
     2077      iday = iday + kstp * rdt / rday  
     2078      !!----------------------------------------------------------------------- 
     2079      !! Convert number of days (iday) into a real date 
     2080      !!---------------------------------------------------------------------- 
    20772081      CALL calc_month_len( iyea, imonth_len ) 
    2078  
     2082      
    20792083      DO WHILE ( iday > imonth_len(imon) ) 
    20802084         iday = iday - imonth_len(imon) 
     
    20862090         ENDIF 
    20872091      END DO 
    2088  
    2089       !---------------------------------------------------------------------- 
    2090       ! Convert it into YYYYMMDD.HHMMSS format. 
    2091       !---------------------------------------------------------------------- 
    2092       ddobsini = iyea * 10000_dp + imon * 100_dp + & 
    2093          &       iday + ihou * 0.01_dp + imin * 0.0001_dp 
    2094  
    2095  
     2092      !!---------------------------------------------------------------------- 
     2093      !! Convert it into YYYYMMDD.HHMMSS format. 
     2094      !!---------------------------------------------------------------------- 
     2095      ddobs = iyea * 10000_dp + imon * 100_dp + & 
     2096         &    iday + ihou * 0.01_dp + imin * 0.0001_dp 
     2097   END SUBROUTINE calc_date 
     2098 
     2099   SUBROUTINE ini_date( ddobsini ) 
     2100      !!---------------------------------------------------------------------- 
     2101      !!                    ***  ROUTINE ini_date  *** 
     2102      !!          
     2103      !! ** Purpose : Get initial data in double precision YYYYMMDD.HHMMSS format 
     2104      !! 
     2105      !! ** Method  : Get initial data in double precision YYYYMMDD.HHMMSS format 
     2106      !! 
     2107      !! ** Action  : Get initial data in double precision YYYYMMDD.HHMMSS format 
     2108      !! 
     2109      !! History : 
     2110      !!        !  06-03  (K. Mogensen)  Original code 
     2111      !!        !  06-05  (K. Mogensen)  Reformatted 
     2112      !!        !  06-10  (A. Weaver) Cleaning 
     2113      !!        !  06-10  (G. Smith) Calculates initial date the same as method for final date 
     2114      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
     2115      !!    `   !  2014-09  (D. Lea) New generic routine now deals with arbitrary initial time of day 
     2116      !!---------------------------------------------------------------------- 
     2117      IMPLICIT NONE 
     2118      !! * Arguments 
     2119      REAL(KIND=dp), INTENT(OUT) :: ddobsini                   ! Initial date in YYYYMMDD.HHMMSS 
     2120      CALL calc_date( nit000 - 1, ddobsini ) 
    20962121   END SUBROUTINE ini_date 
    20972122 
     
    20992124      !!---------------------------------------------------------------------- 
    21002125      !!                    ***  ROUTINE fin_date  *** 
     2126      !!          
     2127      !! ** Purpose : Get final data in double precision YYYYMMDD.HHMMSS format 
    21012128      !! 
    2102       !! ** Purpose : Get final date in double precision YYYYMMDD.HHMMSS format 
     2129      !! ** Method  : Get final data in double precision YYYYMMDD.HHMMSS format 
    21032130      !! 
    2104       !! ** Method  : Get final date in double precision YYYYMMDD.HHMMSS format 
    2105       !! 
    2106       !! ** Action  : Get final date in double precision YYYYMMDD.HHMMSS format 
     2131      !! ** Action  : Get final data in double precision YYYYMMDD.HHMMSS format 
    21072132      !! 
    21082133      !! History : 
     
    21112136      !!        !  06-10  (A. Weaver) Cleaning 
    21122137      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
     2138      !!    `   !  2014-09  (D. Lea) New generic routine now deals with arbitrary initial time of day 
    21132139      !!---------------------------------------------------------------------- 
    2114       USE phycst, ONLY : &            ! Physical constants 
    2115          & rday 
    2116       USE dom_oce, ONLY : &           ! Ocean space and time domain variables 
    2117          & rdt 
    2118  
    21192140      IMPLICIT NONE 
    2120  
    21212141      !! * Arguments 
    2122       REAL(dp), INTENT(OUT) :: ddobsfin ! Final date in YYYYMMDD.HHMMSS 
    2123  
    2124       !! * Local declarations 
    2125       INTEGER :: iyea        ! date - (year, month, day, hour, minute) 
    2126       INTEGER :: imon 
    2127       INTEGER :: iday 
    2128       INTEGER :: ihou 
    2129       INTEGER :: imin 
    2130       INTEGER :: imday       ! Number of days in month. 
    2131       INTEGER, DIMENSION(12) :: & 
    2132          &       imonth_len  ! Length in days of the months of the current year 
    2133       REAL(wp) :: zdayfrc    ! Fraction of day 
    2134  
    2135       !----------------------------------------------------------------------- 
    2136       ! Initial date initialization (year, month, day, hour, minute) 
    2137       ! (This assumes that the initial date is for 00z) 
    2138       !----------------------------------------------------------------------- 
    2139       iyea =   ndate0 / 10000 
    2140       imon = ( ndate0 - iyea * 10000 ) / 100 
    2141       iday =   ndate0 - iyea * 10000 - imon * 100 
    2142       ihou = 0 
    2143       imin = 0 
    2144  
    2145       !----------------------------------------------------------------------- 
    2146       ! Compute number of days + number of hours + min since initial time 
    2147       !----------------------------------------------------------------------- 
    2148       iday    = iday +  nitend  * rdt / rday 
    2149       zdayfrc =  nitend  * rdt / rday 
    2150       zdayfrc = zdayfrc - AINT( zdayfrc ) 
    2151       ihou    = INT( zdayfrc * 24 ) 
    2152       imin    = INT( ( zdayfrc * 24 - ihou ) * 60 ) 
    2153  
    2154       !----------------------------------------------------------------------- 
    2155       ! Convert number of days (iday) into a real date 
    2156       !---------------------------------------------------------------------- 
    2157  
    2158       CALL calc_month_len( iyea, imonth_len ) 
    2159  
    2160       DO WHILE ( iday > imonth_len(imon) ) 
    2161          iday = iday - imonth_len(imon) 
    2162          imon = imon + 1  
    2163          IF ( imon > 12 ) THEN 
    2164             imon = 1 
    2165             iyea = iyea + 1 
    2166             CALL calc_month_len( iyea, imonth_len )  ! update month lengths 
    2167          ENDIF 
    2168       END DO 
    2169  
    2170       !----------------------------------------------------------------------- 
    2171       ! Convert it into YYYYMMDD.HHMMSS format 
    2172       !----------------------------------------------------------------------- 
    2173       ddobsfin = iyea * 10000_dp + imon * 100_dp    + iday & 
    2174          &     + ihou * 0.01_dp  + imin * 0.0001_dp 
    2175  
    2176     END SUBROUTINE fin_date 
     2142      REAL(KIND=dp), INTENT(OUT) :: ddobsfin                   ! Final date in YYYYMMDD.HHMMSS 
     2143      CALL calc_date( nitend, ddobsfin ) 
     2144   END SUBROUTINE fin_date 
    21772145 
    21782146    SUBROUTINE obs_settypefiles( ntypes, jpmaxnfiles, ifiles, cobstypes, cfiles ) 
Note: See TracChangeset for help on using the changeset viewer.