daymod.F90 18 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370
  1. MODULE daymod
  2. !!======================================================================
  3. !! *** MODULE daymod ***
  4. !! Ocean : calendar
  5. !!=====================================================================
  6. !! History : OPA ! 1994-09 (M. Pontaud M. Imbard) Original code
  7. !! ! 1997-03 (O. Marti)
  8. !! ! 1997-05 (G. Madec)
  9. !! ! 1997-08 (M. Imbard)
  10. !! NEMO 1.0 ! 2003-09 (G. Madec) F90 + nyear, nmonth, nday
  11. !! ! 2004-01 (A.M. Treguier) new calculation based on adatrj
  12. !! ! 2006-08 (G. Madec) surface module major update
  13. !!----------------------------------------------------------------------
  14. !!----------------------------------------------------------------------
  15. !! day : calendar
  16. !!
  17. !! -------------------------------
  18. !! ----------- WARNING -----------
  19. !!
  20. !! we suppose that the time step is deviding the number of second of in a day
  21. !! ---> MOD( rday, rdttra(1) ) == 0
  22. !!
  23. !! ----------- WARNING -----------
  24. !! -------------------------------
  25. !!
  26. !!----------------------------------------------------------------------
  27. USE dom_oce ! ocean space and time domain
  28. USE phycst ! physical constants
  29. USE in_out_manager ! I/O manager
  30. USE iom !
  31. USE ioipsl, ONLY : ymds2ju ! for calendar
  32. USE prtctl ! Print control
  33. USE trc_oce, ONLY : lk_offline ! offline flag
  34. USE timing ! Timing
  35. USE restart ! restart
  36. IMPLICIT NONE
  37. PRIVATE
  38. PUBLIC day ! called by step.F90
  39. PUBLIC day_init ! called by istate.F90
  40. PUBLIC day_mth ! Needed by TAM
  41. INTEGER, PUBLIC :: nsecd, nsecd05, ndt, ndt05 ! (PUBLIC for TAM)
  42. !!----------------------------------------------------------------------
  43. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  44. !! $Id: daymod.F90 5424 2018-04-27 07:03:10Z ufla $
  45. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  46. !!----------------------------------------------------------------------
  47. CONTAINS
  48. SUBROUTINE day_init
  49. !!----------------------------------------------------------------------
  50. !! *** ROUTINE day_init ***
  51. !!
  52. !! ** Purpose : Initialization of the calendar values to their values 1 time step before nit000
  53. !! because day will be called at the beginning of step
  54. !!
  55. !! ** Action : - nyear : current year
  56. !! - nmonth : current month of the year nyear
  57. !! - nday : current day of the month nmonth
  58. !! - nday_year : current day of the year nyear
  59. !! - nsec_year : current time step counted in second since 00h jan 1st of the current year
  60. !! - nsec_month : current time step counted in second since 00h 1st day of the current month
  61. !! - nsec_day : current time step counted in second since 00h of the current day
  62. !! - nsec1jan000 : second since Jan. 1st 00h of nit000 year and Jan. 1st 00h of the current year
  63. !! - nmonth_len, nyear_len, nmonth_half, nmonth_end through day_mth
  64. !!----------------------------------------------------------------------
  65. INTEGER :: inbday, idweek
  66. REAL(wp) :: zjul
  67. !!----------------------------------------------------------------------
  68. !
  69. ! max number of seconds between each restart
  70. IF( REAL( nitend - nit000 + 1 ) * rdt > REAL( HUGE( nsec1jan000 ) ) ) THEN
  71. CALL ctl_stop( 'The number of seconds between each restart exceeds the integer 4 max value: 2^31-1. ', &
  72. & 'You must do a restart at higher frequency (or remove this stop and recompile the code in I8)' )
  73. ENDIF
  74. ! all calendar staff is based on the fact that MOD( rday, rdttra(1) ) == 0
  75. IF( MOD( rday , rdttra(1) ) /= 0. ) CALL ctl_stop( 'the time step must devide the number of second of in a day' )
  76. IF( MOD( rday , 2. ) /= 0. ) CALL ctl_stop( 'the number of second of in a day must be an even number' )
  77. IF( MOD( rdttra(1), 2. ) /= 0. ) CALL ctl_stop( 'the time step (in second) must be an even number' )
  78. nsecd = NINT(rday )
  79. nsecd05 = NINT(0.5 * rday )
  80. ndt = NINT( rdttra(1))
  81. ndt05 = NINT(0.5 * rdttra(1))
  82. IF( .NOT. lk_offline ) CALL day_rst( nit000, 'READ' )
  83. ! set the calandar from ndastp (read in restart file and namelist)
  84. nyear = ndastp / 10000
  85. nmonth = ( ndastp - (nyear * 10000) ) / 100
  86. nday = ndastp - (nyear * 10000) - ( nmonth * 100 )
  87. CALL ymds2ju( nyear, nmonth, nday, 0.0, fjulday ) ! we assume that we start run at 00:00
  88. IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < 0.1 / rday ) fjulday = REAL(NINT(fjulday),wp) ! avoid truncation error
  89. fjulday = fjulday + 1. ! move back to the day at nit000 (and not at nit000 - 1)
  90. nsec1jan000 = 0
  91. CALL day_mth
  92. IF ( nday == 0 ) THEN ! for ex if ndastp = ndate0 - 1
  93. nmonth = nmonth - 1
  94. nday = nmonth_len(nmonth)
  95. ENDIF
  96. IF ( nmonth == 0 ) THEN ! go at the end of previous year
  97. nmonth = 12
  98. nyear = nyear - 1
  99. nsec1jan000 = nsec1jan000 - nsecd * nyear_len(0)
  100. IF( nleapy == 1 ) CALL day_mth
  101. ENDIF
  102. ! day since january 1st
  103. nday_year = nday + SUM( nmonth_len(1:nmonth - 1) )
  104. !compute number of days between last monday and today
  105. CALL ymds2ju( 1900, 01, 01, 0.0, zjul ) ! compute julian day value of 01.01.1900 (our reference that was a Monday)
  106. inbday = NINT(fjulday - zjul) ! compute nb day between 01.01.1900 and current day
  107. idweek = MOD(inbday, 7) ! compute nb day between last monday and current day
  108. ! number of seconds since the beginning of current year/month/week/day at the middle of the time-step
  109. nsec_year = nday_year * nsecd - ndt05 ! 1 time step before the middle of the first time step
  110. nsec_month = nday * nsecd - ndt05 ! because day will be called at the beginning of step
  111. nsec_week = idweek * nsecd - ndt05
  112. nsec_day = nsecd - ndt05
  113. ! control print
  114. 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 = ', &
  115. & nyear, '/', nmonth, '/', nday, ' nsec_day:', nsec_day, ' nsec_week:', nsec_week
  116. ! Up to now, calendar parameters are related to the end of previous run (nit000-1)
  117. ! call day to set the calendar parameters at the begining of the current simulaton. needed by iom_init
  118. CALL day( nit000 )
  119. !
  120. END SUBROUTINE day_init
  121. SUBROUTINE day_mth
  122. !!----------------------------------------------------------------------
  123. !! *** ROUTINE day_init ***
  124. !!
  125. !! ** Purpose : calendar values related to the months
  126. !!
  127. !! ** Action : - nmonth_len : length in days of the months of the current year
  128. !! - nyear_len : length in days of the previous/current year
  129. !! - nmonth_half : second since the beginning of the year and the halft of the months
  130. !! - nmonth_end : second since the beginning of the year and the end of the months
  131. !!----------------------------------------------------------------------
  132. INTEGER :: jm ! dummy loop indice
  133. !!----------------------------------------------------------------------
  134. ! length of the month of the current year (from nleapy, read in namelist)
  135. IF ( nleapy < 2 ) THEN
  136. nmonth_len(:) = (/ 31, 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31, 31 /)
  137. nyear_len(:) = 365
  138. IF ( nleapy == 1 ) THEN ! we are using calandar with leap years
  139. IF ( MOD(nyear-1, 4) == 0 .AND. ( MOD(nyear-1, 400) == 0 .OR. MOD(nyear-1, 100) /= 0 ) ) THEN
  140. nyear_len(0) = 366
  141. ENDIF
  142. IF ( MOD(nyear , 4) == 0 .AND. ( MOD(nyear , 400) == 0 .OR. MOD(nyear , 100) /= 0 ) ) THEN
  143. nmonth_len(2) = 29
  144. nyear_len(1) = 366
  145. ENDIF
  146. IF ( MOD(nyear+1, 4) == 0 .AND. ( MOD(nyear+1, 400) == 0 .OR. MOD(nyear+1, 100) /= 0 ) ) THEN
  147. nyear_len(2) = 366
  148. ENDIF
  149. ENDIF
  150. ELSE
  151. nmonth_len(:) = nleapy ! all months with nleapy days per year
  152. nyear_len(:) = 12 * nleapy
  153. ENDIF
  154. ! half month in second since the begining of the year:
  155. ! time since Jan 1st 0 1 2 ... 11 12 13
  156. ! ---------*--|--*--|--*--| ... |--*--|--*--|--*--|--------------------------------------
  157. ! <---> <---> <---> ... <---> <---> <--->
  158. ! month number 0 1 2 ... 11 12 13
  159. !
  160. ! nmonth_half(jm) = rday * REAL( 0.5 * nmonth_len(jm) + SUM(nmonth_len(1:jm-1)) )
  161. nmonth_half(0) = - nsecd05 * nmonth_len(0)
  162. DO jm = 1, 13
  163. nmonth_half(jm) = nmonth_half(jm-1) + nsecd05 * ( nmonth_len(jm-1) + nmonth_len(jm) )
  164. END DO
  165. nmonth_end(0) = 0
  166. DO jm = 1, 13
  167. nmonth_end(jm) = nmonth_end(jm-1) + nsecd * nmonth_len(jm)
  168. END DO
  169. !
  170. END SUBROUTINE
  171. SUBROUTINE day( kt )
  172. !!----------------------------------------------------------------------
  173. !! *** ROUTINE day ***
  174. !!
  175. !! ** Purpose : Compute the date with a day iteration IF necessary.
  176. !!
  177. !! ** Method : - ???
  178. !!
  179. !! ** Action : - nyear : current year
  180. !! - nmonth : current month of the year nyear
  181. !! - nday : current day of the month nmonth
  182. !! - nday_year : current day of the year nyear
  183. !! - ndastp : = nyear*10000 + nmonth*100 + nday
  184. !! - adatrj : date in days since the beginning of the run
  185. !! - nsec_year : current time of the year (in second since 00h, jan 1st)
  186. !!----------------------------------------------------------------------
  187. INTEGER, INTENT(in) :: kt ! ocean time-step indices
  188. !
  189. CHARACTER (len=25) :: charout
  190. REAL(wp) :: zprec ! fraction of day corresponding to 0.1 second
  191. !!----------------------------------------------------------------------
  192. !
  193. IF( nn_timing == 1 ) CALL timing_start('day')
  194. !
  195. zprec = 0.1 / rday
  196. ! ! New time-step
  197. nsec_year = nsec_year + ndt
  198. nsec_month = nsec_month + ndt
  199. nsec_week = nsec_week + ndt
  200. nsec_day = nsec_day + ndt
  201. adatrj = adatrj + rdttra(1) / rday
  202. fjulday = fjulday + rdttra(1) / rday
  203. IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < zprec ) fjulday = REAL(NINT(fjulday),wp) ! avoid truncation error
  204. IF( ABS(adatrj - REAL(NINT(adatrj ),wp)) < zprec ) adatrj = REAL(NINT(adatrj ),wp) ! avoid truncation error
  205. IF( nsec_day > nsecd ) THEN ! New day
  206. !
  207. nday = nday + 1
  208. nday_year = nday_year + 1
  209. nsec_day = ndt05
  210. !
  211. IF( nday == nmonth_len(nmonth) + 1 ) THEN ! New month
  212. nday = 1
  213. nmonth = nmonth + 1
  214. nsec_month = ndt05
  215. IF( nmonth == 13 ) THEN ! New year
  216. nyear = nyear + 1
  217. nmonth = 1
  218. nday_year = 1
  219. nsec_year = ndt05
  220. nsec1jan000 = nsec1jan000 + nsecd * nyear_len(1)
  221. IF( nleapy == 1 ) CALL day_mth
  222. ENDIF
  223. ENDIF
  224. !
  225. ndastp = nyear * 10000 + nmonth * 100 + nday ! New date
  226. !
  227. !compute first day of the year in julian days
  228. CALL ymds2ju( nyear, 01, 01, 0.0, fjulstartyear )
  229. !
  230. IF(lwp) WRITE(numout,'(a,i8,a,i4.4,a,i2.2,a,i2.2,a,i3.3)') '======>> time-step =', kt, &
  231. & ' New day, DATE Y/M/D = ', nyear, '/', nmonth, '/', nday, ' nday_year = ', nday_year
  232. IF(lwp) WRITE(numout,'(a,i8,a,i7,a,i5)') ' nsec_year = ', nsec_year, &
  233. & ' nsec_month = ', nsec_month, ' nsec_day = ', nsec_day, ' nsec_week = ', nsec_week
  234. ENDIF
  235. IF( nsec_week > 7*nsecd ) nsec_week = ndt05 ! New week
  236. IF(ln_ctl) THEN
  237. WRITE(charout,FMT="('kt =', I4,' d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear
  238. CALL prt_ctl_info(charout)
  239. ENDIF
  240. IF( .NOT. lk_offline ) CALL rst_opn( kt ) ! Open the restart file if needed and control lrst_oce
  241. IF( lrst_oce ) CALL day_rst( kt, 'WRITE' ) ! write day restart information
  242. !
  243. IF( nn_timing == 1 ) CALL timing_stop('day')
  244. !
  245. END SUBROUTINE day
  246. SUBROUTINE day_rst( kt, cdrw )
  247. !!---------------------------------------------------------------------
  248. !! *** ROUTINE ts_rst ***
  249. !!
  250. !! ** Purpose : Read or write calendar in restart file:
  251. !!
  252. !! WRITE(READ) mode:
  253. !! kt : number of time step since the begining of the experiment at the
  254. !! end of the current(previous) run
  255. !! adatrj(0) : number of elapsed days since the begining of the experiment at the
  256. !! end of the current(previous) run (REAL -> keep fractions of day)
  257. !! ndastp : date at the end of the current(previous) run (coded as yyyymmdd integer)
  258. !!
  259. !! According to namelist parameter nrstdt,
  260. !! nrstdt = 0 no control on the date (nit000 is arbitrary).
  261. !! nrstdt = 1 we verify that nit000 is equal to the last
  262. !! time step of previous run + 1.
  263. !! In both those options, the exact duration of the experiment
  264. !! since the beginning (cumulated duration of all previous restart runs)
  265. !! is not stored in the restart and is assumed to be (nit000-1)*rdt.
  266. !! This is valid is the time step has remained constant.
  267. !!
  268. !! nrstdt = 2 the duration of the experiment in days (adatrj)
  269. !! has been stored in the restart file.
  270. !!----------------------------------------------------------------------
  271. INTEGER , INTENT(in) :: kt ! ocean time-step
  272. CHARACTER(len=*), INTENT(in) :: cdrw ! "READ"/"WRITE" flag
  273. !
  274. REAL(wp) :: zkt, zndastp
  275. !!----------------------------------------------------------------------
  276. IF( TRIM(cdrw) == 'READ' ) THEN
  277. IF( iom_varid( numror, 'kt', ldstop = .FALSE. ) > 0 ) THEN
  278. ! Get Calendar informations
  279. CALL iom_get( numror, 'kt', zkt ) ! last time-step of previous run
  280. IF(lwp) THEN
  281. WRITE(numout,*) ' *** Info read in restart : '
  282. WRITE(numout,*) ' previous time-step : ', NINT( zkt )
  283. WRITE(numout,*) ' *** restart option'
  284. SELECT CASE ( nrstdt )
  285. CASE ( 0 ) ; WRITE(numout,*) ' nrstdt = 0 : no control of nit000'
  286. CASE ( 1 ) ; WRITE(numout,*) ' nrstdt = 1 : no control the date at nit000 (use ndate0 read in the namelist)'
  287. CASE ( 2 ) ; WRITE(numout,*) ' nrstdt = 2 : calendar parameters read in restart'
  288. END SELECT
  289. WRITE(numout,*)
  290. ENDIF
  291. ! Control of date
  292. IF( nit000 - NINT( zkt ) /= 1 .AND. nrstdt /= 0 ) &
  293. & CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart', &
  294. & ' verify the restart file or rerun with nrstdt = 0 (namelist)' )
  295. ! define ndastp and adatrj
  296. IF ( nrstdt == 2 ) THEN
  297. ! read the parameters correspondting to nit000 - 1 (last time step of previous run)
  298. CALL iom_get( numror, 'ndastp', zndastp )
  299. ndastp = NINT( zndastp )
  300. CALL iom_get( numror, 'adatrj', adatrj )
  301. ELSE
  302. ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day)
  303. ndastp = ndate0 - 1 ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00
  304. adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday
  305. ! note this is wrong if time step has changed during run
  306. ENDIF
  307. ELSE
  308. ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day)
  309. ndastp = ndate0 - 1 ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00
  310. adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday
  311. ENDIF
  312. IF( ABS(adatrj - REAL(NINT(adatrj),wp)) < 0.1 / rday ) adatrj = REAL(NINT(adatrj),wp) ! avoid truncation error
  313. !
  314. IF(lwp) THEN
  315. WRITE(numout,*) ' *** Info used values : '
  316. WRITE(numout,*) ' date ndastp : ', ndastp
  317. WRITE(numout,*) ' number of elapsed days since the begining of run : ', adatrj
  318. WRITE(numout,*)
  319. ENDIF
  320. !
  321. ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
  322. !
  323. IF( kt == nitrst ) THEN
  324. IF(lwp) WRITE(numout,*)
  325. IF(lwp) WRITE(numout,*) 'rst_write : write oce restart file kt =', kt
  326. IF(lwp) WRITE(numout,*) '~~~~~~~'
  327. ENDIF
  328. ! calendar control
  329. CALL iom_rstput( kt, nitrst, numrow, 'kt' , REAL( kt , wp) ) ! time-step
  330. CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp) ) ! date
  331. CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj ) ! number of elapsed days since
  332. ! ! the begining of the run [s]
  333. ENDIF
  334. !
  335. END SUBROUTINE day_rst
  336. !!======================================================================
  337. END MODULE daymod