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 4811 for branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM – NEMO

Ignore:
Timestamp:
2014-10-08T15:49:12+02:00 (10 years ago)
Author:
djlea
Message:

Update reference namelists with nn_time0. Fix to daymod. Fix to offline domain.F90 to get nn_time0 from the namelist. Assimilation date time updates.

Location:
branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/CONFIG/SHARED/1_namelist_ref

    r4347 r4811  
    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 hours 
    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) 
     
    10671068                           !     ln_ssh                  Logical switch for SSH observations 
    10681069 
    1069    ln_sst     = .true.     ! Logical switch for SST observations 
    1070    ln_reysst  = .true.     !     ln_reysst               Logical switch for Reynolds observations 
     1070   ln_sst     = .false.     ! Logical switch for SST observations 
     1071   ln_reysst  = .false.     !     ln_reysst               Logical switch for Reynolds observations 
    10711072   ln_ghrsst  = .false.    !     ln_ghrsst               Logical switch for GHRSST observations       
    10721073 
    10731074   ln_sstfb   = .false.    ! Logical switch for feedback SST data 
    10741075                           !     ln_sss                  Logical switch for SSS observations 
    1075                            !     ln_seaice              Logical switch for Sea Ice observations 
     1076   ln_seaice  = .false.    ! Logical switch for Sea Ice observations 
    10761077                           !     ln_vel3d                Logical switch for velocity observations 
    10771078                           !     ln_velavcur             Logical switch for velocity daily av. cur. 
     
    10941095                           !     sstfiles                GHRSST input observation file name 
    10951096   !                       ! sstfbfiles: Feedback SST input observation file name 
    1096    sstfbfiles = 'sst_01.nc' 'sst_02.nc' 'sst_03.nc' 'sst_04.nc' 'sst_05.nc' 
     1097   sstfbfiles = 'sst_01.nc' 
    10971098                           !     seaicefiles             Sea Ice input observation file name 
     1099   seaicefiles = 'seaice_01.nc' 
    10981100                           !     velavcurfiles           Vel. cur. daily av. input file name 
    10991101                           !     velhvcurfiles           Vel. cur. high freq. input file name 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/CONFIG/SHARED/namelist_ref

    r4384 r4811  
    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 hours 
    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) 
     
    10851086                           !     ln_ssh                  Logical switch for SSH observations 
    10861087 
    1087    ln_sst     = .true.     ! Logical switch for SST observations 
    1088    ln_reysst  = .true.     !     ln_reysst               Logical switch for Reynolds observations 
     1088   ln_sst     = .false.     ! Logical switch for SST observations 
     1089   ln_reysst  = .false.     !     ln_reysst               Logical switch for Reynolds observations 
    10891090   ln_ghrsst  = .false.    !     ln_ghrsst               Logical switch for GHRSST observations       
    10901091 
    10911092   ln_sstfb   = .false.    ! Logical switch for feedback SST data 
    10921093                           !     ln_sss                  Logical switch for SSS observations 
    1093                            !     ln_seaice              Logical switch for Sea Ice observations 
     1094   ln_seaice  = .false.    ! Logical switch for Sea Ice observations 
    10941095                           !     ln_vel3d                Logical switch for velocity observations 
    10951096                           !     ln_velavcur             Logical switch for velocity daily av. cur. 
     
    11121113                           !     sstfiles                GHRSST input observation file name 
    11131114   !                       ! sstfbfiles: Feedback SST input observation file name 
    1114    sstfbfiles = 'sst_01.nc' 'sst_02.nc' 'sst_03.nc' 'sst_04.nc' 'sst_05.nc' 
    1115                            !     seaicefiles             Sea Ice input observation file name 
     1115   sstfbfiles = 'sst_01.nc' 
     1116                           !     seaicefiles             Sea Ice input observation file names 
     1117   seaicefiles = 'seaice_01.nc'   
    11161118                           !     velavcurfiles           Vel. cur. daily av. input file name 
    11171119                           !     velhvcurfiles           Vel. cur. high freq. input file name 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OFF_SRC/domain.F90

    r4624 r4811  
    117117      INTEGER  ::   ios                 ! Local integer output status for namelist read 
    118118      NAMELIST/namrun/ nn_no   , cn_exp    , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl,   & 
    119          &             nn_it000, nn_itend  , nn_date0    , nn_leapy     , nn_istate , nn_stock ,   & 
    120          &             nn_write, ln_dimgnnn, ln_mskland  , ln_clobber   , nn_chunksz, nn_euler 
     119         &             nn_it000, nn_itend  , nn_date0    , nn_time0     , nn_leapy  , nn_istate ,  & 
     120         &             nn_stock, nn_write, ln_dimgnnn  , ln_mskland   , ln_clobber, nn_chunksz,  & 
     121         &             nn_euler 
    121122      NAMELIST/namdom/ nn_bathy , rn_bathy, rn_e3zps_min, rn_e3zps_rat, nn_msh    , rn_hmin,   & 
    122123         &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,            & 
     
    153154         WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend 
    154155         WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0 
     156         WRITE(numout,*) '      initial time of day in hours    nn_time0   = ', nn_time0 
    155157         WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy 
    156158         WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r4772 r4811  
    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 
    1314   !!---------------------------------------------------------------------- 
    1415 
     
    1718   !!---------------------------------------------------------------------- 
    1819   !!   asm_inc_init   : Initialize the increment arrays and IAU weights 
    19    !!   calc_date      : Compute the calendar date YYYYMMDDHH on a given step 
    2020   !!   tra_asm_inc    : Apply the tracer (T and S) increments 
    2121   !!   dyn_asm_inc    : Apply the dynamic (u and v) increments 
     
    4040#endif 
    4141   USE sbc_oce          ! Surface boundary condition variables. 
     42   USE diaobs, ONLY: calc_date     ! Compute the calendar date on a given step 
    4243 
    4344   IMPLICIT NONE 
     
    4546    
    4647   PUBLIC   asm_inc_init   !: Initialize the increment arrays and IAU weights 
    47    PUBLIC   calc_date      !: Compute the calendar date YYYYMMDDHH on a given step 
    4848   PUBLIC   tra_asm_inc    !: Apply the tracer (T and S) increments 
    4949   PUBLIC   dyn_asm_inc    !: Apply the dynamic (u and v) increments 
     
    115115      INTEGER :: iiauper         ! Number of time steps in the IAU period 
    116116      INTEGER :: icycper         ! Number of time steps in the cycle 
    117       INTEGER :: iitend_date     ! Date YYYYMMDDHH of final time step 
    118       INTEGER :: iitbkg_date     ! Date YYYYMMDDHH of background time step for Jb term 
    119       INTEGER :: iitdin_date     ! Date YYYYMMDDHH of background time step for DI 
    120       INTEGER :: iitiaustr_date  ! Date YYYYMMDDHH of IAU interval start time step 
    121       INTEGER :: iitiaufin_date  ! Date YYYYMMDDHH of IAU interval final time step 
    122117      INTEGER :: ios             ! Local integer output status for namelist read 
     118 
     119      REAL(KIND=dp) :: ditend_date     ! Date YYYYMMDD.HHMMSS of final time step 
     120      REAL(KIND=dp) :: ditbkg_date     ! Date YYYYMMDD.HHMMSS of background time step for Jb term 
     121      REAL(KIND=dp) :: ditdin_date     ! Date YYYYMMDD.HHMMSS of background time step for DI 
     122      REAL(KIND=dp) :: ditiaustr_date  ! Date YYYYMMDD.HHMMSS of IAU interval start time step 
     123      REAL(KIND=dp) :: ditiaufin_date  ! Date YYYYMMDD.HHMMSS of IAU interval final time step 
    123124 
    124125      REAL(wp) :: znorm        ! Normalization factor for IAU weights 
     
    187188 
    188189      ! Date of final time step 
    189       CALL calc_date( nit000, nitend, ndate0, iitend_date ) 
     190      CALL calc_date( nitend, ditend_date ) 
    190191 
    191192      ! Background time for Jb referenced to ndate0 
    192       CALL calc_date( nit000, nitbkg_r, ndate0, iitbkg_date ) 
     193      CALL calc_date( nitbkg_r, ditbkg_date ) 
    193194 
    194195      ! Background time for DI referenced to ndate0 
    195       CALL calc_date( nit000, nitdin_r, ndate0, iitdin_date ) 
     196      CALL calc_date( nitdin_r, ditdin_date ) 
    196197 
    197198      ! IAU start time referenced to ndate0 
    198       CALL calc_date( nit000, nitiaustr_r, ndate0, iitiaustr_date ) 
     199      CALL calc_date( nitiaustr_r, ditiaustr_date ) 
    199200 
    200201      ! IAU end time referenced to ndate0 
    201       CALL calc_date( nit000, nitiaufin_r, ndate0, iitiaufin_date ) 
     202      CALL calc_date( nitiaufin_r, ditiaufin_date ) 
    202203 
    203204      IF(lwp) THEN 
     
    215216         WRITE(numout,*) '       ndastp         = ', ndastp 
    216217         WRITE(numout,*) '       ndate0         = ', ndate0 
    217          WRITE(numout,*) '       iitend_date    = ', iitend_date 
    218          WRITE(numout,*) '       iitbkg_date    = ', iitbkg_date 
    219          WRITE(numout,*) '       iitdin_date    = ', iitdin_date 
    220          WRITE(numout,*) '       iitiaustr_date = ', iitiaustr_date 
    221          WRITE(numout,*) '       iitiaufin_date = ', iitiaufin_date 
     218         WRITE(numout,*) '       nn_time0       = ', nn_time0 
     219         WRITE(numout,*) '       ditend_date    = ', ditend_date 
     220         WRITE(numout,*) '       ditbkg_date    = ', ditbkg_date 
     221         WRITE(numout,*) '       ditdin_date    = ', ditdin_date 
     222         WRITE(numout,*) '       ditiaustr_date = ', ditiaustr_date 
     223         WRITE(numout,*) '       ditiaufin_date = ', ditiaufin_date 
    222224      ENDIF 
    223225 
     
    236238         &                ' but ln_asmdin and ln_asmiau are both set to .false. :', & 
    237239         &                ' Inconsistent options') 
    238  
    239       IF ( ( ln_bkgwri ).AND.( ( ln_asmdin ).OR.( ln_asmiau ) ) )  & 
    240          & CALL ctl_stop( ' ln_bkgwri and either ln_asmdin or ln_asmiau are set to .true.:', & 
    241          &                ' The background state must be written before applying the increments') 
    242240 
    243241      IF ( ( niaufn /= 0 ).AND.( niaufn /= 1 ) ) & 
     
    381379            WRITE(numout,*)  
    382380            WRITE(numout,*) 'asm_inc_init : Assimilation increments valid ', & 
    383                &            ' between dates ', NINT( z_inc_dateb ),' and ',  & 
    384                &            NINT( z_inc_datef ) 
     381               &            ' between dates ', z_inc_dateb,' and ',  & 
     382               &            z_inc_datef 
    385383            WRITE(numout,*) '~~~~~~~~~~~~' 
    386384         ENDIF 
    387385 
    388          IF (     ( NINT( z_inc_dateb ) < ndastp      ) & 
    389             & .OR.( NINT( z_inc_datef ) > iitend_date ) ) & 
     386         IF (     ( z_inc_dateb < ndastp + nn_time0*0.01_wp ) & 
     387            & .OR.( z_inc_datef > ditend_date ) ) & 
    390388            & CALL ctl_warn( ' Validity time of assimilation increments is ', & 
    391389            &                ' outside the assimilation interval' ) 
    392390 
    393          IF ( ( ln_asmdin ).AND.( NINT( zdate_inc ) /= iitdin_date ) ) & 
     391         IF ( ( ln_asmdin ).AND.( zdate_inc /= ditdin_date ) ) & 
    394392            & CALL ctl_warn( ' Validity time of assimilation increments does ', & 
    395393            &                ' not agree with Direct Initialization time' ) 
     
    518516            WRITE(numout,*)  
    519517            WRITE(numout,*) 'asm_inc_init : Assimilation background state valid at : ', & 
    520                &  NINT( zdate_bkg ) 
     518               &  zdate_bkg 
    521519            WRITE(numout,*) '~~~~~~~~~~~~' 
    522520         ENDIF 
    523521 
    524          IF ( NINT( zdate_bkg ) /= iitdin_date ) & 
     522         IF ( zdate_bkg /= ditdin_date ) & 
    525523            & CALL ctl_warn( ' Validity time of assimilation background state does', & 
    526524            &                ' not agree with Direct Initialization time' ) 
     
    550548      ! 
    551549   END SUBROUTINE asm_inc_init 
    552  
    553  
    554    SUBROUTINE calc_date( kit000, kt, kdate0, kdate ) 
    555       !!---------------------------------------------------------------------- 
    556       !!                    ***  ROUTINE calc_date  *** 
    557       !!           
    558       !! ** Purpose : Compute the calendar date YYYYMMDDHH at a given time step. 
    559       !! 
    560       !! ** Method  : Compute the calendar date YYYYMMDDHH at a given time step. 
    561       !! 
    562       !! ** Action  :  
    563       !!---------------------------------------------------------------------- 
    564       INTEGER, INTENT(IN) :: kit000  ! Initial time step 
    565       INTEGER, INTENT(IN) :: kt      ! Current time step referenced to kit000 
    566       INTEGER, INTENT(IN) :: kdate0  ! Initial date 
    567       INTEGER, INTENT(OUT) :: kdate  ! Current date reference to kdate0 
    568       ! 
    569       INTEGER :: iyea0    ! Initial year 
    570       INTEGER :: imon0    ! Initial month 
    571       INTEGER :: iday0    ! Initial day 
    572       INTEGER :: ihou0    ! Initial hour 
    573       INTEGER :: iyea     ! Current year 
    574       INTEGER :: imon     ! Current month 
    575       INTEGER :: iday     ! Current day 
    576       INTEGER :: ihou     ! Current hour 
    577       INTEGER :: idaystp  ! Number of days between initial and current date 
    578       INTEGER :: ihoustp  ! Number of hours 
    579       INTEGER :: idaycnt  ! Day counter 
    580  
    581       INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
    582  
    583       !----------------------------------------------------------------------- 
    584       ! Compute the calendar date YYYYMMDDHH 
    585       !----------------------------------------------------------------------- 
    586  
    587       ! Initial date 
    588       iyea0 =   kdate0 / 10000 
    589       imon0 = ( kdate0 - ( iyea0 * 10000 ) ) / 100 
    590       iday0 =   kdate0 - ( iyea0 * 10000 ) - ( imon0 * 100 ) 
    591       ihou0 = nn_time0  
    592  
    593       ! Check that kt >= kit000 - 1 
    594       IF ( kt < kit000 - 1 ) CALL ctl_stop( ' kt must be >= kit000 - 1') 
    595  
    596       ! Compute the number of days from the initial date 
    597       idaystp = INT( REAL( kt - kit000 ) * rdt / 86400. ) 
    598       ihoustp = INT( REAL( kt - kit000 ) * rdt / 3600. ) - ( idaystp * 24 ) 
    599  
    600       iday    = iday0 
    601       imon    = imon0 
    602       iyea    = iyea0 
    603       ihou    = ihou0 
    604       idaycnt = 0 
    605  
    606       ! Increment hours 
    607       ihou = ihou + ihoustp 
    608       IF ( ihou >= 24 ) THEN 
    609          ihou = ihou - 24 
    610          iday = iday + 1 
    611       ENDIF 
    612  
    613       CALL calc_month_len( iyea, imonth_len ) 
    614  
    615       DO WHILE ( idaycnt < idaystp ) 
    616          iday = iday + 1 
    617          IF ( iday > imonth_len(imon) )  THEN 
    618             iday = iday - imonth_len(imon) 
    619             imon = imon + 1 
    620          ENDIF 
    621          IF ( imon > 12 ) THEN 
    622             imon = 1 
    623             iyea = iyea + 1 
    624             CALL calc_month_len( iyea, imonth_len )  ! update month lengths 
    625          ENDIF                  
    626          idaycnt = idaycnt + 1 
    627       END DO 
    628       ! 
    629       kdate = iyea * 1000000 + imon * 10000 + iday * 100 + ihou 
    630       ! 
    631    END SUBROUTINE 
    632  
    633  
    634    SUBROUTINE calc_month_len( iyear, imonth_len ) 
    635       !!---------------------------------------------------------------------- 
    636       !!                    ***  ROUTINE calc_month_len  *** 
    637       !!           
    638       !! ** Purpose : Compute the number of days in a months given a year. 
    639       !! 
    640       !! ** Method  :  
    641       !!---------------------------------------------------------------------- 
    642       INTEGER, DIMENSION(12) ::   imonth_len    !: length in days of the months of the current year 
    643       INTEGER :: iyear         !: year 
    644       !!---------------------------------------------------------------------- 
    645       ! 
    646       ! length of the month of the current year (from nleapy, read in namelist) 
    647       IF ( nleapy < 2 ) THEN  
    648          imonth_len(:) = (/ 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31 /) 
    649          IF ( nleapy == 1 ) THEN   ! we are using calendar with leap years 
    650             IF ( MOD(iyear, 4) == 0 .AND. ( MOD(iyear, 400) == 0 .OR. MOD(iyear, 100) /= 0 ) ) THEN 
    651                imonth_len(2) = 29 
    652             ENDIF 
    653          ENDIF 
    654       ELSE 
    655          imonth_len(:) = nleapy   ! all months with nleapy days per year 
    656       ENDIF 
    657       ! 
    658    END SUBROUTINE 
    659  
    660550 
    661551   SUBROUTINE tra_asm_inc( kt ) 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r4772 r4811  
    8383 
    8484      IF( .NOT. lk_offline ) CALL day_rst( nit000, 'READ' ) 
    85  
    86       ! If we are starting at 00Z then need to wind back to previous day for calendar initialisation  
    87       IF( nn_time0 .eq. 0 ) ndastp = ndastp - 1  
    8885 
    8986      ! set the calandar from ndastp (read in restart file and namelist) 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r4772 r4811  
    138138         &             nn_it000, nn_itend, nn_date0    , nn_time0     , nn_leapy  , nn_istate ,  & 
    139139         &             nn_stock, nn_write, ln_dimgnnn  , ln_mskland   , ln_clobber, nn_chunksz,  & 
    140          &             nn_euler              
     140         &             nn_euler 
    141141      NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,   & 
    142142         &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,                  & 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r4772 r4811  
    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 
     
    5051      &   dia_obs,      &  ! Compute model equivalent to observations 
    5152      &   dia_obs_wri,  &  ! Write model equivalent to observations 
    52       &   dia_obs_dealloc  ! Deallocate dia_obs data 
     53      &   dia_obs_dealloc, &  ! Deallocate dia_obs data 
     54      &   calc_date           ! Compute the date of a timestep 
    5355 
    5456   !! * Shared Module variables 
     
    208210      !----------------------------------------------------------------------- 
    209211 
     212      !Initalise all values in namelist arrays 
     213      enactfiles(:) = '' 
     214      coriofiles(:) = '' 
     215      profbfiles(:) = '' 
     216      slafilesact(:) = '' 
     217      slafilespas(:) = '' 
     218      slafbfiles(:) = '' 
     219      sstfiles(:)   = '' 
     220      sstfbfiles(:) = '' 
     221      seaicefiles(:) = '' 
    210222      velcurfiles(:) = '' 
    211223      veladcpfiles(:) = '' 
     224      velavcurfiles(:) = '' 
     225      velhrcurfiles(:) = '' 
     226      velavadcpfiles(:) = '' 
     227      velhradcpfiles(:) = '' 
     228      velfbfiles(:) = '' 
     229      velcurfiles(:) = '' 
     230      veladcpfiles(:) = '' 
     231      endailyavtypes(:) = -1 
     232      endailyavtypes(1) = 820 
     233      ln_profb_ena(:) = .FALSE. 
     234      ln_profb_enatim(:) = .TRUE. 
     235      ln_velfb_av(:) = .FALSE. 
     236      ln_ignmis = .FALSE.       
     237 
    212238      CALL ini_date( dobsini ) 
    213239      CALL fin_date( dobsend ) 
  • branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OPA_SRC/OBS/jul2greg.h90

    r2287 r4811  
    1616      !!      ! 06-05  (A. Vidard) Reformatted and refdate       
    1717      !!      ! 06-10  (A. Weaver) Cleanup 
     18      !!      ! 2014-09 (D. Lea) Change to use FLOOR to deal with negative prelday 
    1819      !!----------------------------------------------------------------------- 
    1920 
     
    8283 
    8384      zday = prelday 
    84       ksec = NINT( 86400. * MOD( zday, 1. ) ) 
     85      ksec = FLOOR( 86400. * MOD( zday, 1. ) ) 
    8586 
    8687      IF ( ksec < 0. ) ksec = 86400. + ksec 
Note: See TracChangeset for help on using the changeset viewer.