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 trunk/NEMO/OPA_SRC – NEMO

source: trunk/NEMO/OPA_SRC/daymod.F90 @ 896

Last change on this file since 896 was 888, checked in by ctlod, 16 years ago

merge dev_001_SBC branche with the trunk to include the New Surface Module package, see ticket: #113

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 10.0 KB
Line 
1MODULE daymod
2   !!======================================================================
3   !!                       ***  MODULE  daymod  ***
4   !! Ocean        :  calendar
5   !!=====================================================================
6   !! History :        !  94-09  (M. Pontaud M. Imbard)  Original code
7   !!                  !  97-03  (O. Marti)
8   !!                  !  97-05  (G. Madec)
9   !!                  !  97-08  (M. Imbard)
10   !!             9.0  !  03-09  (G. Madec)  F90 + nyear, nmonth, nday
11   !!                  !  04-01  (A.M. Treguier) new calculation based on adatrj
12   !!                  !  06-08  (G. Madec)  surface module major update
13   !!----------------------------------------------------------------------     
14
15   !!----------------------------------------------------------------------
16   !!   day        : calendar
17   !!----------------------------------------------------------------------
18   USE dom_oce         ! ocean space and time domain
19   USE phycst          ! physical constants
20   USE in_out_manager  ! I/O manager
21   USE prtctl          ! Print control
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC day        ! called by step.F90
27
28   INTEGER , PUBLIC ::   nyear       !: current year
29   INTEGER , PUBLIC ::   nmonth      !: current month
30   INTEGER , PUBLIC ::   nday        !: current day of the month
31   INTEGER , PUBLIC ::   nday_year   !: current day counted from jan 1st of the current year
32   REAL(wp), PUBLIC ::   rsec_year   !: current time step counted in second since 00h jan 1st of the current year
33   REAL(wp), PUBLIC ::   rsec_month  !: current time step counted in second since 00h 1st day of the current month
34   REAL(wp), PUBLIC ::   rsec_day    !: current time step counted in second since 00h         of the current day
35   INTEGER , PUBLIC ::   ndastp      !: time step date in year/month/day aammjj
36
37!!gm supprimer adatrj et adatrj0 ==> remplacer par rsecday.....
38   REAL(wp), PUBLIC ::   adatrj      !: number of elapsed days since the begining of the run
39   REAL(wp), PUBLIC ::   adatrj0     !: value of adatrj at nit000-1 (before the present run).
40   !                                 !  it is the accumulated duration of previous runs
41   !                                 !  that may have been run with different time steps.
42   INTEGER , PUBLIC, DIMENSION(0:13) ::   nmonth_len   !: length of the current year
43
44   INTEGER, PUBLIC, DIMENSION(12) ::   nbiss = (/ 31, 29, 31, 30, 31, 30,    &  !: number of days per month
45      &                                           31, 31, 30, 31, 30, 31 /)     !: (leap-year)
46   INTEGER, PUBLIC, DIMENSION(12) ::   nobis = (/ 31, 28, 31, 30, 31, 30,    &  !: number of days per month
47      &                                           31, 31, 30, 31, 30, 31 /)     !: (365 days a year)
48
49   REAL(wp), PUBLIC, DIMENSION(0:14) ::   rmonth_half(0:14)
50
51   !!----------------------------------------------------------------------
52   !!  OPA 9.0 , LOCEAN-IPSL (2006)
53   !! $Id$
54   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
55   !!----------------------------------------------------------------------
56
57CONTAINS
58
59   SUBROUTINE day( kt )
60      !!----------------------------------------------------------------------
61      !!                      ***  ROUTINE day  ***
62      !!
63      !! ** Purpose :   Compute the date with a day iteration IF necessary.
64      !!
65      !! ** Method  : - ???
66      !!
67      !! ** Action  : - nyear     : current year
68      !!              - nmonth    : current month of the year nyear
69      !!              - nday      : current day of the month nmonth
70      !!              - nday_year : current day of the year nyear
71      !!              - ndastp    : =nyear*10000+nmonth*100+nday
72      !!              - adatrj    : date in days since the beginning of the run
73      !!              - rsec_year : current time of the year (in second since 00h, jan 1st)
74      !!----------------------------------------------------------------------     
75      INTEGER, INTENT(in) ::   kt        ! ocean time-step indices
76      !
77      INTEGER  ::   js, jm               ! dummy loop indice
78      CHARACTER (len=25) ::   charout
79      !!----------------------------------------------------------------------
80
81      ! 0.  initialization of adatrj0 and nday, nmonth,nyear, nday_year.
82      !     ndastp has been initialized in domain.F90 or restart.F90
83      !-----------------------------------------------------------------
84
85      !                        ! ---------------- !
86      IF( kt == -1 ) THEN      !  Initialisation  !
87         !                     ! ---------------- !
88         !
89         IF( .NOT.ln_rstart )   adatrj0 = 0.e0      ! adatrj0 initialized in rst_read when restart
90
91         ! set the calandar from adatrj0 and ndastp (read in restart file and namelist)
92         adatrj  =   adatrj0      !???? bug.... toujours rest   !!gm
93         nyear   =   ndastp / 10000
94         nmonth  = ( ndastp - (nyear * 10000) ) / 100
95         nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 ) 
96
97         ! length of the month of the current year (from nleapy, read in namelist)
98         nmonth_len(0) = nbiss(12)   ;   nmonth_len(13) = nbiss(1)
99         SELECT CASE( nleapy )
100         CASE( 1  )   
101            IF( MOD( nyear, 4 ) == 0 ) THEN
102               ;          nmonth_len(1:12) = nbiss(:)      ! 366 days per year (leap year)
103            ELSE
104               ;          nmonth_len(1:12) = nobis(:)      ! 365 days per year
105            ENDIF
106         CASE( 0  )   ;   nmonth_len(1:12) = nobis(:)      ! 365 days per year
107         CASE( 2: )   ;   nmonth_len(1:13) = nleapy        ! 12*nleapy days per year
108         END SELECT
109
110         ! half month in second since the bigining of the year
111         rmonth_half(0) = - 0.5 * rday * REAL( nmonth_len( 0 ) )
112         DO jm = 1, 12
113            rmonth_half(jm) = rmonth_half(jm-1) + 0.5 * rday * REAL( nmonth_len(jm-1) + nmonth_len(jm) )
114         END DO
115         rmonth_half(13) = rmonth_half( 1 ) + 365. * rday
116         rmonth_half(14) = rmonth_half( 2 ) + 365. * rday
117
118         ! day since january 1st (useful to read  daily forcing fields)
119         nday_year =  nday
120         DO js = 1, nmonth - 1             ! accumulates days of previous months of this year
121            nday_year = nday_year + nmonth_len(js)
122         END DO
123
124         ! number of seconds since...
125         IF( ln_rstart )   THEN
126            rsec_year  = REAL( nday_year ) * rday     - rdttra(1)      ! 00h 1st day of the current year
127            rsec_month = REAL( nday      ) * rday     - rdttra(1)      ! 00h 1st day of the current month
128            rsec_day   = REAL( nday      ) * rday     - rdttra(1)      ! 00h         of the current day
129         ELSE
130            rsec_year  = REAL( nday_year - 1 ) * rday - rdttra(1)      ! 00h 1st day of the current year
131            rsec_month = REAL( nday      - 1 ) * rday - rdttra(1)      ! 00h 1st day of the current month
132            rsec_day   =                              - rdttra(1)      ! 00h         of the current day
133         ENDIF
134
135         ! control print
136         IF(lwp) WRITE(numout,*)' ==============>> time-step =', kt, ' Initial DATE Y/M/D = ',   &
137               &                   nyear, '/', nmonth, '/', nday, '  rsec_day:', rsec_day
138
139         !                     ! -------------------------------- !
140      ELSE                     !  Model calendar at time-step kt  !
141         !                     ! -------------------------------- !
142
143         rsec_year  = rsec_year  + rdttra(1)                 ! New time-step
144         rsec_month = rsec_month + rdttra(1)                 ! New time-step
145         rsec_day   = rsec_day   + rdttra(1)                 ! New time-step
146
147         adatrj    = adatrj0 + ( kt - nit000 + 1 ) * rdttra(1) / rday
148
149         IF( rsec_day >= rday ) THEN
150            !
151            rsec_day  = 0.e0                               ! NEW day
152            nday      = nday + 1
153            nday_year = nday_year + 1
154            !
155            IF( nday == nmonth_len(nmonth) + 1 ) THEN      ! NEW month
156               nday  = 1
157               rsec_month = 0.e0   
158               nmonth = nmonth + 1
159               IF( nmonth == 13 ) THEN                     ! NEW year
160                  nyear     = nyear + 1
161                  nmonth    = 1
162                  nday_year = 1
163                  rsec_year = 0.e0
164                  !                                        ! update the length of the month
165                  IF( nleapy == 1 ) THEN                   ! of the current year (if necessary)
166                     IF( MOD( nyear, 4 ) == 0 ) THEN
167                        nmonth_len(1:12) = nbiss(:)              ! 366 days per year (leap year)
168                     ELSE
169                        nmonth_len(1:12) = nobis(:)              ! 365 days per year
170                     ENDIF
171                     ! half month in second since the bigining of the year
172                     rmonth_half(0) = - 0.5 * rday * REAL( nmonth_len( 0 ) )
173                     DO jm = 1, 12
174                        rmonth_half(jm) = rmonth_half(jm-1) + 0.5 * rday * REAL( nmonth_len(jm-1) + nmonth_len(jm) )
175                     END DO
176                     rmonth_half(13) = rmonth_half( 1 ) + 365. * rday
177                     rmonth_half(14) = rmonth_half( 2 ) + 365. * rday
178                  ENDIF
179               ENDIF
180            ENDIF
181
182            !
183            ndastp = nyear * 10000 + nmonth * 100 + nday   ! NEW date
184            !
185           IF(lwp) WRITE(numout,'(a,i8,a,i4,a,i2,a,i2,a,i3)') '======>> time-step =', kt,   &
186              &   '      New day, DATE Y/M/D = ', nyear, '/', nmonth, '/', nday, '      nday_year = ', nday_year
187           IF(lwp) WRITE(numout,'(a,F9.0,a,F9.0,a,F9.0)') '         rsec_year = ', rsec_year,   &
188              &   '   rsec_month = ', rsec_month, '   rsec_day = ', rsec_day
189         ENDIF
190
191         IF(ln_ctl) THEN
192            WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear
193            CALL prt_ctl_info(charout)
194         ENDIF
195         !
196      ENDIF
197
198   END SUBROUTINE day
199
200   !!======================================================================
201END MODULE daymod
Note: See TracBrowser for help on using the repository browser.