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

Ignore:
Timestamp:
2018-07-26T13:07:55+02:00 (6 years ago)
Author:
timgraham
Message:

Included all of the functional changes from STARTHOUR branch in branches/2014

File:
1 edited

Legend:

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

    r6486 r10005  
    5050      &   dia_obs,      &  ! Compute model equivalent to observations 
    5151      &   dia_obs_wri,  &  ! Write model equivalent to observations 
    52       &   dia_obs_dealloc  ! Deallocate dia_obs data 
     52      &   dia_obs_dealloc, &  ! Deallocate dia_obs data 
     53      &   calc_date           ! Compute the date of a timestep 
    5354 
    5455   !! * Shared Module variables 
     
    14331434   END SUBROUTINE dia_obs_dealloc 
    14341435 
    1435    SUBROUTINE ini_date( ddobsini ) 
    1436       !!---------------------------------------------------------------------- 
    1437       !!                    ***  ROUTINE ini_date  *** 
     1436   SUBROUTINE calc_date( kstp, ddobs ) 
     1437      !!---------------------------------------------------------------------- 
     1438      !!                    ***  ROUTINE calc_date  *** 
    14381439      !!           
    1439       !! ** Purpose : Get initial data in double precision YYYYMMDD.HHMMSS format 
    1440       !! 
    1441       !! ** Method  : Get initial data in double precision YYYYMMDD.HHMMSS format 
    1442       !! 
    1443       !! ** Action  : Get initial data in double precision YYYYMMDD.HHMMSS format 
     1440      !! ** Purpose : Get date in double precision YYYYMMDD.HHMMSS format 
     1441      !! 
     1442      !! ** Method  : Get date in double precision YYYYMMDD.HHMMSS format 
     1443      !! 
     1444      !! ** Action  : Get date in double precision YYYYMMDD.HHMMSS format 
    14441445      !! 
    14451446      !! History : 
     
    14491450      !!        !  06-10  (G. Smith) Calculates initial date the same as method for final date 
    14501451      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
     1452      !!        !  2014-09  (D. Lea) New generic routine now deals with arbitrary initial time of day 
    14511453      !!---------------------------------------------------------------------- 
    14521454      USE phycst, ONLY : &            ! Physical constants 
     
    14601462 
    14611463      !! * Arguments 
    1462       REAL(KIND=dp), INTENT(OUT) :: ddobsini                         ! Initial date in YYYYMMDD.HHMMSS 
     1464      REAL(KIND=dp), INTENT(OUT) :: ddobs                        ! Date in YYYYMMDD.HHMMSS 
     1465      INTEGER :: kstp 
    14631466 
    14641467      !! * Local declarations 
     
    14751478      !!---------------------------------------------------------------------- 
    14761479      !! Initial date initialization (year, month, day, hour, minute) 
    1477       !! (This assumes that the initial date is for 00z)) 
    14781480      !!---------------------------------------------------------------------- 
    14791481      iyea =   ndate0 / 10000 
    14801482      imon = ( ndate0 - iyea * 10000 ) / 100 
    14811483      iday =   ndate0 - iyea * 10000 - imon * 100 
    1482       ihou = 0 
    1483       imin = 0 
     1484      ihou =   nn_time0 / 100 
     1485      imin = ( nn_time0 - ihou * 100 )  
    14841486 
    14851487      !!---------------------------------------------------------------------- 
    14861488      !! Compute number of days + number of hours + min since initial time 
    14871489      !!---------------------------------------------------------------------- 
    1488       iday = iday + ( nit000 -1 ) * rdt / rday 
    1489       zdayfrc = ( nit000 -1 ) * rdt / rday 
     1490      zdayfrc = kstp * rdt / rday 
    14901491      zdayfrc = zdayfrc - aint(zdayfrc) 
    1491       ihou = int( zdayfrc * 24 ) 
    1492       imin = int( (zdayfrc * 24 - ihou) * 60 ) 
     1492      imin = imin + int( zdayfrc * 24 * 60 )  
     1493      DO WHILE (imin >= 60)  
     1494        imin=imin-60 
     1495        ihou=ihou+1 
     1496      END DO 
     1497      DO WHILE (ihou >= 24) 
     1498        ihou=ihou-24 
     1499        iday=iday+1 
     1500      END DO  
     1501      iday = iday + kstp * rdt / rday  
    14931502 
    14941503      !!----------------------------------------------------------------------- 
     
    15111520      !! Convert it into YYYYMMDD.HHMMSS format. 
    15121521      !!---------------------------------------------------------------------- 
    1513       ddobsini = iyea * 10000_dp + imon * 100_dp + & 
    1514          &       iday + ihou * 0.01_dp + imin * 0.0001_dp 
    1515  
     1522      ddobs = iyea * 10000_dp + imon * 100_dp + & 
     1523         &    iday + ihou * 0.01_dp + imin * 0.0001_dp 
     1524 
     1525   END SUBROUTINE calc_date 
     1526 
     1527   SUBROUTINE ini_date( ddobsini ) 
     1528      !!---------------------------------------------------------------------- 
     1529      !!                    ***  ROUTINE ini_date  *** 
     1530      !!           
     1531      !! ** Purpose : Get initial data in double precision YYYYMMDD.HHMMSS format 
     1532      !! 
     1533      !! ** Method  : Get initial data in double precision YYYYMMDD.HHMMSS format 
     1534      !! 
     1535      !! ** Action  : Get initial data in double precision YYYYMMDD.HHMMSS format 
     1536      !! 
     1537      !! History : 
     1538      !!        !  06-03  (K. Mogensen)  Original code 
     1539      !!        !  06-05  (K. Mogensen)  Reformatted 
     1540      !!        !  06-10  (A. Weaver) Cleaning 
     1541      !!        !  06-10  (G. Smith) Calculates initial date the same as method for final date 
     1542      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
     1543      !!---------------------------------------------------------------------- 
     1544 
     1545      IMPLICIT NONE 
     1546 
     1547      !! * Arguments 
     1548      REAL(KIND=dp), INTENT(OUT) :: ddobsini                   ! Initial date in YYYYMMDD.HHMMSS 
     1549 
     1550      CALL calc_date( nit000 - 1, ddobsini ) 
    15161551 
    15171552   END SUBROUTINE ini_date 
     
    15331568      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
    15341569      !!---------------------------------------------------------------------- 
    1535       USE phycst, ONLY : &            ! Physical constants 
    1536          & rday 
    1537 !      USE daymod, ONLY : &            ! Time variables 
    1538 !         & nmonth_len                 
    1539       USE dom_oce, ONLY : &           ! Ocean space and time domain variables 
    1540          & rdt 
    15411570 
    15421571      IMPLICIT NONE 
     
    15451574      REAL(KIND=dp), INTENT(OUT) :: ddobsfin                   ! Final date in YYYYMMDD.HHMMSS 
    15461575 
    1547       !! * Local declarations 
    1548       INTEGER :: iyea        ! date - (year, month, day, hour, minute) 
    1549       INTEGER :: imon 
    1550       INTEGER :: iday 
    1551       INTEGER :: ihou 
    1552       INTEGER :: imin 
    1553       INTEGER :: imday         ! Number of days in month. 
    1554       REAL(KIND=wp) :: zdayfrc       ! Fraction of day 
    1555           
    1556       INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
    1557              
    1558       !----------------------------------------------------------------------- 
    1559       ! Initial date initialization (year, month, day, hour, minute) 
    1560       ! (This assumes that the initial date is for 00z) 
    1561       !----------------------------------------------------------------------- 
    1562       iyea =   ndate0 / 10000 
    1563       imon = ( ndate0 - iyea * 10000 ) / 100 
    1564       iday =   ndate0 - iyea * 10000 - imon * 100 
    1565       ihou = 0 
    1566       imin = 0 
    1567        
    1568       !----------------------------------------------------------------------- 
    1569       ! Compute number of days + number of hours + min since initial time 
    1570       !----------------------------------------------------------------------- 
    1571       iday    = iday +  nitend  * rdt / rday 
    1572       zdayfrc =  nitend  * rdt / rday 
    1573       zdayfrc = zdayfrc - AINT( zdayfrc ) 
    1574       ihou    = INT( zdayfrc * 24 ) 
    1575       imin    = INT( ( zdayfrc * 24 - ihou ) * 60 ) 
    1576  
    1577       !----------------------------------------------------------------------- 
    1578       ! Convert number of days (iday) into a real date 
    1579       !---------------------------------------------------------------------- 
    1580  
    1581       CALL calc_month_len( iyea, imonth_len ) 
    1582        
    1583       DO WHILE ( iday > imonth_len(imon) ) 
    1584          iday = iday - imonth_len(imon) 
    1585          imon = imon + 1  
    1586          IF ( imon > 12 ) THEN 
    1587             imon = 1 
    1588             iyea = iyea + 1 
    1589             CALL calc_month_len( iyea, imonth_len )  ! update month lengths 
    1590          ENDIF 
    1591       END DO 
    1592  
    1593       !----------------------------------------------------------------------- 
    1594       ! Convert it into YYYYMMDD.HHMMSS format 
    1595       !----------------------------------------------------------------------- 
    1596       ddobsfin = iyea * 10000_dp + imon * 100_dp    + iday & 
    1597          &     + ihou * 0.01_dp  + imin * 0.0001_dp 
    1598  
    1599     END SUBROUTINE fin_date 
    1600      
     1576      CALL calc_date( nitend, ddobsfin ) 
     1577 
     1578   END SUBROUTINE fin_date 
     1579    
    16011580END MODULE diaobs 
Note: See TracChangeset for help on using the changeset viewer.