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.
daymod.F90 in branches/UKMO/dev_r7750_GO6_package_oasis_timers/NEMOGCM/NEMO/OPA_SRC/DOM – NEMO

source: branches/UKMO/dev_r7750_GO6_package_oasis_timers/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90 @ 9261

Last change on this file since 9261 was 9261, checked in by andmirek, 6 years ago

#1978 only 1 and 2 for nn_timing

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