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 tags/nemo_v3_2/nemo_v3_2/NEMO/OFF_SRC/DOM – NEMO

source: tags/nemo_v3_2/nemo_v3_2/NEMO/OFF_SRC/DOM/daymod.F90 @ 1878

Last change on this file since 1878 was 1878, checked in by flavoni, 14 years ago

initial test for nemogcm

File size: 11.1 KB
Line 
1MODULE 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   !!----------------------------------------------------------------------
16   !!   day        : calendar
17   !! 
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   !!           -------------------------------
26   !! 
27   !!----------------------------------------------------------------------
28   USE dom_oce         ! ocean space and time domain
29   USE phycst          ! physical constants
30   USE in_out_manager  ! I/O manager
31   USE ioipsl, ONLY :   ymds2ju   ! for calendar
32   USE prtctl          ! Print control
33
34   IMPLICIT NONE
35   PRIVATE
36
37   PUBLIC   day        ! called by step.F90
38   PUBLIC   day_init   ! called by istate.F90
39
40   INTEGER ::   nsecd, nsecd05, ndt, ndt05
41
42   !!----------------------------------------------------------------------
43   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
44   !! $Id: daymod.F90 1748 2009-11-23 10:51:20Z cetlod $
45   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
46   !!----------------------------------------------------------------------
47
48CONTAINS
49
50   SUBROUTINE day_init
51      !!----------------------------------------------------------------------
52      !!                   ***  ROUTINE day_init  ***
53      !!
54      !! ** Purpose :   Initialization of the calendar values to their values 1 time step before nit000
55      !!                because day will be called at the beginning of step
56      !!
57      !! ** Action  : - nyear        : current year
58      !!              - nmonth       : current month of the year nyear
59      !!              - nday         : current day of the month nmonth
60      !!              - nday_year    : current day of the year nyear
61      !!              - nsec_year    : current time step counted in second since 00h jan 1st of the current year
62      !!              - nsec_month   : current time step counted in second since 00h 1st day of the current month
63      !!              - nsec_day     : current time step counted in second since 00h of the current day
64      !!              - nsec1jan000  : second since Jan. 1st 00h of nit000 year and Jan. 1st 00h of the current year
65      !!              - nmonth_len, nyear_len, nmonth_half, nmonth_end through day_mth
66      !!----------------------------------------------------------------------
67
68      ! all calendar staff is based on the fact that MOD( rday, rdttra(1) ) == 0
69      IF( MOD( rday     , rdttra(1) ) /= 0. )   CALL ctl_stop( 'the time step must devide the number of second of in a day' )
70      IF( MOD( rday     , 2.        ) /= 0. )   CALL ctl_stop( 'the number of second of in a day must be an even number'    )
71      IF( MOD( rdttra(1), 2.        ) /= 0. )   CALL ctl_stop( 'the time step (in second) must be an even number'           )
72      nsecd   = NINT(rday           )
73      nsecd05 = NINT(0.5 * rday     )
74      ndt     = NINT(      rdttra(1))
75      ndt05   = NINT(0.5 * rdttra(1))
76
77
78      ! set the calandar from ndastp (read in restart file and namelist)
79
80      nyear   =   ndastp / 10000
81      nmonth  = ( ndastp - (nyear * 10000) ) / 100
82      nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 ) 
83
84      CALL ymds2ju( nyear, nmonth, nday, 0.0, fjulday )  ! we assume that we start run at 00:00
85      IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < 0.1 / rday )   fjulday = REAL(NINT(fjulday),wp)   ! avoid truncation error
86      fjulday = fjulday + 1.                             ! move back to the day at nit000 (and not at nit000 - 1)
87
88      nsec1jan000 = 0
89      CALL day_mth
90     
91      IF ( nday == 0 ) THEN     !   for ex if ndastp = ndate0 - 1
92         nmonth = nmonth - 1 
93         nday = nmonth_len(nmonth)
94      ENDIF
95      IF ( nmonth == 0 ) THEN   ! go at the end of previous year
96         nmonth = 12
97         nyear = nyear - 1
98         nsec1jan000 = nsec1jan000 - nsecd * nyear_len(0)
99         IF( nleapy == 1 )   CALL day_mth
100      ENDIF
101     
102      ! day since january 1st
103      nday_year = nday + SUM( nmonth_len(1:nmonth - 1) )
104     
105      ! number of seconds since the beginning of current year/month at the middle of the time-step
106      nsec_year  = nday_year * nsecd - ndt05   ! 1 time step before the middle of the first time step
107      nsec_month = nday      * nsecd - ndt05   ! because day will be called at the beginning of step
108      nsec_day   =             nsecd - ndt05
109
110      ! control print
111      IF(lwp) WRITE(numout,'(a,i6,a,i2,a,i2,a,i6)')' ==============>> 1/2 time step before the start of the run DATE Y/M/D = ',   &
112           &                   nyear, '/', nmonth, '/', nday, '  nsec_day:', nsec_day
113
114      ! Up to now, calendar parameters are related to the end of previous run (nit000-1)
115      ! call day to set the calendar parameters at the begining of the current simulaton. needed by iom_init
116      CALL day( nit000 )
117
118     
119   END SUBROUTINE day_init
120
121
122   SUBROUTINE day_mth
123      !!----------------------------------------------------------------------
124      !!                   ***  ROUTINE day_init  ***
125      !!
126      !! ** Purpose :   calendar values related to the months
127      !!
128      !! ** Action  : - nmonth_len    : length in days of the months of the current year
129      !!              - nyear_len     : length in days of the previous/current year
130      !!              - nmonth_half   : second since the beginning of the year and the halft of the months
131      !!              - nmonth_end    : second since the beginning of the year and the end of the months
132      !!----------------------------------------------------------------------
133      INTEGER  ::   jm               ! dummy loop indice
134      !!----------------------------------------------------------------------
135
136      ! length of the month of the current year (from nleapy, read in namelist)
137      IF ( nleapy < 2 ) THEN
138         nmonth_len(:) = (/ 31, 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31, 31 /)
139         nyear_len(:) = 365
140         IF ( nleapy == 1 ) THEN   ! we are using calandar with leap years
141            IF ( MOD(nyear-1, 4) == 0 .AND. ( MOD(nyear-1, 400) == 0 .OR. MOD(nyear-1, 100) /= 0 ) ) THEN
142               nyear_len(0) = 366
143            ENDIF
144            IF ( MOD(nyear, 4) == 0 .AND. ( MOD(nyear, 400) == 0 .OR. MOD(nyear, 100) /= 0 ) ) THEN
145               nmonth_len(2) = 29
146               nyear_len(1) = 366
147            ENDIF
148         ENDIF
149      ELSE
150         nmonth_len(:) = nleapy   ! all months with nleapy days per year
151         nyear_len(:) = 12 * nleapy
152      ENDIF
153
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
166      nmonth_end(0) = 0
167      DO jm = 1, 13
168         nmonth_end(jm) = nmonth_end(jm-1) + nsecd * nmonth_len(jm)
169      END DO
170      !           
171   END SUBROUTINE
172
173
174   SUBROUTINE day( kt )
175      !!----------------------------------------------------------------------
176      !!                      ***  ROUTINE day  ***
177      !!
178      !! ** Purpose :   Compute the date with a day iteration IF necessary.
179      !!
180      !! ** Method  : - ???
181      !!
182      !! ** Action  : - nyear     : current year
183      !!              - nmonth    : current month of the year nyear
184      !!              - nday      : current day of the month nmonth
185      !!              - nday_year : current day of the year nyear
186      !!              - ndastp    : = nyear*10000 + nmonth*100 + nday
187      !!              - adatrj    : date in days since the beginning of the run
188      !!              - nsec_year : current time of the year (in second since 00h, jan 1st)
189      !!----------------------------------------------------------------------     
190      INTEGER, INTENT(in) ::   kt        ! ocean time-step indices
191      !
192      CHARACTER (len=25) ::   charout
193      REAL(wp)           ::   zprec      ! fraction of day corresponding to 0.1 second
194      !!----------------------------------------------------------------------
195      zprec = 0.1 / rday
196      !                                                 ! New time-step
197      nsec_year  = nsec_year  + ndt 
198      nsec_month = nsec_month + ndt                 
199      nsec_day   = nsec_day   + ndt               
200      adatrj  = adatrj  + rdttra(1) / rday
201      fjulday = fjulday + rdttra(1) / rday
202      IF( ABS(fjulday - REAL(NINT(fjulday),wp)) < zprec )   fjulday = REAL(NINT(fjulday),wp)   ! avoid truncation error
203      IF( ABS(adatrj  - REAL(NINT(adatrj ),wp)) < zprec )   adatrj  = REAL(NINT(adatrj ),wp)   ! avoid truncation error
204     
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         IF(lwp) WRITE(numout,'(a,i8,a,i4.4,a,i2.2,a,i2.2,a,i3.3)') '======>> time-step =', kt,   &
228              &   '      New day, DATE Y/M/D = ', nyear, '/', nmonth, '/', nday, '      nday_year = ', nday_year
229         IF(lwp) WRITE(numout,'(a,i8,a,i7,a,i5)') '         nsec_year = ', nsec_year,   &
230              &   '   nsec_month = ', nsec_month, '   nsec_day = ', nsec_day
231      ENDIF
232     
233      IF(ln_ctl) THEN
234         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear
235         CALL prt_ctl_info(charout)
236      ENDIF
237
238   END SUBROUTINE day
239
240   !!======================================================================
241END MODULE daymod
Note: See TracBrowser for help on using the repository browser.