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 @ 3

Last change on this file since 3 was 3, checked in by opalod, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.4 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 ,          &   ! (non integer) number of elapsed days since the begining of the experiment
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   !!----------------------------------------------------------------------
36
37CONTAINS
38
39   SUBROUTINE day ( kt )
40      !!----------------------------------------------------------------------
41      !!                  ***  ROUTINE day  ***
42      !!
43      !! ** Purpose :   Compute the date with a day iteration IF necessary.
44      !!
45      !! ** Method  : - ???
46      !!
47      !! ** Action  : - nyear     : current year
48      !!              - nmonth    : current month of the year nyear
49      !!              - nday      : current day of the month nmonth
50      !!              - nday_year : current day of the year nyear
51      !!              - ndastp    : =nyear*10000+nmonth*100+nday
52      !!              - adatrj    : date in days since the beginning
53      !!                            of the experiment
54      !!
55      !! History :
56      !!        !  94-09  (M. Pontaud M. Imbard)  Original code
57      !!        !  97-03  (O. Marti)
58      !!        !  97-05  (G. Madec)
59      !!        !  97-08  (M. Imbard)
60      !!   9.0  !  03-09  (G. Madec)  F90 + nyear, nmonth, nday
61      !!        !  04-01  (A.M. Treguier) new calculation based on adatrj
62      !!----------------------------------------------------------------------     
63      !! * Arguments
64      INTEGER, INTENT( in ) ::   kt      ! ocean time-step indices
65
66      !! * Local declarations
67      INTEGER  ::   js                   ! dummy loop indice
68      INTEGER  ::   iend, iday0, iday1   ! temporary integers
69      REAL(wp) :: zadatrjn, zadatrjb     ! adatrj at timestep kt-1 and kt-2
70      !!----------------------------------------------------------------------
71      !!  OPA 9, LODYC-IPSL (2004)
72      !!----------------------------------------------------------------------
73
74      ! 0.  initialization of adatrj0 and nday, nmonth,nyear, nday_year.
75      !     ndastp has been initialized in domain.F90 or restart.F90
76      !-----------------------------------------------------------------
77
78      IF (  kt == nit000 ) THEN
79
80         IF ( .NOT.ln_rstart )   adatrj0 = 0.e0      ! adatrj0 initialized in rst_read when restart
81
82         adatrj  = adatrj0
83         nyear   =   ndastp / 10000
84         nmonth  = ( ndastp - (nyear * 10000) ) / 100
85         nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 ) 
86
87         ! Calculates nday_year, day since january 1st (useful to read  daily forcing fields)
88         nday_year =  nday
89         !                               ! accumulates days of previous months of this year
90         DO js = 1, nmonth-1
91            IF( MOD( nyear, 4 ) == 0 ) THEN
92               nday_year = nday_year + nbiss(js)
93            ELSE
94               nday_year = nday_year + nobis(js)
95            ENDIF
96         END DO
97
98      ENDIF
99
100      ! I.  calculates adatrj, zadatrjn, zadatrjb.
101      ! ------------------------------------------------------------------
102
103      adatrj    = adatrj0 + ( kt - nit000 + 1 ) * rdttra(1) / rday
104      zadatrjn  = adatrj0 + ( kt - nit000     ) * rdttra(1) / rday
105      zadatrjb  = adatrj0 + ( kt - nit000 - 1 ) * rdttra(1) / rday
106
107
108      ! II.  increment the date.  The date corresponds to 'now' variables (kt-1),
109      !      which is the time step of forcing fields.
110      !      Do not do this at nit000  unless nrstdt= 2
111      !      In that case ndastp (read in restart) was for step nit000-2
112      ! -------------------------------------------------------------------
113
114      iday0 = INT( zadatrjb )
115      iday1 = INT( zadatrjn )
116
117      if ( iday1 - iday0 >= 1 .AND. ( kt /= nit000 .OR. nrstdt == 2 ) ) THEN
118
119         ! increase calendar
120         nyear  =   ndastp / 10000
121         nmonth = ( ndastp - (nyear * 10000) ) / 100
122         nday   =   ndastp - (nyear * 10000) - ( nmonth * 100 ) 
123         nday = nday + 1
124         IF( nleapy == 1 .AND. MOD( nyear, 4 ) == 0 ) THEN
125            iend = nbiss(nmonth)
126         ELSEIF( nleapy > 1 ) THEN
127            iend = nleapy
128         ELSE
129            iend = nobis(nmonth)
130         ENDIF
131         IF( nday == iend + 1 ) THEN
132            nday  = 1
133            nmonth = nmonth + 1
134            IF( nmonth == 13 ) THEN
135               nmonth  = 1
136               nyear = nyear + 1
137            ENDIF
138         ENDIF
139         ndastp = nyear * 10000 + nmonth * 100 + nday
140
141         ! Calculates nday_year, day since january 1st (useful to read  daily forcing fields)
142         nday_year =  nday
143         !                                ! accumulates days of previous months of this year
144         DO js = 1, nmonth-1
145            IF( MOD( nyear, 4 ) == 0 ) THEN
146               nday_year = nday_year + nbiss(js)
147            ELSE
148               nday_year = nday_year + nobis(js)
149            ENDIF
150         END DO
151
152         IF(lwp) WRITE(numout,*)' ==============>> time-step =', kt, ' New day, DATE= ',   &
153            &                   nyear, '/', nmonth, '/', nday, 'nday_year:', nday_year
154      ENDIF
155
156      IF(l_ctl) WRITE(numout,*)' kt =', kt, 'd/m/y =', nday, nmonth, nyear
157
158   END SUBROUTINE day
159
160   !!======================================================================
161END MODULE daymod
Note: See TracBrowser for help on using the repository browser.