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

Changeset 5997


Ignore:
Timestamp:
2015-12-03T17:04:43+01:00 (8 years ago)
Author:
timgraham
Message:

Merged branches/2014/dev_r4650_UKMO7_STARTHOUR into branch

Location:
branches/2015/dev_MetOffice_merge_2015/NEMOGCM
Files:
10 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/CONFIG/SHARED/namelist_ref

    r5992 r5997  
    3131   nn_itend    =    5475   !  last  time step (std 5475) 
    3232   nn_date0    =  010101   !  date at nit_0000 (format yyyymmdd) used if ln_rstart=F or (ln_rstart=T and nn_rstctl=0 or 1) 
     33   nn_time0    =       0   !  initial time of day in hhmm 
    3334   nn_leapy    =       0   !  Leap year calendar (1) or not (0) 
    3435   ln_rstart   = .false.   !  start from rest (F) or from a restart file (T) 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r5836 r5997  
    1111   !!             -   ! 2010-05  (D. Lea)  add calc_month_len routine based on day_init  
    1212   !!            3.4  ! 2012-10  (A. Weaver and K. Mogensen) Fix for direct initialization 
     13   !!                 ! 2014-09  (D. Lea)  Local calc_date removed use routine from OBS 
     14   !!                 ! 2015-11  (D. Lea)  Handle non-zero initial time of day 
    1315   !!---------------------------------------------------------------------- 
    1416 
    1517   !!---------------------------------------------------------------------- 
    1618   !!   asm_inc_init   : Initialize the increment arrays and IAU weights 
    17    !!   calc_date      : Compute the calendar date YYYYMMDD on a given step 
    1819   !!   tra_asm_inc    : Apply the tracer (T and S) increments 
    1920   !!   dyn_asm_inc    : Apply the dynamic (u and v) increments 
     
    3839#endif 
    3940   USE sbc_oce          ! Surface boundary condition variables. 
     41   USE diaobs, ONLY: calc_date     ! Compute the calendar date on a given step 
    4042 
    4143   IMPLICIT NONE 
     
    4345    
    4446   PUBLIC   asm_inc_init   !: Initialize the increment arrays and IAU weights 
    45    PUBLIC   calc_date      !: Compute the calendar date YYYYMMDD on a given step 
    4647   PUBLIC   tra_asm_inc    !: Apply the tracer (T and S) increments 
    4748   PUBLIC   dyn_asm_inc    !: Apply the dynamic (u and v) increments 
     
    111112      INTEGER :: iiauper         ! Number of time steps in the IAU period 
    112113      INTEGER :: icycper         ! Number of time steps in the cycle 
    113       INTEGER :: iitend_date     ! Date YYYYMMDD of final time step 
    114       INTEGER :: iitbkg_date     ! Date YYYYMMDD of background time step for Jb term 
    115       INTEGER :: iitdin_date     ! Date YYYYMMDD of background time step for DI 
    116       INTEGER :: iitiaustr_date  ! Date YYYYMMDD of IAU interval start time step 
    117       INTEGER :: iitiaufin_date  ! Date YYYYMMDD of IAU interval final time step 
    118       ! 
     114      REAL(KIND=dp) :: ditend_date     ! Date YYYYMMDD.HHMMSS of final time step 
     115      REAL(KIND=dp) :: ditbkg_date     ! Date YYYYMMDD.HHMMSS of background time step for Jb term 
     116      REAL(KIND=dp) :: ditdin_date     ! Date YYYYMMDD.HHMMSS of background time step for DI 
     117      REAL(KIND=dp) :: ditiaustr_date  ! Date YYYYMMDD.HHMMSS of IAU interval start time step 
     118      REAL(KIND=dp) :: ditiaufin_date  ! Date YYYYMMDD.HHMMSS of IAU interval final time step 
     119 
    119120      REAL(wp) :: znorm        ! Normalization factor for IAU weights 
    120121      REAL(wp) :: ztotwgt      ! Value of time-integrated IAU weights (should be equal to one) 
     
    178179      icycper = nitend      - nit000      + 1  ! Cycle interval length 
    179180 
    180       CALL calc_date( nit000, nitend     , ndate0, iitend_date    )     ! Date of final time step 
    181       CALL calc_date( nit000, nitbkg_r   , ndate0, iitbkg_date    )     ! Background time for Jb referenced to ndate0 
    182       CALL calc_date( nit000, nitdin_r   , ndate0, iitdin_date    )     ! Background time for DI referenced to ndate0 
    183       CALL calc_date( nit000, nitiaustr_r, ndate0, iitiaustr_date )     ! IAU start time referenced to ndate0 
    184       CALL calc_date( nit000, nitiaufin_r, ndate0, iitiaufin_date )     ! IAU end time referenced to ndate0 
    185       ! 
     181      ! Date of final time step 
     182      CALL calc_date( nitend, ditend_date ) 
     183 
     184      ! Background time for Jb referenced to ndate0 
     185      CALL calc_date( nitbkg_r, ditbkg_date ) 
     186 
     187      ! Background time for DI referenced to ndate0 
     188      CALL calc_date( nitdin_r, ditdin_date ) 
     189 
     190      ! IAU start time referenced to ndate0 
     191      CALL calc_date( nitiaustr_r, ditiaustr_date ) 
     192 
     193      ! IAU end time referenced to ndate0 
     194      CALL calc_date( nitiaufin_r, ditiaufin_date ) 
     195 
    186196      IF(lwp) THEN 
    187197         WRITE(numout,*) 
     
    198208         WRITE(numout,*) '       ndastp         = ', ndastp 
    199209         WRITE(numout,*) '       ndate0         = ', ndate0 
    200          WRITE(numout,*) '       iitend_date    = ', iitend_date 
    201          WRITE(numout,*) '       iitbkg_date    = ', iitbkg_date 
    202          WRITE(numout,*) '       iitdin_date    = ', iitdin_date 
    203          WRITE(numout,*) '       iitiaustr_date = ', iitiaustr_date 
    204          WRITE(numout,*) '       iitiaufin_date = ', iitiaufin_date 
     210         WRITE(numout,*) '       nn_time0       = ', nn_time0 
     211         WRITE(numout,*) '       ditend_date    = ', ditend_date 
     212         WRITE(numout,*) '       ditbkg_date    = ', ditbkg_date 
     213         WRITE(numout,*) '       ditdin_date    = ', ditdin_date 
     214         WRITE(numout,*) '       ditiaustr_date = ', ditiaustr_date 
     215         WRITE(numout,*) '       ditiaufin_date = ', ditiaufin_date 
    205216      ENDIF 
    206217 
     
    360371            WRITE(numout,*)  
    361372            WRITE(numout,*) 'asm_inc_init : Assimilation increments valid ', & 
    362                &            ' between dates ', NINT( z_inc_dateb ),' and ',  & 
    363                &            NINT( z_inc_datef ) 
     373               &            ' between dates ', z_inc_dateb,' and ',  & 
     374               &            z_inc_datef 
    364375            WRITE(numout,*) '~~~~~~~~~~~~' 
    365376         ENDIF 
    366377 
    367          IF (     ( NINT( z_inc_dateb ) < ndastp      ) & 
    368             & .OR.( NINT( z_inc_datef ) > iitend_date ) ) & 
     378         IF (     ( z_inc_dateb < ndastp + nn_time0*0.0001_wp ) & 
     379            & .OR.( z_inc_datef > ditend_date ) ) & 
    369380            & CALL ctl_warn( ' Validity time of assimilation increments is ', & 
    370381            &                ' outside the assimilation interval' ) 
    371382 
    372          IF ( ( ln_asmdin ).AND.( NINT( zdate_inc ) /= iitdin_date ) ) & 
     383         IF ( ( ln_asmdin ).AND.( zdate_inc /= ditdin_date ) ) & 
    373384            & CALL ctl_warn( ' Validity time of assimilation increments does ', & 
    374385            &                ' not agree with Direct Initialization time' ) 
     
    490501         IF(lwp) THEN 
    491502            WRITE(numout,*)  
    492             WRITE(numout,*) 'asm_inc_init : Assimilation background state valid at : ', NINT( zdate_bkg ) 
     503            WRITE(numout,*) 'asm_inc_init : Assimilation background state valid at : ', & 
     504               &  zdate_bkg 
    493505            WRITE(numout,*) '~~~~~~~~~~~~' 
    494506         ENDIF 
    495507         ! 
    496          IF ( NINT( zdate_bkg ) /= iitdin_date ) & 
     508         IF ( zdate_bkg /= ditdin_date ) & 
    497509            & CALL ctl_warn( ' Validity time of assimilation background state does', & 
    498510            &                ' not agree with Direct Initialization time' ) 
     
    522534      ! 
    523535   END SUBROUTINE asm_inc_init 
    524  
    525  
    526    SUBROUTINE calc_date( kit000, kt, kdate0, kdate ) 
    527       !!---------------------------------------------------------------------- 
    528       !!                    ***  ROUTINE calc_date  *** 
    529       !!           
    530       !! ** Purpose : Compute the calendar date YYYYMMDD at a given time step. 
    531       !! 
    532       !! ** Method  : Compute the calendar date YYYYMMDD at a given time step. 
    533       !! 
    534       !! ** Action  :  
    535       !!---------------------------------------------------------------------- 
    536       INTEGER, INTENT(IN) :: kit000  ! Initial time step 
    537       INTEGER, INTENT(IN) :: kt      ! Current time step referenced to kit000 
    538       INTEGER, INTENT(IN) :: kdate0  ! Initial date 
    539       INTEGER, INTENT(OUT) :: kdate  ! Current date reference to kdate0 
    540       ! 
    541       INTEGER :: iyea0    ! Initial year 
    542       INTEGER :: imon0    ! Initial month 
    543       INTEGER :: iday0    ! Initial day 
    544       INTEGER :: iyea     ! Current year 
    545       INTEGER :: imon     ! Current month 
    546       INTEGER :: iday     ! Current day 
    547       INTEGER :: idaystp  ! Number of days between initial and current date 
    548       INTEGER :: idaycnt  ! Day counter 
    549  
    550       INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
    551  
    552       !----------------------------------------------------------------------- 
    553       ! Compute the calendar date YYYYMMDD 
    554       !----------------------------------------------------------------------- 
    555  
    556       ! Initial date 
    557       iyea0 =   kdate0 / 10000 
    558       imon0 = ( kdate0 - ( iyea0 * 10000 ) ) / 100 
    559       iday0 =   kdate0 - ( iyea0 * 10000 ) - ( imon0 * 100 )  
    560  
    561       ! Check that kt >= kit000 - 1 
    562       IF ( kt < kit000 - 1 ) CALL ctl_stop( ' kt must be >= kit000 - 1') 
    563  
    564       ! If kt = kit000 - 1 then set the date to the restart date 
    565       IF ( kt == kit000 - 1 ) THEN 
    566          kdate = ndastp 
    567          RETURN 
    568       ENDIF 
    569  
    570       ! Compute the number of days from the initial date 
    571       idaystp = INT( REAL( kt - kit000 ) * rdt / 86400. ) 
    572     
    573       iday    = iday0 
    574       imon    = imon0 
    575       iyea    = iyea0 
    576       idaycnt = 0 
    577  
    578       CALL calc_month_len( iyea, imonth_len ) 
    579  
    580       DO WHILE ( idaycnt < idaystp ) 
    581          iday = iday + 1 
    582          IF ( iday > imonth_len(imon) )  THEN 
    583             iday = 1 
    584             imon = imon + 1 
    585          ENDIF 
    586          IF ( imon > 12 ) THEN 
    587             imon = 1 
    588             iyea = iyea + 1 
    589             CALL calc_month_len( iyea, imonth_len )  ! update month lengths 
    590          ENDIF                  
    591          idaycnt = idaycnt + 1 
    592       END DO 
    593       ! 
    594       kdate = iyea * 10000 + imon * 100 + iday 
    595       ! 
    596    END SUBROUTINE 
    597  
    598  
    599    SUBROUTINE calc_month_len( iyear, imonth_len ) 
    600       !!---------------------------------------------------------------------- 
    601       !!                    ***  ROUTINE calc_month_len  *** 
    602       !!           
    603       !! ** Purpose : Compute the number of days in a months given a year. 
    604       !! 
    605       !! ** Method  :  
    606       !!---------------------------------------------------------------------- 
    607       INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
    608       INTEGER :: iyear         !: year 
    609       !!---------------------------------------------------------------------- 
    610       ! 
    611       ! length of the month of the current year (from nleapy, read in namelist) 
    612       IF ( nleapy < 2 ) THEN  
    613          imonth_len(:) = (/ 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31 /) 
    614          IF ( nleapy == 1 ) THEN   ! we are using calendar with leap years 
    615             IF ( MOD(iyear, 4) == 0 .AND. ( MOD(iyear, 400) == 0 .OR. MOD(iyear, 100) /= 0 ) ) THEN 
    616                imonth_len(2) = 29 
    617             ENDIF 
    618          ENDIF 
    619       ELSE 
    620          imonth_len(:) = nleapy   ! all months with nleapy days per year 
    621       ENDIF 
    622       ! 
    623    END SUBROUTINE 
    624  
    625  
    626536   SUBROUTINE tra_asm_inc( kt ) 
    627537      !!---------------------------------------------------------------------- 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/BDY/bdytides.F90

    r5930 r5997  
    5757   !!---------------------------------------------------------------------- 
    5858   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    59    !! $Id$  
     59   !! $Id$ 
    6060   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    6161   !!---------------------------------------------------------------------- 
     
    323323      ENDIF 
    324324 
    325       IF ( nsec_day == NINT(0.5_wp * rdttra(1)) .AND. zflag==1 ) THEN 
     325      IF ( (nsec_day == NINT(0.5_wp * rdttra(1)) .OR. kt==nit000) .AND. zflag==1 ) THEN 
    326326        ! 
    327         kt_tide = kt 
     327        kt_tide = kt - (nsec_day - 0.5_wp * rdttra(1))/rdttra(1) 
    328328        ! 
    329329        IF(lwp) THEN 
     
    438438            ! We refresh nodal factors every day below 
    439439            ! This should be done somewhere else 
    440             IF ( nsec_day == NINT(0.5_wp * rdttra(1)) .AND. lk_first_btstp ) THEN 
    441                ! 
    442                kt_tide = kt                
     440            IF ( ( nsec_day == NINT(0.5_wp * rdttra(1)) .OR. kt==nit000 ) .AND. lk_first_btstp ) THEN 
     441               ! 
     442               kt_tide = kt - (nsec_day - 0.5_wp * rdttra(1))/rdttra(1) 
    443443               ! 
    444444               IF(lwp) THEN 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r5563 r5997  
    1111   !!                 ! 2004-01  (A.M. Treguier) new calculation based on adatrj 
    1212   !!                 ! 2006-08  (G. Madec)  surface module major update 
     13   !!                 ! 2015-11  (D. Lea) Allow non-zero initial time of day 
    1314   !!---------------------------------------------------------------------- 
    1415 
     
    9596      nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 ) 
    9697 
    97       CALL ymds2ju( nyear, nmonth, nday, 0.0, fjulday )  ! we assume that we start run at 00:00 
     98      nhour   =   nn_time0 / 100 
     99      nminute = ( nn_time0 - nhour * 100 ) 
     100 
     101      CALL ymds2ju( nyear, nmonth, nday, nhour*3600._wp+nminute*60._wp, fjulday )   
    98102      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) 
     103      IF( nn_time0*3600 - ndt05 .lt. 0 ) fjulday = fjulday + 1.                    ! move back to the day at nit000 (and not at nit000 - 1) 
    100104 
    101105      nsec1jan000 = 0 
     
    118122      !compute number of days between last monday and today 
    119123      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 
     124      inbday = FLOOR(fjulday - zjul)            ! compute nb day between  01.01.1900 and start of current day 
    121125      idweek = MOD(inbday, 7)                  ! compute nb day between last monday and current day 
     126      IF (idweek .lt. 0) idweek=idweek+7       ! Avoid negative values for dates before 01.01.1900 
    122127 
    123128      ! 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 
     129      IF (nhour*3600+nminute*60-ndt05 .gt. 0) THEN 
     130         ! 1 timestep before current middle of first time step is still the same day 
     131         nsec_year  = (nday_year-1) * nsecd + nhour*3600+nminute*60 - ndt05  
     132         nsec_month = (nday-1)      * nsecd + nhour*3600+nminute*60 - ndt05     
     133      ELSE 
     134         ! 1 time step before the middle of the first time step is the previous day  
     135         nsec_year  = nday_year * nsecd + nhour*3600+nminute*60 - ndt05  
     136         nsec_month = nday      * nsecd + nhour*3600+nminute*60 - ndt05    
     137      ENDIF 
     138      nsec_week  = idweek    * nsecd + nhour*3600+nminute*60 - ndt05 
     139      nsec_day   =             nhour*3600+nminute*60 - ndt05  
     140      IF( nsec_day .lt. 0 ) nsec_day = nsec_day + nsecd 
     141      IF( nsec_week .lt. 0 ) nsec_week = nsec_week + nsecd*7 
    128142 
    129143      ! 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 
     144      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 = ',   & 
     145           &                   nyear, '/', nmonth, '/', nday, '  nsec_day:', nsec_day, '  nsec_week:', nsec_week, '  & 
     146           &                   nsec_month:', nsec_month , '  nsec_year:' , nsec_year 
    132147 
    133148      ! Up to now, calendar parameters are related to the end of previous run (nit000-1) 
     
    302317      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag 
    303318      ! 
    304       REAL(wp) ::   zkt, zndastp 
     319      REAL(wp) ::   zkt, zndastp, zdayfrac, ksecs, ktime 
     320      INTEGER  ::   ihour, iminute 
    305321      !!---------------------------------------------------------------------- 
    306322 
     
    327343            ! define ndastp and adatrj 
    328344            IF ( nrstdt == 2 ) THEN 
    329                ! read the parameters correspondting to nit000 - 1 (last time step of previous run) 
     345               ! read the parameters corresponding to nit000 - 1 (last time step of previous run) 
    330346               CALL iom_get( numror, 'ndastp', zndastp ) 
    331347               ndastp = NINT( zndastp ) 
    332348               CALL iom_get( numror, 'adatrj', adatrj  ) 
     349          CALL iom_get( numror, 'ntime', ktime ) 
     350          nn_time0=INT(ktime) 
     351               ! calculate start time in hours and minutes 
     352          zdayfrac=adatrj-INT(adatrj) 
     353          ksecs = NINT(zdayfrac*86400)        ! Nearest second to catch rounding errors in adatrj          
     354          ihour = INT(ksecs/3600) 
     355          iminute = ksecs/60-ihour*60 
     356            
     357               ! Add to nn_time0 
     358               nhour   =   nn_time0 / 100 
     359               nminute = ( nn_time0 - nhour * 100 ) 
     360          nminute=nminute+iminute 
     361           
     362          IF( nminute >= 60 ) THEN 
     363             nminute=nminute-60 
     364        nhour=nhour+1 
     365          ENDIF 
     366          nhour=nhour+ihour 
     367          IF( nhour >= 24 ) THEN 
     368        nhour=nhour-24 
     369             adatrj=adatrj+1 
     370          ENDIF           
     371          nn_time0 = nhour * 100 + nminute 
     372          adatrj = INT(adatrj)                    ! adatrj set to integer as nn_time0 updated           
    333373            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 
     374               ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) 
     375               ndastp = ndate0        ! ndate0 read in the namelist in dom_nam 
     376               nhour   =   nn_time0 / 100 
     377               nminute = ( nn_time0 - nhour * 100 ) 
     378               IF( nhour*3600+nminute*60-ndt05 .lt. 0 )  ndastp=ndastp-1      ! Start hour is specified in the namelist (default 0) 
    336379               adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    337380               ! note this is wrong if time step has changed during run 
    338381            ENDIF 
    339382         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 
     383            ! parameters corresponding to nit000 - 1 (as we start the step loop with a call to day) 
     384            ndastp = ndate0           ! ndate0 read in the namelist in dom_nam 
     385            nhour   =   nn_time0 / 100 
     386       nminute = ( nn_time0 - nhour * 100 ) 
     387            IF( nhour*3600+nminute*60-ndt05 .lt. 0 )  ndastp=ndastp-1      ! Start hour is specified in the namelist (default 0) 
    342388            adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    343389         ENDIF 
     
    348394            WRITE(numout,*) '   date ndastp                                      : ', ndastp 
    349395            WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
     396       WRITE(numout,*) '   nn_time0                                         : ',nn_time0 
    350397            WRITE(numout,*) 
    351398         ENDIF 
     
    363410         CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj            )   ! number of elapsed days since 
    364411         !                                                                     ! the begining of the run [s] 
     412    CALL iom_rstput( kt, nitrst, numrow, 'ntime'  , REAL( nn_time0, wp) ) ! time 
    365413      ENDIF 
    366414      ! 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r5930 r5997  
    271271   INTEGER , PUBLIC ::   nmonth        !: current month 
    272272   INTEGER , PUBLIC ::   nday          !: current day of the month 
     273   INTEGER , PUBLIC ::   nhour         !: current hour 
     274   INTEGER , PUBLIC ::   nminute       !: current minute 
    273275   INTEGER , PUBLIC ::   ndastp        !: time step date in yyyymmdd format 
    274276   INTEGER , PUBLIC ::   nday_year     !: current day counted from jan 1st of the current year 
     
    307309   !!---------------------------------------------------------------------- 
    308310   !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
    309    !! $Id$  
     311   !! $Id$ 
    310312   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    311313   !!---------------------------------------------------------------------- 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r5836 r5997  
    136136      USE ioipsl 
    137137      NAMELIST/namrun/ cn_ocerst_indir, cn_ocerst_outdir, nn_stocklist, ln_rst_list,               & 
    138          &             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 ,   & 
    140          &             nn_write, ln_dimgnnn, ln_mskland  , ln_cfmeta    , ln_clobber, nn_chunksz, nn_euler 
     138                       nn_no   , cn_exp  , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl ,  & 
     139         &             nn_it000, nn_itend, nn_date0    , nn_time0     , nn_leapy  , nn_istate ,  & 
     140         &             nn_stock, nn_write, ln_dimgnnn  , ln_mskland   , ln_clobber, nn_chunksz,  & 
     141         &             nn_euler, ln_cfmeta 
    141142      NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,   & 
    142143         &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,                  & 
     
    178179         WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend 
    179180         WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0 
     181         WRITE(numout,*) '      initial time of day in hhmm     nn_time0   = ', nn_time0 
    180182         WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy 
    181183         WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r5960 r5997  
    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/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r5992 r5997  
    1212   !!   dia_obs      : Compute model equivalent to observations 
    1313   !!   dia_obs_wri  : Write observational diagnostics 
     14   !!   calc_date    : Compute the date of timestep in YYYYMMDD.HHMMSS format 
    1415   !!   ini_date     : Compute the initial date YYYYMMDD.HHMMSS 
    1516   !!   fin_date     : Compute the final date YYYYMMDD.HHMMSS 
     
    5152      &   dia_obs,      &  ! Compute model equivalent to observations 
    5253      &   dia_obs_wri,  &  ! Write model equivalent to observations 
    53       &   dia_obs_dealloc  ! Deallocate dia_obs data 
     54      &   dia_obs_dealloc, &  ! Deallocate dia_obs data 
     55      &   calc_date           ! Compute the date of a timestep 
    5456 
    5557   !! * Shared Module variables 
     
    218220      !----------------------------------------------------------------------- 
    219221       
    220       !Initalise all values in namelist arrays  
    221       enactfiles(:) = ''  
    222       coriofiles(:) = ''  
    223       profbfiles(:) = ''  
    224       slafilesact(:) = ''  
    225       slafilespas(:) = ''  
    226       slafbfiles(:) = ''  
    227       sstfiles(:)   = ''  
    228       sstfbfiles(:) = ''  
    229       seaicefiles(:) = ''  
    230       velcurfiles(:) = ''  
    231       velavcurfiles(:) = ''  
    232       velhrcurfiles(:) = ''  
    233       velavadcpfiles(:) = ''  
    234       velhradcpfiles(:) = ''  
    235       velfbfiles(:) = ''  
     222      !Initalise all values in namelist arrays 
     223      enactfiles(:) = '' 
     224      coriofiles(:) = '' 
     225      profbfiles(:) = '' 
     226      slafilesact(:) = '' 
     227      slafilespas(:) = '' 
     228      slafbfiles(:) = '' 
     229      sstfiles(:)   = '' 
     230      sstfbfiles(:) = '' 
     231      seaicefiles(:) = '' 
     232      velcurfiles(:) = '' 
    236233      veladcpfiles(:) = '' 
    237       sstbias_files(:) = ''   
    238       endailyavtypes(:) = -1  
    239       endailyavtypes(1) = 820  
    240       ln_profb_ena(:) = .FALSE.  
    241       ln_profb_enatim(:) = .TRUE.  
    242       ln_velfb_av(:) = .FALSE.  
    243       ln_ignmis = .FALSE.  
     234      velavcurfiles(:) = '' 
     235      velhrcurfiles(:) = '' 
     236      velavadcpfiles(:) = '' 
     237      velhradcpfiles(:) = '' 
     238      velfbfiles(:) = '' 
     239      velcurfiles(:) = '' 
     240      veladcpfiles(:) = '' 
     241      endailyavtypes(:) = -1 
     242      endailyavtypes(1) = 820 
     243      ln_profb_ena(:) = .FALSE. 
     244      ln_profb_enatim(:) = .TRUE. 
     245      ln_velfb_av(:) = .FALSE. 
     246      ln_ignmis = .FALSE.       
    244247 
    245248      CALL ini_date( dobsini ) 
     
    14841487   END SUBROUTINE dia_obs_dealloc 
    14851488 
    1486    SUBROUTINE ini_date( ddobsini ) 
    1487       !!---------------------------------------------------------------------- 
    1488       !!                    ***  ROUTINE ini_date  *** 
     1489   SUBROUTINE calc_date( kstp, ddobs ) 
     1490      !!---------------------------------------------------------------------- 
     1491      !!                    ***  ROUTINE calc_date  *** 
    14891492      !!           
    1490       !! ** Purpose : Get initial data in double precision YYYYMMDD.HHMMSS format 
    1491       !! 
    1492       !! ** Method  : Get initial data in double precision YYYYMMDD.HHMMSS format 
    1493       !! 
    1494       !! ** Action  : Get initial data in double precision YYYYMMDD.HHMMSS format 
     1493      !! ** Purpose : Get date in double precision YYYYMMDD.HHMMSS format 
     1494      !! 
     1495      !! ** Method  : Get date in double precision YYYYMMDD.HHMMSS format 
     1496      !! 
     1497      !! ** Action  : Get date in double precision YYYYMMDD.HHMMSS format 
    14951498      !! 
    14961499      !! History : 
     
    15001503      !!        !  06-10  (G. Smith) Calculates initial date the same as method for final date 
    15011504      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
     1505      !!        !  2014-09  (D. Lea) New generic routine now deals with arbitrary initial time of day 
    15021506      !!---------------------------------------------------------------------- 
    15031507      USE phycst, ONLY : &            ! Physical constants 
     
    15111515 
    15121516      !! * Arguments 
    1513       REAL(KIND=dp), INTENT(OUT) :: ddobsini                         ! Initial date in YYYYMMDD.HHMMSS 
     1517      REAL(KIND=dp), INTENT(OUT) :: ddobs                        ! Date in YYYYMMDD.HHMMSS 
     1518      INTEGER :: kstp 
    15141519 
    15151520      !! * Local declarations 
     
    15261531      !!---------------------------------------------------------------------- 
    15271532      !! Initial date initialization (year, month, day, hour, minute) 
    1528       !! (This assumes that the initial date is for 00z)) 
    15291533      !!---------------------------------------------------------------------- 
    15301534      iyea =   ndate0 / 10000 
    15311535      imon = ( ndate0 - iyea * 10000 ) / 100 
    15321536      iday =   ndate0 - iyea * 10000 - imon * 100 
    1533       ihou = 0 
    1534       imin = 0 
     1537      ihou =   nn_time0 / 100 
     1538      imin = ( nn_time0 - ihou * 100 )  
    15351539 
    15361540      !!---------------------------------------------------------------------- 
    15371541      !! Compute number of days + number of hours + min since initial time 
    15381542      !!---------------------------------------------------------------------- 
    1539       iday = iday + ( nit000 -1 ) * rdt / rday 
    1540       zdayfrc = ( nit000 -1 ) * rdt / rday 
     1543      zdayfrc = kstp * rdt / rday 
    15411544      zdayfrc = zdayfrc - aint(zdayfrc) 
    1542       ihou = int( zdayfrc * 24 ) 
    1543       imin = int( (zdayfrc * 24 - ihou) * 60 ) 
     1545      imin = imin + int( zdayfrc * 24 * 60 )  
     1546      DO WHILE (imin >= 60)  
     1547        imin=imin-60 
     1548        ihou=ihou+1 
     1549      END DO 
     1550      DO WHILE (ihou >= 24) 
     1551        ihou=ihou-24 
     1552        iday=iday+1 
     1553      END DO  
     1554      iday = iday + kstp * rdt / rday  
    15441555 
    15451556      !!----------------------------------------------------------------------- 
     
    15621573      !! Convert it into YYYYMMDD.HHMMSS format. 
    15631574      !!---------------------------------------------------------------------- 
    1564       ddobsini = iyea * 10000_dp + imon * 100_dp + & 
    1565          &       iday + ihou * 0.01_dp + imin * 0.0001_dp 
    1566  
    1567  
    1568    END SUBROUTINE ini_date 
    1569  
    1570    SUBROUTINE fin_date( ddobsfin ) 
    1571       !!---------------------------------------------------------------------- 
    1572       !!                    ***  ROUTINE fin_date  *** 
     1575      ddobs = iyea * 10000_dp + imon * 100_dp + & 
     1576         &    iday + ihou * 0.01_dp + imin * 0.0001_dp 
     1577 
     1578   END SUBROUTINE calc_date 
     1579 
     1580   SUBROUTINE ini_date( ddobsini ) 
     1581      !!---------------------------------------------------------------------- 
     1582      !!                    ***  ROUTINE ini_date  *** 
    15731583      !!           
    1574       !! ** Purpose : Get final data in double precision YYYYMMDD.HHMMSS format 
    1575       !! 
    1576       !! ** Method  : Get final data in double precision YYYYMMDD.HHMMSS format 
    1577       !! 
    1578       !! ** Action  : Get final data in double precision YYYYMMDD.HHMMSS format 
     1584      !! ** Purpose : Get initial date in double precision YYYYMMDD.HHMMSS format 
     1585      !! 
     1586      !! ** Method  :  
     1587      !! 
     1588      !! ** Action  :  
    15791589      !! 
    15801590      !! History : 
     
    15831593      !!        !  06-10  (A. Weaver) Cleaning 
    15841594      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
    1585       !!---------------------------------------------------------------------- 
    1586       USE phycst, ONLY : &            ! Physical constants 
    1587          & rday 
    1588 !      USE daymod, ONLY : &            ! Time variables 
    1589 !         & nmonth_len                 
    1590       USE dom_oce, ONLY : &           ! Ocean space and time domain variables 
    1591          & rdt 
     1595      !!        !  2014-09  (D. Lea) Change to call generic routine calc_date 
     1596      !!---------------------------------------------------------------------- 
     1597 
     1598      IMPLICIT NONE 
     1599 
     1600      !! * Arguments 
     1601      REAL(KIND=dp), INTENT(OUT) :: ddobsini                   ! Initial date in YYYYMMDD.HHMMSS 
     1602 
     1603      CALL calc_date( nit000 - 1, ddobsini ) 
     1604 
     1605   END SUBROUTINE ini_date 
     1606 
     1607   SUBROUTINE fin_date( ddobsfin ) 
     1608      !!---------------------------------------------------------------------- 
     1609      !!                    ***  ROUTINE fin_date  *** 
     1610      !!           
     1611      !! ** Purpose : Get final date in double precision YYYYMMDD.HHMMSS format 
     1612      !! 
     1613      !! ** Method  :  
     1614      !! 
     1615      !! ** Action  :  
     1616      !! 
     1617      !! History : 
     1618      !!        !  06-03  (K. Mogensen)  Original code 
     1619      !!        !  06-05  (K. Mogensen)  Reformatted 
     1620      !!        !  06-10  (A. Weaver) Cleaning 
     1621      !!        !  10-05  (D. Lea) Update to month length calculation for NEMO vn3.2 
     1622      !!        !  2014-09  (D. Lea) Change to call generic routine calc_date 
     1623      !!---------------------------------------------------------------------- 
    15921624 
    15931625      IMPLICIT NONE 
     
    15961628      REAL(KIND=dp), INTENT(OUT) :: ddobsfin                   ! Final date in YYYYMMDD.HHMMSS 
    15971629 
    1598       !! * Local declarations 
    1599       INTEGER :: iyea        ! date - (year, month, day, hour, minute) 
    1600       INTEGER :: imon 
    1601       INTEGER :: iday 
    1602       INTEGER :: ihou 
    1603       INTEGER :: imin 
    1604       INTEGER :: imday         ! Number of days in month. 
    1605       REAL(KIND=wp) :: zdayfrc       ! Fraction of day 
    1606           
    1607       INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
    1608              
    1609       !----------------------------------------------------------------------- 
    1610       ! Initial date initialization (year, month, day, hour, minute) 
    1611       ! (This assumes that the initial date is for 00z) 
    1612       !----------------------------------------------------------------------- 
    1613       iyea =   ndate0 / 10000 
    1614       imon = ( ndate0 - iyea * 10000 ) / 100 
    1615       iday =   ndate0 - iyea * 10000 - imon * 100 
    1616       ihou = 0 
    1617       imin = 0 
    1618        
    1619       !----------------------------------------------------------------------- 
    1620       ! Compute number of days + number of hours + min since initial time 
    1621       !----------------------------------------------------------------------- 
    1622       iday    = iday +  nitend  * rdt / rday 
    1623       zdayfrc =  nitend  * rdt / rday 
    1624       zdayfrc = zdayfrc - AINT( zdayfrc ) 
    1625       ihou    = INT( zdayfrc * 24 ) 
    1626       imin    = INT( ( zdayfrc * 24 - ihou ) * 60 ) 
    1627  
    1628       !----------------------------------------------------------------------- 
    1629       ! Convert number of days (iday) into a real date 
    1630       !---------------------------------------------------------------------- 
    1631  
    1632       CALL calc_month_len( iyea, imonth_len ) 
    1633        
    1634       DO WHILE ( iday > imonth_len(imon) ) 
    1635          iday = iday - imonth_len(imon) 
    1636          imon = imon + 1  
    1637          IF ( imon > 12 ) THEN 
    1638             imon = 1 
    1639             iyea = iyea + 1 
    1640             CALL calc_month_len( iyea, imonth_len )  ! update month lengths 
    1641          ENDIF 
    1642       END DO 
    1643  
    1644       !----------------------------------------------------------------------- 
    1645       ! Convert it into YYYYMMDD.HHMMSS format 
    1646       !----------------------------------------------------------------------- 
    1647       ddobsfin = iyea * 10000_dp + imon * 100_dp    + iday & 
    1648          &     + ihou * 0.01_dp  + imin * 0.0001_dp 
    1649  
    1650     END SUBROUTINE fin_date 
    1651      
     1630      CALL calc_date( nitend, ddobsfin ) 
     1631 
     1632   END SUBROUTINE fin_date 
     1633    
    16521634END MODULE diaobs 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/OBS/obs_prep.F90

    r5963 r5997  
    128128      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    129129      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    130       ihou0 = 0 
    131       imin0 = 0 
     130      ihou0 =   nn_time0 / 100 
     131      imin0 = ( nn_time0 - ihou0 * 100 ) 
    132132 
    133133      icycle = no     ! Assimilation cycle 
     
    400400      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    401401      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    402       ihou0 = 0 
    403       imin0 = 0 
     402      ihou0 =   nn_time0 / 100 
     403      imin0 = ( nn_time0 - ihou0 * 100 ) 
    404404 
    405405      icycle = no     ! Assimilation cycle 
     
    588588      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    589589      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    590       ihou0 = 0 
    591       imin0 = 0 
     590      ihou0 =   nn_time0 / 100 
     591      imin0 = ( nn_time0 - ihou0 * 100 ) 
    592592 
    593593      icycle = no     ! Assimilation cycle 
     
    773773      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    774774      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    775       ihou0 = 0 
    776       imin0 = 0 
     775      ihou0 =   nn_time0 / 100 
     776      imin0 = ( nn_time0 - ihou0 * 100 ) 
    777777 
    778778      icycle = no     ! Assimilation cycle 
     
    971971      imon0 = ( ndate0 - iyea0 * 10000 ) / 100 
    972972      iday0 =   ndate0 - iyea0 * 10000 - imon0 * 100 
    973       ihou0 = 0 
    974       imin0 = 0 
     973      ihou0 =   nn_time0 / 100 
     974      imin0 = ( nn_time0 - ihou0 * 100 ) 
    975975 
    976976      icycle = no     ! Assimilation cycle 
  • branches/2015/dev_MetOffice_merge_2015/NEMOGCM/NEMO/OPA_SRC/SBC/sbctide.F90

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