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

Changeset 15256


Ignore:
Timestamp:
2021-09-14T13:47:06+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?

Location:
branches/UKMO/dev_r5518_obs_oper_strthr/NEMOGCM
Files:
11 edited

Legend:

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

    r14591 r15256  
    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_obs_oper_strthr/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r12610 r15256  
    4141#endif 
    4242   USE sbc_oce          ! Surface boundary condition variables. 
     43   USE diaobs, ONLY: calc_date     ! Compute the calendar date on a given step 
    4344 
    4445   IMPLICIT NONE 
     
    4647    
    4748   PUBLIC   asm_inc_init   !: Initialize the increment arrays and IAU weights 
    48    PUBLIC   calc_date      !: Compute the calendar date YYYYMMDD on a given step 
    4949   PUBLIC   tra_asm_inc    !: Apply the tracer (T and S) increments 
    5050   PUBLIC   dyn_asm_inc    !: Apply the dynamic (u and v) increments 
     
    119119      INTEGER :: iiauper         ! Number of time steps in the IAU period 
    120120      INTEGER :: icycper         ! Number of time steps in the cycle 
    121       INTEGER :: iitend_date     ! Date YYYYMMDD of final time step 
    122       INTEGER :: iitbkg_date     ! Date YYYYMMDD of background time step for Jb term 
    123       INTEGER :: iitdin_date     ! Date YYYYMMDD of background time step for DI 
    124       INTEGER :: iitiaustr_date  ! Date YYYYMMDD of IAU interval start time step 
    125       INTEGER :: iitiaufin_date  ! Date YYYYMMDD of IAU interval final time step 
     121      REAL(KIND=dp) :: ditend_date     ! Date YYYYMMDD.HHMMSS of final time step 
     122      REAL(KIND=dp) :: ditbkg_date     ! Date YYYYMMDD.HHMMSS of background time step for Jb term 
     123      REAL(KIND=dp) :: ditdin_date     ! Date YYYYMMDD.HHMMSS of background time step for DI 
     124      REAL(KIND=dp) :: ditiaustr_date  ! Date YYYYMMDD.HHMMSS of IAU interval start time step 
     125      REAL(KIND=dp) :: ditiaufin_date  ! Date YYYYMMDD.HHMMSS of IAU interval final time step 
    126126      ! 
    127127      REAL(wp) :: znorm        ! Normalization factor for IAU weights 
     
    189189      iiauper = nitiaufin_r - nitiaustr_r + 1  ! IAU interval length 
    190190      icycper = nitend      - nit000      + 1  ! Cycle interval length 
    191  
    192       CALL calc_date( nit000, nitend     , ndate0, iitend_date    )    ! Date of final time step 
    193       CALL calc_date( nit000, nitbkg_r   , ndate0, iitbkg_date    )    ! Background time for Jb referenced to ndate0 
    194       CALL calc_date( nit000, nitdin_r   , ndate0, iitdin_date    )    ! Background time for DI referenced to ndate0 
    195       CALL calc_date( nit000, nitiaustr_r, ndate0, iitiaustr_date )    ! IAU start time referenced to ndate0 
    196       CALL calc_date( nit000, nitiaufin_r, ndate0, iitiaufin_date )    ! IAU end time referenced to ndate0 
     191       
     192      CALL calc_date( nitend, ditend_date ) ! Date of final time step 
     193      CALL calc_date( nitbkg_r, ditbkg_date ) ! Background time for Jb referenced to ndate0 
     194      CALL calc_date( nitdin_r, ditdin_date ) ! Background time for DI referenced to ndate0 
     195      CALL calc_date( nitiaustr_r, ditiaustr_date ) ! IAU start time referenced to ndate0 
     196      CALL calc_date( nitiaufin_r, ditiaufin_date ) ! IAU end time referenced to ndate0 
    197197      ! 
    198198      IF(lwp) THEN 
     
    210210         WRITE(numout,*) '       ndastp         = ', ndastp 
    211211         WRITE(numout,*) '       ndate0         = ', ndate0 
    212          WRITE(numout,*) '       iitend_date    = ', iitend_date 
    213          WRITE(numout,*) '       iitbkg_date    = ', iitbkg_date 
    214          WRITE(numout,*) '       iitdin_date    = ', iitdin_date 
    215          WRITE(numout,*) '       iitiaustr_date = ', iitiaustr_date 
    216          WRITE(numout,*) '       iitiaufin_date = ', iitiaufin_date 
     212         WRITE(numout,*) '       nn_time0       = ', nn_time0 
     213         WRITE(numout,*) '       ditend_date    = ', ditend_date 
     214         WRITE(numout,*) '       ditbkg_date    = ', ditbkg_date 
     215         WRITE(numout,*) '       ditdin_date    = ', ditdin_date 
     216         WRITE(numout,*) '       ditiaustr_date = ', ditiaustr_date 
     217         WRITE(numout,*) '       ditiaufin_date = ', ditiaufin_date 
    217218      ENDIF 
    218219 
     
    386387            WRITE(numout,*)  
    387388            WRITE(numout,*) 'asm_inc_init : Assimilation increments valid ', & 
    388                &            ' between dates ', NINT( z_inc_dateb ),' and ',  & 
    389                &            NINT( z_inc_datef ) 
     389               &            ' between dates ', z_inc_dateb,' and ',  & 
     390               &            z_inc_datef 
    390391            WRITE(numout,*) '~~~~~~~~~~~~' 
    391392         ENDIF 
    392393 
    393          IF (     ( NINT( z_inc_dateb ) < ndastp      ) & 
    394             & .OR.( NINT( z_inc_datef ) > iitend_date ) ) & 
     394         IF (     ( z_inc_dateb < ndastp + nn_time0*0.0001_wp ) & 
     395            & .OR.( z_inc_datef > ditend_date ) ) & 
    395396            & CALL ctl_warn( ' Validity time of assimilation increments is ', & 
    396397            &                ' outside the assimilation interval' ) 
    397398 
    398          IF ( ( ln_asmdin ).AND.( NINT( zdate_inc ) /= iitdin_date ) ) & 
     399         IF ( ( ln_asmdin ).AND.( zdate_inc /= ditdin_date ) ) & 
    399400            & CALL ctl_warn( ' Validity time of assimilation increments does ', & 
    400401            &                ' not agree with Direct Initialization time' ) 
     
    532533            WRITE(numout,*)  
    533534            WRITE(numout,*) 'asm_inc_init : Assimilation background state valid at : ', & 
    534                &  NINT( zdate_bkg ) 
     535               & zdate_bkg 
    535536            WRITE(numout,*) '~~~~~~~~~~~~' 
    536537         ENDIF 
    537538 
    538          IF ( NINT( zdate_bkg ) /= iitdin_date ) & 
     539         IF ( zdate_bkg /= ditdin_date ) & 
    539540            & CALL ctl_warn( ' Validity time of assimilation background state does', & 
    540541            &                ' not agree with Direct Initialization time' ) 
     
    564565      ! 
    565566   END SUBROUTINE asm_inc_init 
    566  
    567  
    568    SUBROUTINE calc_date( kit000, kt, kdate0, kdate ) 
    569       !!---------------------------------------------------------------------- 
    570       !!                    ***  ROUTINE calc_date  *** 
    571       !!           
    572       !! ** Purpose : Compute the calendar date YYYYMMDD at a given time step. 
    573       !! 
    574       !! ** Method  : Compute the calendar date YYYYMMDD at a given time step. 
    575       !! 
    576       !! ** Action  :  
    577       !!---------------------------------------------------------------------- 
    578       INTEGER, INTENT(IN) :: kit000  ! Initial time step 
    579       INTEGER, INTENT(IN) :: kt      ! Current time step referenced to kit000 
    580       INTEGER, INTENT(IN) :: kdate0  ! Initial date 
    581       INTEGER, INTENT(OUT) :: kdate  ! Current date reference to kdate0 
    582       ! 
    583       INTEGER :: iyea0    ! Initial year 
    584       INTEGER :: imon0    ! Initial month 
    585       INTEGER :: iday0    ! Initial day 
    586       INTEGER :: iyea     ! Current year 
    587       INTEGER :: imon     ! Current month 
    588       INTEGER :: iday     ! Current day 
    589       INTEGER :: idaystp  ! Number of days between initial and current date 
    590       INTEGER :: idaycnt  ! Day counter 
    591  
    592       INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
    593  
    594       !----------------------------------------------------------------------- 
    595       ! Compute the calendar date YYYYMMDD 
    596       !----------------------------------------------------------------------- 
    597  
    598       ! Initial date 
    599       iyea0 =   kdate0 / 10000 
    600       imon0 = ( kdate0 - ( iyea0 * 10000 ) ) / 100 
    601       iday0 =   kdate0 - ( iyea0 * 10000 ) - ( imon0 * 100 )  
    602  
    603       ! Check that kt >= kit000 - 1 
    604       IF ( kt < kit000 - 1 ) CALL ctl_stop( ' kt must be >= kit000 - 1') 
    605  
    606       ! If kt = kit000 - 1 then set the date to the restart date 
    607       IF ( kt == kit000 - 1 ) THEN 
    608  
    609          kdate = ndastp 
    610          RETURN 
    611  
    612       ENDIF 
    613  
    614       ! Compute the number of days from the initial date 
    615       idaystp = INT( REAL( kt - kit000 ) * rdt / 86400. ) 
    616     
    617       iday    = iday0 
    618       imon    = imon0 
    619       iyea    = iyea0 
    620       idaycnt = 0 
    621  
    622       CALL calc_month_len( iyea, imonth_len ) 
    623  
    624       DO WHILE ( idaycnt < idaystp ) 
    625          iday = iday + 1 
    626          IF ( iday > imonth_len(imon) )  THEN 
    627             iday = 1 
    628             imon = imon + 1 
    629          ENDIF 
    630          IF ( imon > 12 ) THEN 
    631             imon = 1 
    632             iyea = iyea + 1 
    633             CALL calc_month_len( iyea, imonth_len )  ! update month lengths 
    634          ENDIF                  
    635          idaycnt = idaycnt + 1 
    636       END DO 
    637       ! 
    638       kdate = iyea * 10000 + imon * 100 + iday 
    639       ! 
    640    END SUBROUTINE 
    641  
    642  
    643    SUBROUTINE calc_month_len( iyear, imonth_len ) 
    644       !!---------------------------------------------------------------------- 
    645       !!                    ***  ROUTINE calc_month_len  *** 
    646       !!           
    647       !! ** Purpose : Compute the number of days in a months given a year. 
    648       !! 
    649       !! ** Method  :  
    650       !!---------------------------------------------------------------------- 
    651       INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
    652       INTEGER :: iyear         !: year 
    653       !!---------------------------------------------------------------------- 
    654       ! 
    655       ! length of the month of the current year (from nleapy, read in namelist) 
    656       IF ( nleapy < 2 ) THEN  
    657          imonth_len(:) = (/ 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31 /) 
    658          IF ( nleapy == 1 ) THEN   ! we are using calendar with leap years 
    659             IF ( MOD(iyear, 4) == 0 .AND. ( MOD(iyear, 400) == 0 .OR. MOD(iyear, 100) /= 0 ) ) THEN 
    660                imonth_len(2) = 29 
    661             ENDIF 
    662          ENDIF 
    663       ELSE 
    664          imonth_len(:) = nleapy   ! all months with nleapy days per year 
    665       ENDIF 
    666       ! 
    667    END SUBROUTINE 
    668  
    669567 
    670568   SUBROUTINE tra_asm_inc( kt ) 
  • branches/UKMO/dev_r5518_obs_oper_strthr/NEMOGCM/NEMO/OPA_SRC/BDY/bdytides.F90

    r7960 r15256  
    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 
     
    436436            ELSE 
    437437               ilen0(:)=nblenrim(:) 
    438             ENDIF      
     438            ENDIF 
    439439 
    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_obs_oper_strthr/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r7960 r15256  
    7373      !!---------------------------------------------------------------------- 
    7474      ! 
     75      ! max number of seconds between each restart 
     76      IF( REAL( nitend - nit000 + 1 ) * rdt > REAL( HUGE( nsec1jan000 ) ) ) THEN 
     77         CALL ctl_stop( 'The number of seconds between each restart exceeds the integer 4 max value: 2^31-1. ',   & 
     78            &           'You must do a restart at higher frequency (or remove this stop and recompile the code in I8)' ) 
     79      ENDIF 
    7580      ! all calendar staff is based on the fact that MOD( rday, rdttra(1) ) == 0 
    7681      IF( MOD( rday     , rdttra(1) ) /= 0. )   CALL ctl_stop( 'the time step must devide the number of second of in a day' ) 
     
    9095      nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 ) 
    9196 
    92       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 )   
    93101      IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < 0.1 / rday )   fjulday = REAL(NINT(fjulday),wp)   ! avoid truncation error 
    94       fjulday = fjulday + 1.                             ! move back to the day at nit000 (and not at nit000 - 1) 
     102      IF(nhour*3600 + nminute*60 - ndt05 .lt. 0)   fjulday = fjulday + 1.                    ! move back to the day at nit000 (and not at nit000 - 1) 
    95103 
    96104      nsec1jan000 = 0 
     
    113121      !compute number of days between last monday and today 
    114122      CALL ymds2ju( 1900, 01, 01, 0.0, zjul )  ! compute julian day value of 01.01.1900 (our reference that was a Monday) 
    115       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 
    116124      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 
    117126 
    118127      ! number of seconds since the beginning of current year/month/week/day at the middle of the time-step 
    119       nsec_year  = nday_year * nsecd - ndt05   ! 1 time step before the middle of the first time step 
    120       nsec_month = nday      * nsecd - ndt05   ! because day will be called at the beginning of step 
    121       nsec_week  = idweek    * nsecd - ndt05 
    122       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 
    123141 
    124142      ! control print 
    125       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 = ',   & 
    126            &                   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 
    127146 
    128147      ! Up to now, calendar parameters are related to the end of previous run (nit000-1) 
     
    238257               nday_year = 1 
    239258               nsec_year = ndt05 
    240                IF( nsec1jan000 >= 2 * (2**30 - nsecd * nyear_len(1) / 2 ) ) THEN   ! test integer 4 max value 
    241                   CALL ctl_stop( 'The number of seconds between Jan. 1st 00h of nit000 year and Jan. 1st 00h ',   & 
    242                      &           'of the current year is exceeding the INTEGER 4 max VALUE: 2^31-1 -> 68.09 years in seconds', & 
    243                      & 'You must do a restart at higher frequency (or remove this STOP and recompile everything in I8)' ) 
    244                ENDIF 
    245259               nsec1jan000 = nsec1jan000 + nsecd * nyear_len(1) 
    246260               IF( nleapy == 1 )   CALL day_mth 
     
    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 
     
    309324         IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN 
    310325            ! Get Calendar informations 
     326            IF(nn_timing == 2)  CALL timing_start('iom_rstget') 
    311327            CALL iom_get( numror, 'kt', zkt )   ! last time-step of previous run 
     328            IF(nn_timing == 2)  CALL timing_stop('iom_rstget') 
    312329            IF(lwp) THEN 
    313330               WRITE(numout,*) ' *** Info read in restart : ' 
     
    327344            ! define ndastp and adatrj 
    328345            IF ( nrstdt == 2 ) THEN 
     346               IF(nn_timing == 2)  CALL timing_start('iom_rstget') 
    329347               ! read the parameters correspondting to nit000 - 1 (last time step of previous run) 
    330348               CALL iom_get( numror, 'ndastp', zndastp ) 
    331349               ndastp = NINT( zndastp ) 
    332350               CALL iom_get( numror, 'adatrj', adatrj  ) 
     351          CALL iom_get( numror, 'ntime', ktime ) 
     352               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           
    333376            ELSE 
    334                ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
    335                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) 
    336382               adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    337383               ! note this is wrong if time step has changed during run 
    338384            ENDIF 
    339385         ELSE 
    340             ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day) 
    341             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) 
    342391            adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    343392         ENDIF 
     
    348397            WRITE(numout,*) '   date ndastp                                      : ', ndastp 
    349398            WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
     399            WRITE(numout,*) '   nn_time0                                         : ',nn_time0 
    350400            WRITE(numout,*) 
    351401         ENDIF 
     
    359409         ENDIF 
    360410         ! calendar control 
     411         IF(nn_timing == 2)  CALL timing_start('iom_rstput') 
    361412         CALL iom_rstput( kt, nitrst, numrow, 'kt'     , REAL( kt    , wp) )   ! time-step 
    362413         CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp) )   ! date 
    363414         CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj            )   ! number of elapsed days since 
    364415         !                                                                     ! the begining of the run [s] 
     416         CALL iom_rstput( kt, nitrst, numrow, 'ntime'  , REAL( nn_time0, wp) ) ! time 
     417         IF(nn_timing == 2)  CALL timing_stop('iom_rstput') 
    365418      ENDIF 
    366419      ! 
  • branches/UKMO/dev_r5518_obs_oper_strthr/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r7960 r15256  
    277277   INTEGER , PUBLIC ::   nmonth        !: current month 
    278278   INTEGER , PUBLIC ::   nday          !: current day of the month 
     279   INTEGER , PUBLIC ::   nhour         !: current hour 
     280   INTEGER , PUBLIC ::   nminute       !: current minute 
    279281   INTEGER , PUBLIC ::   ndastp        !: time step date in yyyymmdd format 
    280282   INTEGER , PUBLIC ::   nday_year     !: current day counted from jan 1st of the current year 
  • branches/UKMO/dev_r5518_obs_oper_strthr/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r7960 r15256  
    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 , 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,   & 
     
    179179         WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend 
    180180         WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0 
     181         WRITE(numout,*) '      initial time of day in hhmm     nn_time0   = ', nn_time0 
    181182         WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy 
    182183         WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate 
  • branches/UKMO/dev_r5518_obs_oper_strthr/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r7960 r15256  
    3737   INTEGER       ::   nn_itend         !: index of the last time step 
    3838   INTEGER       ::   nn_date0         !: initial calendar date aammjj 
     39   INTEGER       ::   nn_time0         !: initial time of day in hhmm 
    3940   INTEGER       ::   nn_leapy         !: Leap year calendar flag (0/1 or 30) 
    4041   INTEGER       ::   nn_istate        !: initial state output flag (0/1) 
  • branches/UKMO/dev_r5518_obs_oper_strthr/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r7960 r15256  
    115115      CASE (30)   ;   CALL xios_set_context_attr(TRIM(clname), calendar_type= "D360") 
    116116      END SELECT 
    117       WRITE(cldate,"(i4.4,'-',i2.2,'-',i2.2,' 00:00:00')") nyear,nmonth,nday  
     117      WRITE(cldate,"(i4.4,'-',i2.2,'-',i2.2,',i2.2,':',i2.2,':00')") nyear,nmonth,nday,nhour,nminute 
    118118      CALL xios_set_context_attr(TRIM(clname), start_date=cldate ) 
    119119 
  • branches/UKMO/dev_r5518_obs_oper_strthr/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r14591 r15256  
    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 ) 
  • branches/UKMO/dev_r5518_obs_oper_strthr/NEMOGCM/NEMO/OPA_SRC/OBS/obs_prep.F90

    r13393 r15256  
    133133      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    134134      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    135       ihou0 = 0 
    136       imin0 = 0 
     135      ihou0 =   nn_time0 / 100 
     136      imin0 = ( nn_time0 - ihou0 * 100 ) 
    137137 
    138138      icycle = no     ! Assimilation cycle 
     
    378378      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    379379      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    380       ihou0 = 0 
    381       imin0 = 0 
     380      ihou0 =   nn_time0 / 100 
     381      imin0 = ( nn_time0 - ihou0 * 100 ) 
    382382 
    383383      icycle = no     ! Assimilation cycle 
  • branches/UKMO/dev_r5518_obs_oper_strthr/NEMOGCM/NEMO/OPA_SRC/SBC/sbctide.F90

    r7960 r15256  
    4747      INTEGER, INTENT( in ) ::   kt     ! ocean time-step 
    4848      INTEGER               ::   jk     ! dummy loop index 
     49      INTEGER               ::   nsec_day_orig     ! Temporary variable 
    4950      !!---------------------------------------------------------------------- 
    5051 
    51       IF( nsec_day == NINT(0.5_wp * rdttra(1)) ) THEN      ! start a new day 
     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 
     73         ! 
    6274         CALL tide_harmo( omega_tide, v0tide, utide, ftide, ntide, nb_harmo ) 
    63          ! 
    64          kt_tide = kt 
    6575         ! 
    6676         IF(lwp) THEN 
     
    7484         ! 
    7585         IF( ln_tide_pot )   CALL tide_init_potential 
     86         ! 
     87         ! Reset nsec_day 
     88         nsec_day = nsec_day_orig 
    7689         ! 
    7790      ENDIF 
Note: See TracChangeset for help on using the changeset viewer.