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

Changeset 10005 for branches


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

Location:
branches/UKMO/dev_r5518_GO6_package_STARTHOUR/NEMOGCM
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GO6_package_STARTHOUR/NEMOGCM/CONFIG/SHARED/namelist_ref

    r8447 r10005  
    2929   nn_itend    =    5475   !  last  time step (std 5475) 
    3030   nn_date0    =  010101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     31   nn_time0    =       0   !  initial time of day in hhmm 
    3132   nn_leapy    =       0   !  Leap year calendar (1) or not (0) 
    3233   ln_rstart   = .false.   !  start from rest (F) or from a restart file (T) 
  • branches/UKMO/dev_r5518_GO6_package_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r8400 r10005  
    4444#endif 
    4545   USE sbc_oce          ! Surface boundary condition variables. 
     46   USE diaobs, ONLY: calc_date     ! Compute the calendar date on a given step 
    4647 
    4748   IMPLICIT NONE 
     
    4950    
    5051   PUBLIC   asm_inc_init   !: Initialize the increment arrays and IAU weights 
    51    PUBLIC   calc_date      !: Compute the calendar date YYYYMMDD on a given step 
    5252   PUBLIC   tra_asm_inc    !: Apply the tracer (T and S) increments 
    5353   PUBLIC   dyn_asm_inc    !: Apply the dynamic (u and v) increments 
     
    118118      INTEGER :: iiauper         ! Number of time steps in the IAU period 
    119119      INTEGER :: icycper         ! Number of time steps in the cycle 
    120       INTEGER :: iitend_date     ! Date YYYYMMDD of final time step 
    121       INTEGER :: iitbkg_date     ! Date YYYYMMDD of background time step for Jb term 
    122       INTEGER :: iitdin_date     ! Date YYYYMMDD of background time step for DI 
    123       INTEGER :: iitiaustr_date  ! Date YYYYMMDD of IAU interval start time step 
    124       INTEGER :: iitiaufin_date  ! Date YYYYMMDD of IAU interval final time step 
    125       ! 
     120      REAL(KIND=dp) :: ditend_date     ! Date YYYYMMDD.HHMMSS of final time step 
     121      REAL(KIND=dp) :: ditbkg_date     ! Date YYYYMMDD.HHMMSS of background time step for Jb term 
     122      REAL(KIND=dp) :: ditdin_date     ! Date YYYYMMDD.HHMMSS of background time step for DI 
     123      REAL(KIND=dp) :: ditiaustr_date  ! Date YYYYMMDD.HHMMSS of IAU interval start time step 
     124      REAL(KIND=dp) :: ditiaufin_date  ! Date YYYYMMDD.HHMMSS of IAU interval final time step 
     125 
    126126      REAL(wp) :: znorm        ! Normalization factor for IAU weights 
    127127      REAL(wp) :: ztotwgt      ! Value of time-integrated IAU weights (should be equal to one) 
     
    186186      icycper = nitend      - nit000      + 1  ! Cycle interval length 
    187187 
    188       CALL calc_date( nit000, nitend     , ndate0, iitend_date    )     ! Date of final time step 
    189       CALL calc_date( nit000, nitbkg_r   , ndate0, iitbkg_date    )     ! Background time for Jb referenced to ndate0 
    190       CALL calc_date( nit000, nitdin_r   , ndate0, iitdin_date    )     ! Background time for DI referenced to ndate0 
    191       CALL calc_date( nit000, nitiaustr_r, ndate0, iitiaustr_date )     ! IAU start time referenced to ndate0 
    192       CALL calc_date( nit000, nitiaufin_r, ndate0, iitiaufin_date )     ! IAU end time referenced to ndate0 
    193       ! 
     188      ! Date of final time step 
     189      CALL calc_date( nitend, ditend_date ) 
     190 
     191      ! Background time for Jb referenced to ndate0 
     192      CALL calc_date( nitbkg_r, ditbkg_date ) 
     193 
     194      ! Background time for DI referenced to ndate0 
     195      CALL calc_date( nitdin_r, ditdin_date ) 
     196 
     197      ! IAU start time referenced to ndate0 
     198      CALL calc_date( nitiaustr_r, ditiaustr_date ) 
     199 
     200      ! IAU end time referenced to ndate0 
     201      CALL calc_date( nitiaufin_r, ditiaufin_date ) 
     202 
    194203      IF(lwp) THEN 
    195204         WRITE(numout,*) 
     
    206215         WRITE(numout,*) '       ndastp         = ', ndastp 
    207216         WRITE(numout,*) '       ndate0         = ', ndate0 
    208          WRITE(numout,*) '       iitend_date    = ', iitend_date 
    209          WRITE(numout,*) '       iitbkg_date    = ', iitbkg_date 
    210          WRITE(numout,*) '       iitdin_date    = ', iitdin_date 
    211          WRITE(numout,*) '       iitiaustr_date = ', iitiaustr_date 
    212          WRITE(numout,*) '       iitiaufin_date = ', iitiaufin_date 
     217         WRITE(numout,*) '       nn_time0       = ', nn_time0 
     218         WRITE(numout,*) '       ditend_date    = ', ditend_date 
     219         WRITE(numout,*) '       ditbkg_date    = ', ditbkg_date 
     220         WRITE(numout,*) '       ditdin_date    = ', ditdin_date 
     221         WRITE(numout,*) '       ditiaustr_date = ', ditiaustr_date 
     222         WRITE(numout,*) '       ditiaufin_date = ', ditiaufin_date 
    213223      ENDIF 
    214224 
     
    368378            WRITE(numout,*)  
    369379            WRITE(numout,*) 'asm_inc_init : Assimilation increments valid ', & 
    370                &            ' between dates ', NINT( z_inc_dateb ),' and ',  & 
    371                &            NINT( z_inc_datef ) 
     380               &            ' between dates ', z_inc_dateb,' and ',  & 
     381               &            z_inc_datef 
    372382            WRITE(numout,*) '~~~~~~~~~~~~' 
    373383         ENDIF 
    374384 
    375          IF (     ( NINT( z_inc_dateb ) < ndastp      ) & 
    376             & .OR.( NINT( z_inc_datef ) > iitend_date ) ) & 
     385         IF (     ( z_inc_dateb < ndastp + nn_time0*0.0001_wp ) & 
     386            & .OR.( z_inc_datef > ditend_date ) ) & 
    377387            & CALL ctl_warn( ' Validity time of assimilation increments is ', & 
    378388            &                ' outside the assimilation interval' ) 
    379389 
    380          IF ( ( ln_asmdin ).AND.( NINT( zdate_inc ) /= iitdin_date ) ) & 
     390         IF ( ( ln_asmdin ).AND.( zdate_inc /= ditdin_date ) ) & 
    381391            & CALL ctl_warn( ' Validity time of assimilation increments does ', & 
    382392            &                ' not agree with Direct Initialization time' ) 
     
    505515            WRITE(numout,*)  
    506516            WRITE(numout,*) 'asm_inc_init : Assimilation background state valid at : ', & 
    507                &  NINT( zdate_bkg ) 
     517               &  zdate_bkg 
    508518            WRITE(numout,*) '~~~~~~~~~~~~' 
    509519         ENDIF 
    510520 
    511          IF ( NINT( zdate_bkg ) /= iitdin_date ) & 
     521         IF ( zdate_bkg /= ditdin_date ) & 
    512522            & CALL ctl_warn( ' Validity time of assimilation background state does', & 
    513523            &                ' not agree with Direct Initialization time' ) 
     
    537547      ! 
    538548   END SUBROUTINE asm_inc_init 
    539  
    540  
    541    SUBROUTINE calc_date( kit000, kt, kdate0, kdate ) 
    542       !!---------------------------------------------------------------------- 
    543       !!                    ***  ROUTINE calc_date  *** 
    544       !!           
    545       !! ** Purpose : Compute the calendar date YYYYMMDD at a given time step. 
    546       !! 
    547       !! ** Method  : Compute the calendar date YYYYMMDD at a given time step. 
    548       !! 
    549       !! ** Action  :  
    550       !!---------------------------------------------------------------------- 
    551       INTEGER, INTENT(IN) :: kit000  ! Initial time step 
    552       INTEGER, INTENT(IN) :: kt      ! Current time step referenced to kit000 
    553       INTEGER, INTENT(IN) :: kdate0  ! Initial date 
    554       INTEGER, INTENT(OUT) :: kdate  ! Current date reference to kdate0 
    555       ! 
    556       INTEGER :: iyea0    ! Initial year 
    557       INTEGER :: imon0    ! Initial month 
    558       INTEGER :: iday0    ! Initial day 
    559       INTEGER :: iyea     ! Current year 
    560       INTEGER :: imon     ! Current month 
    561       INTEGER :: iday     ! Current day 
    562       INTEGER :: idaystp  ! Number of days between initial and current date 
    563       INTEGER :: idaycnt  ! Day counter 
    564  
    565       INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
    566  
    567       !----------------------------------------------------------------------- 
    568       ! Compute the calendar date YYYYMMDD 
    569       !----------------------------------------------------------------------- 
    570  
    571       ! Initial date 
    572       iyea0 =   kdate0 / 10000 
    573       imon0 = ( kdate0 - ( iyea0 * 10000 ) ) / 100 
    574       iday0 =   kdate0 - ( iyea0 * 10000 ) - ( imon0 * 100 )  
    575  
    576       ! Check that kt >= kit000 - 1 
    577       IF ( kt < kit000 - 1 ) CALL ctl_stop( ' kt must be >= kit000 - 1') 
    578  
    579       ! If kt = kit000 - 1 then set the date to the restart date 
    580       IF ( kt == kit000 - 1 ) THEN 
    581  
    582          kdate = ndastp 
    583          RETURN 
    584  
    585       ENDIF 
    586  
    587       ! Compute the number of days from the initial date 
    588       idaystp = INT( REAL( kt - kit000 ) * rdt / 86400. ) 
    589     
    590       iday    = iday0 
    591       imon    = imon0 
    592       iyea    = iyea0 
    593       idaycnt = 0 
    594  
    595       CALL calc_month_len( iyea, imonth_len ) 
    596  
    597       DO WHILE ( idaycnt < idaystp ) 
    598          iday = iday + 1 
    599          IF ( iday > imonth_len(imon) )  THEN 
    600             iday = 1 
    601             imon = imon + 1 
    602          ENDIF 
    603          IF ( imon > 12 ) THEN 
    604             imon = 1 
    605             iyea = iyea + 1 
    606             CALL calc_month_len( iyea, imonth_len )  ! update month lengths 
    607          ENDIF                  
    608          idaycnt = idaycnt + 1 
    609       END DO 
    610       ! 
    611       kdate = iyea * 10000 + imon * 100 + iday 
    612       ! 
    613    END SUBROUTINE 
    614  
    615  
    616    SUBROUTINE calc_month_len( iyear, imonth_len ) 
    617       !!---------------------------------------------------------------------- 
    618       !!                    ***  ROUTINE calc_month_len  *** 
    619       !!           
    620       !! ** Purpose : Compute the number of days in a months given a year. 
    621       !! 
    622       !! ** Method  :  
    623       !!---------------------------------------------------------------------- 
    624       INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
    625       INTEGER :: iyear         !: year 
    626       !!---------------------------------------------------------------------- 
    627       ! 
    628       ! length of the month of the current year (from nleapy, read in namelist) 
    629       IF ( nleapy < 2 ) THEN  
    630          imonth_len(:) = (/ 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31 /) 
    631          IF ( nleapy == 1 ) THEN   ! we are using calendar with leap years 
    632             IF ( MOD(iyear, 4) == 0 .AND. ( MOD(iyear, 400) == 0 .OR. MOD(iyear, 100) /= 0 ) ) THEN 
    633                imonth_len(2) = 29 
    634             ENDIF 
    635          ENDIF 
    636       ELSE 
    637          imonth_len(:) = nleapy   ! all months with nleapy days per year 
    638       ENDIF 
    639       ! 
    640    END SUBROUTINE 
    641  
    642549 
    643550   SUBROUTINE tra_asm_inc( kt ) 
  • branches/UKMO/dev_r5518_GO6_package_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/BDY/bdytides.F90

    r9583 r10005  
    325325      ENDIF 
    326326 
    327       IF ( nsec_day == NINT(0.5_wp * rdttra(1)) .AND. zflag==1 ) THEN 
     327      IF ( (nsec_day == NINT(0.5_wp * rdttra(1)) .OR. kt==nit000) .AND. zflag==1 ) THEN 
    328328        ! 
    329329        kt_tide = kt 
     
    440440            ! We refresh nodal factors every day below 
    441441            ! This should be done somewhere else 
    442             IF ( nsec_day == NINT(0.5_wp * rdttra(1)) .AND. lk_first_btstp ) THEN 
    443                ! 
    444                kt_tide = kt                
     442            IF ( ( nsec_day == NINT(0.5_wp * rdttra(1)) .OR. kt==nit000 ) .AND. lk_first_btstp ) THEN 
     443               ! 
     444               kt_tide = kt - (nsec_day - 0.5_wp * rdttra(1))/rdttra(1) 
    445445               ! 
    446446               IF(lwp) THEN 
  • branches/UKMO/dev_r5518_GO6_package_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r9321 r10005  
    9595      nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 ) 
    9696 
    97       CALL ymds2ju( nyear, nmonth, nday, 0.0, fjulday )  ! we assume that we start run at 00:00 
     97      nhour   =   nn_time0 / 100 
     98      nminute = ( nn_time0 - nhour * 100 ) 
     99 
     100      CALL ymds2ju( nyear, nmonth, nday, nhour*3600._wp+nminute*60._wp, fjulday )   
    98101      IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < 0.1 / rday )   fjulday = REAL(NINT(fjulday),wp)   ! avoid truncation error 
    99       fjulday = fjulday + 1.                             ! move back to the day at nit000 (and not at nit000 - 1) 
     102      IF( nn_time0*3600 - ndt05 .lt. 0 ) fjulday = fjulday + 1.                    ! move back to the day at nit000 (and not at nit000 - 1) 
    100103 
    101104      nsec1jan000 = 0 
     
    118121      !compute number of days between last monday and today 
    119122      CALL ymds2ju( 1900, 01, 01, 0.0, zjul )  ! compute julian day value of 01.01.1900 (our reference that was a Monday) 
    120       inbday = NINT(fjulday - zjul)            ! compute nb day between  01.01.1900 and current day 
     123      inbday = FLOOR(fjulday - zjul)            ! compute nb day between  01.01.1900 and start of current day 
    121124      idweek = MOD(inbday, 7)                  ! compute nb day between last monday and current day 
     125      IF (idweek .lt. 0) idweek=idweek+7       ! Avoid negative values for dates before 01.01.1900 
    122126 
    123127      ! number of seconds since the beginning of current year/month/week/day at the middle of the time-step 
    124       nsec_year  = nday_year * nsecd - ndt05   ! 1 time step before the middle of the first time step 
    125       nsec_month = nday      * nsecd - ndt05   ! because day will be called at the beginning of step 
    126       nsec_week  = idweek    * nsecd - ndt05 
    127       nsec_day   =             nsecd - ndt05 
     128      IF (nhour*3600+nminute*60-ndt05 .gt. 0) THEN 
     129         ! 1 timestep before current middle of first time step is still the same day 
     130         nsec_year  = (nday_year-1) * nsecd + nhour*3600+nminute*60 - ndt05  
     131         nsec_month = (nday-1)      * nsecd + nhour*3600+nminute*60 - ndt05     
     132      ELSE 
     133         ! 1 time step before the middle of the first time step is the previous day  
     134         nsec_year  = nday_year * nsecd + nhour*3600+nminute*60 - ndt05  
     135         nsec_month = nday      * nsecd + nhour*3600+nminute*60 - ndt05    
     136      ENDIF 
     137      nsec_week  = idweek    * nsecd + nhour*3600+nminute*60 - ndt05 
     138      nsec_day   =             nhour*3600+nminute*60 - ndt05  
     139      IF( nsec_day .lt. 0 ) nsec_day = nsec_day + nsecd 
     140      IF( nsec_week .lt. 0 ) nsec_week = nsec_week + nsecd*7 
    128141 
    129142      ! control print 
    130       IF(lwp) WRITE(numout,'(a,i6,a,i2,a,i2,a,i8,a,i8)')' =======>> 1/2 time step before the start of the run DATE Y/M/D = ',   & 
    131            &                   nyear, '/', nmonth, '/', nday, '  nsec_day:', nsec_day, '  nsec_week:', nsec_week 
     143      IF(lwp) WRITE(numout,'(a,i6,a,i2,a,i2,a,i8,a,i8,a,i8,a,i8)')' =======>> 1/2 time step before the start of the run DATE Y/M/D = ',   & 
     144           &                   nyear, '/', nmonth, '/', nday, '  nsec_day:', nsec_day, '  nsec_week:', nsec_week, '  & 
     145           &                   nsec_month:', nsec_month , '  nsec_year:' , nsec_year 
    132146 
    133147      ! Up to now, calendar parameters are related to the end of previous run (nit000-1) 
     
    302316      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag 
    303317      ! 
    304       REAL(wp) ::   zkt, zndastp 
     318      REAL(wp) ::   zkt, zndastp, zdayfrac, ksecs, ktime 
     319      INTEGER  ::   ihour, iminute 
    305320      !!---------------------------------------------------------------------- 
    306321 
     
    334349               ndastp = NINT( zndastp ) 
    335350               CALL iom_get( numror, 'adatrj', adatrj  ) 
     351          CALL iom_get( numror, 'ntime', ktime ) 
    336352               IF(nn_timing == 2)  CALL timing_stop('iom_rstget') 
     353          nn_time0=INT(ktime) 
     354               ! calculate start time in hours and minutes 
     355          zdayfrac=adatrj-INT(adatrj) 
     356          ksecs = NINT(zdayfrac*86400)        ! Nearest second to catch rounding errors in adatrj          
     357          ihour = INT(ksecs/3600) 
     358          iminute = ksecs/60-ihour*60 
     359            
     360               ! Add to nn_time0 
     361               nhour   =   nn_time0 / 100 
     362               nminute = ( nn_time0 - nhour * 100 ) 
     363          nminute=nminute+iminute 
     364           
     365          IF( nminute >= 60 ) THEN 
     366             nminute=nminute-60 
     367        nhour=nhour+1 
     368          ENDIF 
     369          nhour=nhour+ihour 
     370          IF( nhour >= 24 ) THEN 
     371        nhour=nhour-24 
     372             adatrj=adatrj+1 
     373          ENDIF           
     374          nn_time0 = nhour * 100 + nminute 
     375          adatrj = INT(adatrj)                    ! adatrj set to integer as nn_time0 updated           
    337376            ELSE 
    338                ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
    339                ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
     377               ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) 
     378               ndastp = ndate0        ! ndate0 read in the namelist in dom_nam 
     379               nhour   =   nn_time0 / 100 
     380               nminute = ( nn_time0 - nhour * 100 ) 
     381               IF( nhour*3600+nminute*60-ndt05 .lt. 0 )  ndastp=ndastp-1      ! Start hour is specified in the namelist (default 0) 
    340382               adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    341383               ! note this is wrong if time step has changed during run 
    342384            ENDIF 
    343385         ELSE 
    344             ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
    345             ndastp = ndate0 - 1        ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00 
     386            ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) 
     387            ndastp = ndate0           ! ndate0 read in the namelist in dom_nam 
     388            nhour   =   nn_time0 / 100 
     389            nminute = ( nn_time0 - nhour * 100 ) 
     390            IF( nhour*3600+nminute*60-ndt05 .lt. 0 )  ndastp=ndastp-1      ! Start hour is specified in the namelist (default 0) 
    346391            adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    347392         ENDIF 
     
    352397            WRITE(numout,*) '   date ndastp                                      : ', ndastp 
    353398            WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
     399            WRITE(numout,*) '   nn_time0                                         : ',nn_time0 
    354400            WRITE(numout,*) 
    355401         ENDIF 
     
    368414         CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj            )   ! number of elapsed days since 
    369415         !                                                                     ! the begining of the run [s] 
     416         CALL iom_rstput( kt, nitrst, numrow, 'ntime'  , REAL( nn_time0, wp) ) ! time 
    370417         IF(nn_timing == 2)  CALL timing_stop('iom_rstput') 
    371418      ENDIF 
  • branches/UKMO/dev_r5518_GO6_package_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r9830 r10005  
    280280   INTEGER , PUBLIC ::   nmonth        !: current month 
    281281   INTEGER , PUBLIC ::   nday          !: current day of the month 
     282   INTEGER , PUBLIC ::   nhour         !: current hour 
     283   INTEGER , PUBLIC ::   nminute       !: current minute 
    282284   INTEGER , PUBLIC ::   ndastp        !: time step date in yyyymmdd format 
    283285   INTEGER , PUBLIC ::   nday_year     !: current day counted from jan 1st of the current year 
  • branches/UKMO/dev_r5518_GO6_package_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r6491 r10005  
    137137      NAMELIST/namrun/ cn_ocerst_indir, cn_ocerst_outdir, nn_stocklist, ln_rst_list,               & 
    138138         &             nn_no   , cn_exp    , cn_ocerst_in, cn_ocerst_out, ln_rstart , ln_rstdate, nn_rstctl,   & 
    139          &             nn_it000, nn_itend  , nn_date0    , nn_leapy     , nn_istate , nn_stock ,   & 
     139         &             nn_it000, nn_itend  , nn_date0    , nn_time0,      nn_leapy     , nn_istate , nn_stock ,   & 
    140140         &             nn_write, ln_dimgnnn, ln_mskland  , ln_cfmeta    , ln_clobber, nn_chunksz, nn_euler 
    141141      NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,   & 
     
    180180         WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend 
    181181         WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0 
     182         WRITE(numout,*) '      initial time of day in hhmm     nn_time0   = ', nn_time0 
    182183         WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy 
    183184         WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate 
  • branches/UKMO/dev_r5518_GO6_package_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r6491 r10005  
    3838   INTEGER       ::   nn_itend         !: index of the last time step 
    3939   INTEGER       ::   nn_date0         !: initial calendar date aammjj 
     40   INTEGER       ::   nn_time0         !: initial time of day in hhmm 
    4041   INTEGER       ::   nn_leapy         !: Leap year calendar flag (0/1 or 30) 
    4142   INTEGER       ::   nn_istate        !: initial state output flag (0/1) 
  • 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 
  • branches/UKMO/dev_r5518_GO6_package_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/OBS/obs_prep.F90

    r6486 r10005  
    125125      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    126126      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    127       ihou0 = 0 
    128       imin0 = 0 
     127      ihou0 =   nn_time0 / 100 
     128      imin0 = ( nn_time0 - ihou0 * 100 ) 
    129129 
    130130      icycle = no     ! Assimilation cycle 
     
    397397      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    398398      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    399       ihou0 = 0 
    400       imin0 = 0 
     399      ihou0 =   nn_time0 / 100 
     400      imin0 = ( nn_time0 - ihou0 * 100 ) 
    401401 
    402402      icycle = no     ! Assimilation cycle 
     
    585585      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    586586      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    587       ihou0 = 0 
    588       imin0 = 0 
     587      ihou0 =   nn_time0 / 100 
     588      imin0 = ( nn_time0 - ihou0 * 100 ) 
    589589 
    590590      icycle = no     ! Assimilation cycle 
     
    770770      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    771771      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    772       ihou0 = 0 
    773       imin0 = 0 
     772      ihou0 =   nn_time0 / 100 
     773      imin0 = ( nn_time0 - ihou0 * 100 ) 
    774774 
    775775      icycle = no     ! Assimilation cycle 
     
    968968      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    969969      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    970       ihou0 = 0 
    971       imin0 = 0 
     970      ihou0 =   nn_time0 / 100 
     971      imin0 = ( nn_time0 - ihou0 * 100 ) 
    972972 
    973973      icycle = no     ! Assimilation cycle 
  • branches/UKMO/dev_r5518_GO6_package_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/SBC/sbctide.F90

    r6486 r10005  
    4747      INTEGER, INTENT( in ) ::   kt     ! ocean time-step 
    4848      INTEGER               ::   jk     ! dummy loop index 
     49      INTEGER               ::   nsec_day_orig     ! Temporary variable 
    4950      !!---------------------------------------------------------------------- 
    50  
    51       IF( nsec_day == NINT(0.5_wp * rdttra(1)) ) THEN      ! start a new day 
     51       
     52      IF( nsec_day == NINT(0.5_wp * rdttra(1)) .OR. kt == nit000 ) THEN      ! start a new day 
    5253         ! 
    5354         IF( kt == nit000 ) THEN 
     
    6061         pot_astro(:,:) = 0._wp 
    6162         ! 
     63         ! If the run does not start from midnight then need to initialise tides 
     64         ! at the start of the current day (only occurs when kt==nit000) 
     65         ! Temporarily set nsec_day to beginning of day. 
     66         nsec_day_orig = nsec_day 
     67         IF ( nsec_day /= NINT(0.5_wp * rdttra(1)) ) THEN  
     68            kt_tide = kt - (nsec_day - 0.5_wp * rdttra(1))/rdttra(1) 
     69            nsec_day = NINT(0.5_wp * rdttra(1)) 
     70         ELSE 
     71            kt_tide = kt  
     72         ENDIF 
    6273         CALL tide_harmo( omega_tide, v0tide, utide, ftide, ntide, nb_harmo ) 
    6374         ! 
    64          kt_tide = kt 
    6575         ! 
    6676         IF(lwp) THEN 
     
    7585         IF( ln_tide_pot )   CALL tide_init_potential 
    7686         ! 
     87         ! Reset nsec_day 
     88         nsec_day = nsec_day_orig  
    7789      ENDIF 
    7890      ! 
Note: See TracChangeset for help on using the changeset viewer.