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_1_beta/NEMO/OFF_SRC – NEMO

source: tags/nemo_v3_1_beta/NEMO/OFF_SRC/daymod.F90 @ 9319

Last change on this file since 9319 was 1265, checked in by cetlod, 15 years ago

clean OFFLINE routines to avoid warning when compiling, see ticket:303

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 6.7 KB
Line 
1MODULE daymod
2   !!======================================================================
3   !!                       ***  MODULE  daymod  ***
4   !! Ocean        :  calendar
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !!   day        : calendar
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE dom_oce         ! ocean space and time domain
12   USE phycst          ! physical constants
13   USE in_out_manager  ! I/O manager
14
15   IMPLICIT NONE
16   PRIVATE
17
18   !! * Routine accessibility
19   PUBLIC day        ! called by step.F90
20
21   !! * Shared module variables
22   INTEGER , PUBLIC ::   &  !:
23      nyear     ,   &  !: current year
24      nmonth    ,   &  !: current month
25      nday      ,   &  !: current day of the month
26      nday_year ,   &  !: curent day counted from jan 1st of the current year
27      ndastp           !: time step date in year/month/day aammjj
28
29   REAL(wp), PUBLIC ::   &  !:
30       adatrj   ,   &  !: number of elapsed days since the begining of the run
31       adatrj0         !: value of adatrj at nit000-1 (before the present run).
32       !               !  it is the accumulated duration of previous runs
33       !               !  that may have been run with different time steps.
34
35   INTEGER, PUBLIC, DIMENSION(12) ::   nbiss = (/ 31, 29, 31, 30, 31, 30,    &  !: number of days per month
36      &                                           31, 31, 30, 31, 30, 31 /)     !: (leap-year)
37   INTEGER, PUBLIC, DIMENSION(12) ::   nobis = (/ 31, 28, 31, 30, 31, 30,    &  !: number of days per month
38      &                                           31, 31, 30, 31, 30, 31 /)     !: (365 days a year)
39
40   !!----------------------------------------------------------------------
41   !!  OPA 9.0 , LOCEAN-IPSL (2005)
42   !! $Id$
43   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
44   !!----------------------------------------------------------------------
45
46CONTAINS
47
48   SUBROUTINE day( kt )
49      !!----------------------------------------------------------------------
50      !!                      ***  ROUTINE day  ***
51      !!
52      !! ** Purpose :   Compute the date with a day iteration IF necessary.
53      !!
54      !! ** Method  : - ???
55      !!
56      !! ** Action  : - nyear     : current year
57      !!              - nmonth    : current month of the year nyear
58      !!              - nday      : current day of the month nmonth
59      !!              - nday_year : current day of the year nyear
60      !!              - ndastp    : =nyear*10000+nmonth*100+nday
61      !!              - adatrj    : date in days since the beginning of the run
62      !!
63      !! History :
64      !!        !  94-09  (M. Pontaud M. Imbard)  Original code
65      !!        !  97-03  (O. Marti)
66      !!        !  97-05  (G. Madec)
67      !!        !  97-08  (M. Imbard)
68      !!   9.0  !  03-09  (G. Madec)  F90 + nyear, nmonth, nday
69      !!        !  04-01  (A.M. Treguier) new calculation based on adatrj
70      !!----------------------------------------------------------------------     
71      !! * Arguments
72      INTEGER, INTENT( in ) ::   kt      ! ocean time-step indices
73
74      !! * Local declarations
75      INTEGER  ::   js                   ! dummy loop indice
76      INTEGER  ::   iend, iday0, iday1   ! temporary integers
77      REAL(wp) :: zadatrjn, zadatrjb     ! adatrj at timestep kt-1 and kt-2
78      !!----------------------------------------------------------------------
79
80      ! 0.  initialization of adatrj0 and nday, nmonth,nyear, nday_year.
81      !     ndastp has been initialized in domain.F90 or restart.F90
82      !-----------------------------------------------------------------
83
84      IF( kt == nit000 ) THEN
85
86         IF( .NOT.ln_rstart )   adatrj0 = 0.e0      ! adatrj0 initialized in rst_read when restart
87
88         adatrj  = adatrj0
89         nyear   =   ndastp / 10000
90         nmonth  = ( ndastp - (nyear * 10000) ) / 100
91         nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 ) 
92
93         ! Calculates nday_year, day since january 1st (useful to read  daily forcing fields)
94         nday_year =  nday
95         !                               ! accumulates days of previous months of this year
96         DO js = 1, nmonth-1
97            IF( nleapy == 1 .AND. MOD( nyear, 4 ) == 0 ) THEN
98               nday_year = nday_year + nbiss(js)
99            ELSE
100               nday_year = nday_year + nobis(js)
101            ENDIF
102         END DO
103
104      ENDIF
105
106      ! I.  calculates adatrj, zadatrjn, zadatrjb.
107      ! ------------------------------------------------------------------
108
109      adatrj    = adatrj0 + ( kt - nit000 + 1 ) * rdttra(1) / rday
110      zadatrjn  = adatrj0 + ( kt - nit000     ) * rdttra(1) / rday
111      zadatrjb  = adatrj0 + ( kt - nit000 - 1 ) * rdttra(1) / rday
112
113
114      ! II.  increment the date.  The date corresponds to 'now' variables (kt-1),
115      !      which is the time step of forcing fields.
116      !      Do not do this at nit000  unless nrstdt= 2
117      !      In that case ndastp (read in restart) was for step nit000-2
118      ! -------------------------------------------------------------------
119
120      iday0 = INT( zadatrjb )
121      iday1 = INT( zadatrjn )
122
123      IF( iday1 - iday0 >= 1 .AND. ( kt /= nit000 .OR. nrstdt == 2 ) ) THEN
124
125         ! increase calendar
126         nyear  =   ndastp / 10000
127         nmonth = ( ndastp - (nyear * 10000) ) / 100
128         nday   =   ndastp - (nyear * 10000) - ( nmonth * 100 ) 
129         nday = nday + 1
130         IF( nleapy == 1 .AND. MOD( nyear, 4 ) == 0 ) THEN
131            iend = nbiss(nmonth)
132         ELSEIF( nleapy > 1 ) THEN
133            iend = nleapy
134         ELSE
135            iend = nobis(nmonth)
136         ENDIF
137         IF( nday == iend + 1 ) THEN
138            nday  = 1
139            nmonth = nmonth + 1
140            IF( nmonth == 13 ) THEN
141               nmonth  = 1
142               nyear = nyear + 1
143            ENDIF
144         ENDIF
145         ndastp = nyear * 10000 + nmonth * 100 + nday
146
147         ! Calculates nday_year, day since january 1st (useful to read  daily forcing fields)
148         nday_year =  nday
149         !                                ! accumulates days of previous months of this year
150         DO js = 1, nmonth-1
151            IF( nleapy == 1 .AND. MOD( nyear, 4 ) == 0 ) THEN
152               nday_year = nday_year + nbiss(js)
153            ELSE
154               nday_year = nday_year + nobis(js)
155            ENDIF
156         END DO
157
158         IF(lwp) WRITE(numout,*)' ==============>> time-step =', kt, ' New day, DATE= ',   &
159            &                   nyear, '/', nmonth, '/', nday, 'nday_year:', nday_year
160      ENDIF
161
162   END SUBROUTINE day
163
164   !!======================================================================
165END MODULE daymod
Note: See TracBrowser for help on using the repository browser.