MODULE daymod !!====================================================================== !! *** MODULE daymod *** !! Ocean : calendar !!===================================================================== !! History : ! 94-09 (M. Pontaud M. Imbard) Original code !! ! 97-03 (O. Marti) !! ! 97-05 (G. Madec) !! ! 97-08 (M. Imbard) !! 9.0 ! 03-09 (G. Madec) F90 + nyear, nmonth, nday !! ! 04-01 (A.M. Treguier) new calculation based on adatrj !! ! 06-08 (G. Madec) surface module major update !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! day : calendar !! !! ------------------------------- !! ----------- WARNING ----------- !! !! we suppose that the time step is deviding the number of second of in a day !! ---> MOD( rday, rdttra(1) ) == 0 !! !! ----------- WARNING ----------- !! ------------------------------- !! !!---------------------------------------------------------------------- USE dom_oce ! ocean space and time domain USE phycst ! physical constants USE in_out_manager ! I/O manager USE iom ! USE prtctl ! Print control USE restart ! IMPLICIT NONE PRIVATE PUBLIC day ! called by step.F90 PUBLIC day_init ! called by istate.F90 INTEGER , PUBLIC :: nyear !: current year INTEGER , PUBLIC :: nmonth !: current month INTEGER , PUBLIC :: nday !: current day of the month INTEGER , PUBLIC :: ndastp !: time step date in yyyymmdd format INTEGER , PUBLIC :: nday_year !: current day counted from jan 1st of the current year REAL(wp), PUBLIC :: rsec_year !: current time step counted in second since 00h jan 1st of the current year REAL(wp), PUBLIC :: rsec_month !: current time step counted in second since 00h 1st day of the current month REAL(wp), PUBLIC :: rsec_day !: current time step counted in second since 00h of the current day REAL(wp), PUBLIC :: adatrj !: number of elapsed days since the begining of the run ! !: it is the accumulated duration of previous runs ! !: that may have been run with different time steps. INTEGER , PUBLIC, DIMENSION(0:1) :: nyear_len !: length in days of the previous/current year INTEGER , PUBLIC, DIMENSION(0:13) :: nmonth_len !: length in days of the months of the current year REAL(wp), PUBLIC, DIMENSION(0:13) :: rmonth_half !: second since the beginning of the year and the halft of the months REAL(wp), PUBLIC, DIMENSION(0:13) :: rmonth_end !: second since the beginning of the year and the end of the months REAL(wp), PUBLIC :: sec1jan000 !: second since Jan. 1st 00h of nit000 year ! this two variables are wrong DO NOT USE THEM !!! INTEGER, PUBLIC, DIMENSION(12) :: nbiss = (/ 31, 29, 31, 30, 31, 30, & !: number of days per month & 31, 31, 30, 31, 30, 31 /) !: (leap-year) INTEGER, PUBLIC, DIMENSION(12) :: nobis = (/ 31, 28, 31, 30, 31, 30, & !: number of days per month & 31, 31, 30, 31, 30, 31 /) !: (365 days a year) !!---------------------------------------------------------------------- !! OPA 9.0 , LOCEAN-IPSL (2006) !! $Id$ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE day_init !!---------------------------------------------------------------------- !! *** ROUTINE day_init *** !! !! ** Purpose : Initialization of the calendar values to their values 1 time step before nit000 !! because day will be called at the beginning of step !! !! ** Action : - nyear : current year !! - nmonth : current month of the year nyear !! - nday : current day of the month nmonth !! - nday_year : current day of the year nyear !! - rsec_year : current time step counted in second since 00h jan 1st of the current year !! - rsec_month : current time step counted in second since 00h 1st day of the current month !! - rsec_day : current time step counted in second since 00h of the current day !! - sec1jan000 : second since Jan. 1st 00h of nit000 year !! - nmonth_len, nyear_len, rmonth_half, rmonth_end through day_mth !!---------------------------------------------------------------------- ! all calendar staff is based on the fact that MOD( rday, rdttra(1) ) == 0 IF( MOD( rday, rdttra(1) ) /= 0 ) CALL ctl_stop( 'the time step must devide the number of second of in a day' ) CALL day_rst( nit000, 'READ' ) ! set the calandar from ndastp (read in restart file and namelist) nyear = ndastp / 10000 nmonth = ( ndastp - (nyear * 10000) ) / 100 nday = ndastp - (nyear * 10000) - ( nmonth * 100 ) sec1jan000 = 0.e0 CALL day_mth IF ( nday == 0 ) THEN ! for ex if ndastp = ndate0 - 1 nmonth = nmonth - 1 nday = nmonth_len(nmonth) ENDIF IF ( nmonth == 0 ) THEN ! go at the end of previous year nmonth = 12 nyear = nyear - 1 sec1jan000 = sec1jan000 - rday * REAL( nyear_len(0), wp ) IF( nleapy == 1 ) CALL day_mth ENDIF ! day since january 1st nday_year = nday + SUM( nmonth_len(1:nmonth - 1) ) ! number of seconds since the beginning of current year/month at the middle of the time-step rsec_year = REAL( nday_year, wp ) * rday - 0.5 * rdttra(1) ! 1 time step before the middle of the first time step rsec_month = REAL( nday , wp ) * rday - 0.5 * rdttra(1) ! because day will be called at the beginning of step rsec_day = rday - 0.5 * rdttra(1) ! control print IF(lwp) WRITE(numout,*)' ==============>> 1/2 time step before the start of the run DATE Y/M/D = ', & & nyear, '/', nmonth, '/', nday, ' rsec_day:', rsec_day END SUBROUTINE day_init SUBROUTINE day_mth !!---------------------------------------------------------------------- !! *** ROUTINE day_init *** !! !! ** Purpose : calendar values related to the months !! !! ** Action : - nmonth_len : length in days of the months of the current year !! - nyear_len : length in days of the previous/current year !! - rmonth_half : second since the beginning of the year and the halft of the months !! - rmonth_end : second since the beginning of the year and the end of the months !!---------------------------------------------------------------------- INTEGER :: jm ! dummy loop indice !!---------------------------------------------------------------------- ! length of the month of the current year (from nleapy, read in namelist) IF ( nleapy < 2 ) THEN nmonth_len(:) = (/ 31, 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31, 31 /) nyear_len(:) = 365 IF ( nleapy == 1 ) THEN ! we are using calandar with leap years IF ( MOD(nyear-1, 4) == 0 .AND. ( MOD(nyear-1, 400) == 0 .OR. MOD(nyear-1, 100) /= 0 ) ) THEN nyear_len(0) = 366 ENDIF IF ( MOD(nyear, 4) == 0 .AND. ( MOD(nyear, 400) == 0 .OR. MOD(nyear, 100) /= 0 ) ) THEN nmonth_len(2) = 29 nyear_len(1) = 366 ENDIF ENDIF ELSE nmonth_len(:) = nleapy ! all months with nleapy days per year nyear_len(:) = 12 * nleapy ENDIF ! half month in second since the begining of the year: ! time since Jan 1st 0 1 2 ... 11 12 13 ! ---------*--|--*--|--*--| ... |--*--|--*--|--*--|-------------------------------------- ! <---> <---> <---> ... <---> <---> <---> ! month number 0 1 2 ... 11 12 13 ! ! rmonth_half(jm) = rday * REAL( 0.5 * nmonth_len(jm) + SUM(nmonth_len(1:jm-1)) ) rmonth_half(0) = - 0.5 * rday * REAL( nmonth_len(0), wp ) DO jm = 1, 13 rmonth_half(jm) = rmonth_half(jm-1) + 0.5 * rday * REAL( nmonth_len(jm-1) + nmonth_len(jm), wp ) END DO rmonth_half(:) = rmonth_half(:) + sec1jan000 rmonth_end(0) = 0. DO jm = 1, 13 rmonth_end(jm) = rmonth_end(jm-1) + rday * REAL( nmonth_len(jm), wp ) END DO END SUBROUTINE SUBROUTINE day( kt ) !!---------------------------------------------------------------------- !! *** ROUTINE day *** !! !! ** Purpose : Compute the date with a day iteration IF necessary. !! !! ** Method : - ??? !! !! ** Action : - nyear : current year !! - nmonth : current month of the year nyear !! - nday : current day of the month nmonth !! - nday_year : current day of the year nyear !! - ndastp : = nyear*10000 + nmonth*100 + nday !! - adatrj : date in days since the beginning of the run !! - rsec_year : current time of the year (in second since 00h, jan 1st) !!---------------------------------------------------------------------- INTEGER, INTENT(in) :: kt ! ocean time-step indices ! CHARACTER (len=25) :: charout !!---------------------------------------------------------------------- ! ! New time-step rsec_year = rsec_year + rdttra(1) rsec_month = rsec_month + rdttra(1) rsec_day = rsec_day + rdttra(1) adatrj = adatrj + rdttra(1) / rday IF( rsec_day > rday ) THEN ! NEW day ! nday = nday + 1 nday_year = nday_year + 1 rsec_day = 0.5 * rdttra(1) ! IF( nday == nmonth_len(nmonth) + 1 ) THEN ! NEW month nday = 1 nmonth = nmonth + 1 rsec_month = 0.5 * rdttra(1) IF( nmonth == 13 ) THEN ! NEW year nyear = nyear + 1 nmonth = 1 nday_year = 1 rsec_year = 0.5 * rdttra(1) sec1jan000 = sec1jan000 + rday * REAL( nyear_len(1), wp ) IF( nleapy == 1 ) CALL day_mth ENDIF ENDIF ! ndastp = nyear * 10000 + nmonth * 100 + nday ! NEW date ! IF(lwp) WRITE(numout,'(a,i8,a,i4.4,a,i2.2,a,i2.2,a,i3.3)') '======>> time-step =', kt, & & ' New day, DATE Y/M/D = ', nyear, '/', nmonth, '/', nday, ' nday_year = ', nday_year IF(lwp) WRITE(numout,'(a,F9.0,a,F9.0,a,F9.0)') ' rsec_year = ', rsec_year, & & ' rsec_month = ', rsec_month, ' rsec_day = ', rsec_day ENDIF IF(ln_ctl) THEN WRITE(charout,FMT="('kt =', I4,' d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear CALL prt_ctl_info(charout) ENDIF IF( lrst_oce ) CALL day_rst( kt, 'WRITE' ) ! END SUBROUTINE day SUBROUTINE day_rst( kt, cdrw ) !!--------------------------------------------------------------------- !! *** ROUTINE ts_rst *** !! !! ** Purpose : Read or write calendar in restart file: !! !! WRITE(READ) mode: !! kt : number of time step since the begining of the experiment at the !! end of the current(previous) run !! adatrj(0) : number of elapsed days since the begining of the experiment at the !! end of the current(previous) run (REAL -> keep fractions of day) !! ndastp : date at the end of the current(previous) run (coded as yyyymmdd integer) !! !! According to namelist parameter nrstdt, !! nrstdt = 0 no control on the date (nit000 is arbitrary). !! nrstdt = 1 we verify that nit000 is equal to the last !! time step of previous run + 1. !! In both those options, the exact duration of the experiment !! since the beginning (cumulated duration of all previous restart runs) !! is not stored in the restart and is assumed to be (nit000-1)*rdt. !! This is valid is the time step has remained constant. !! !! nrstdt = 2 the duration of the experiment in days (adatrj) !! has been stored in the restart file. !!---------------------------------------------------------------------- INTEGER , INTENT(in) :: kt ! ocean time-step CHARACTER(len=*), INTENT(in) :: cdrw ! "READ"/"WRITE" flag ! REAL(wp) :: zkt, zndastp !!---------------------------------------------------------------------- IF( TRIM(cdrw) == 'READ' ) THEN IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN ! Get Calendar informations CALL iom_get( numror, 'kt', zkt ) ! last time-step of previous run IF(lwp) THEN WRITE(numout,*) ' *** Info read in restart : ' WRITE(numout,*) ' previous time-step : ', NINT( zkt ) WRITE(numout,*) ' *** restart option' SELECT CASE ( nrstdt ) CASE ( 0 ) ; WRITE(numout,*) ' nrstdt = 0 : no control of nit000' CASE ( 1 ) ; WRITE(numout,*) ' nrstdt = 1 : no control the date at nit000 (use ndate0 read in the namelist)' CASE ( 2 ) ; WRITE(numout,*) ' nrstdt = 2 : calendar parameters read in restart' END SELECT WRITE(numout,*) ENDIF ! Control of date IF( nit000 - NINT( zkt ) /= 1 .AND. nrstdt /= 0 ) & & CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart', & & ' verify the restart file or rerun with nrstdt = 0 (namelist)' ) ! define ndastp and adatrj IF ( nrstdt == 2 ) THEN CALL iom_get( numror, 'ndastp', zndastp ) ndastp = NINT( zndastp ) CALL iom_get( numror, 'adatrj', adatrj ) ELSE ndastp = ndate0 - 1 ! ndate0 read in the namelist in dom_nam adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday ! note this is wrong if time step has changed during run ENDIF ELSE ndastp = ndate0 - 1 ! ndate0 read in the namelist in dom_nam adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday ENDIF ! IF(lwp) THEN WRITE(numout,*) ' *** Info used values : ' WRITE(numout,*) ' date ndastp : ', ndastp WRITE(numout,*) ' number of elapsed days since the begining of run : ', adatrj WRITE(numout,*) ENDIF ! ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN ! IF( kt == nitrst ) THEN IF(lwp) WRITE(numout,*) IF(lwp) WRITE(numout,*) 'rst_write : write oce restart file kt =', kt IF(lwp) WRITE(numout,*) '~~~~~~~' ENDIF ! calendar control CALL iom_rstput( kt, nitrst, numrow, 'kt' , REAL( kt , wp) ) ! time-step CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp) ) ! date CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj ) ! number of elapsed days since ! ! the begining of the run [s] ENDIF ! END SUBROUTINE day_rst !!====================================================================== END MODULE daymod