source: branches/ORCHIDEE_2_2/ORCHIDEE/src_global/time.f90 @ 8579

Last change on this file since 8579 was 7792, checked in by josefine.ghattas, 20 months ago

Minimum of modifications to have PRINTLEV=1 functionnality(only master opens out_orchidee text file) as in the ticket #874

File size: 15.1 KB
Line 
1! ================================================================================================================================
2!  MODULE       : time
3!
4!  CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6!  LICENCE      : IPSL (2006)
7!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF   This module contians the time information for ORCHIDEE
10!!
11!!\n DESCRIPTION: This module contains the time information for ORCHIDEE.
12!! Time variables are calculated and updated at each time step. The variables are public and can be used from other modules.
13!! The time variables must not be modified outside this module.
14!!
15!! Time variables in this module are given for the interval corresponding to current time-step.
16!! The variables xxx_start and xxx_end are given to describe the time interval, either on julian(julian_start, julian_end) or
17!! yymmddsec format (year_start/end, month_start/end, day_start/end, sec_start/end). The variables can be used in all other modules.
18!! Logical variables telling if it's the last or first time-step of the day, of the month or of the year are also available. 
19!!
20!! Subroutines in module time :
21!!   time_initialize : To initialize time variables.
22!!                     Public subroutine called from intersurf_initialize_2d, intersurf_initialize_gathered or orchideedriver.
23!!                     This subroutine is called before the first call to sechiba.
24!!   time_nextstep   : Update time variables in the beginning at each new time step.
25!!                     Public subroutine called from intersurf_main_2d, intersurf_main_gathered or orchideedriver.
26!!   time_interval   : Calculate the interval for a given time step. Local subroutine, called from time_nextstep.
27!!
28!! REFERENCE(S) : None
29!!
30!! SVN          :
31!! $HeadURL: $
32!! $Date: $
33!! $Revision: $
34!! \n
35!_ ================================================================================================================================
36MODULE time
37
38  USE defprec
39  USE constantes_var
40  USE mod_orchidee_para_var, ONLY : numout, is_mpi_root, is_omp_root
41  USE ioipsl
42  USE ioipsl_para
43 
44  IMPLICIT NONE
45  PRIVATE
46
47  PUBLIC :: time_initialize, time_nextstep
48
49  REAL(r_std), PUBLIC                 :: dt_sechiba         !! Lenght of time step in sechiba (s)
50!$OMP THREADPRIVATE(dt_sechiba)
51  REAL(r_std), PUBLIC                 :: dt_stomate         !! Length of time step in slow processes in stomate (s)
52!$OMP THREADPRIVATE(dt_stomate)
53  CHARACTER(LEN=20), PUBLIC           :: calendar_str       !! The calendar type
54!$OMP THREADPRIVATE(calendar_str)
55  INTEGER(i_std), SAVE, PUBLIC        :: year_start         !! Year at beginng of current time step
56!$OMP THREADPRIVATE(year_start)
57  INTEGER(i_std), SAVE, PUBLIC        :: month_start        !! Month at beginng of current time step
58!$OMP THREADPRIVATE(month_start)
59  INTEGER(i_std), SAVE, PUBLIC        :: day_start          !! Day in month at beginng of current time step
60!$OMP THREADPRIVATE(day_start)
61  REAL(r_std), SAVE, PUBLIC           :: sec_start          !! Seconds in the day at beginng of current time step
62!$OMP THREADPRIVATE(sec_start)
63  INTEGER(i_std), SAVE, PUBLIC        :: year_end           !! Year at end of current time step
64!$OMP THREADPRIVATE(year_end)
65  INTEGER(i_std), SAVE, PUBLIC        :: month_end          !! Month at end of current time step
66!$OMP THREADPRIVATE(month_end)
67  INTEGER(i_std), SAVE, PUBLIC        :: day_end            !! Day in month at end of current time step
68!$OMP THREADPRIVATE(day_end)
69  REAL(r_std), SAVE, PUBLIC           :: sec_end            !! Seconds in the day at end of current time step
70!$OMP THREADPRIVATE(sec_end)
71  CHARACTER(LEN=6), SAVE, PUBLIC      :: tstepint_type      !! Position of time step in the time interval
72!$OMP THREADPRIVATE(tstepint_type)
73  INTEGER(i_std), PUBLIC              :: month_len          !! Lenght of current month (d)
74!$OMP THREADPRIVATE(month_len)
75  REAL(r_std), PUBLIC                 :: one_day            !! Lenght of one day in seconds (s)
76!$OMP THREADPRIVATE(one_day)
77  REAL(r_std), PUBLIC                 :: one_year           !! Length of current year in days (d)
78!$OMP THREADPRIVATE(one_year)
79  REAL(r_std), PARAMETER, PUBLIC      :: one_hour = 3600.0  !! Lenght of hour in seconds (s) 
80
81  LOGICAL, PUBLIC                     :: FirstTsYear        !! Flag is true for the first sechiba time step on the year.
82!$OMP THREADPRIVATE(FirstTsYear)
83  LOGICAL, PUBLIC                     :: LastTsYear         !! Flag is true for the last sechiba time step of the year, previously named EndOfYear
84!$OMP THREADPRIVATE(LastTsYear)
85  LOGICAL, PUBLIC                     :: FirstTsMonth       !! Flag is true for the first sechiba time step of the month.
86!$OMP THREADPRIVATE(FirstTsMonth)
87  LOGICAL, PUBLIC                     :: LastTsMonth        !! Flag is true for the last sechiba time step of the month.
88!$OMP THREADPRIVATE(LastTsMonth)
89  LOGICAL, PUBLIC                     :: FirstTsDay         !! Flag is true for the first sechiba time step of the day.
90!$OMP THREADPRIVATE(FirstTsDay)
91  LOGICAL, PUBLIC                     :: LastTsDay          !! Flag is true for the last sechiba time step of the day.
92!$OMP THREADPRIVATE(LastTsDay)
93  REAL(r_std), SAVE, PUBLIC           :: date0_save         !! Start date of simulation, in juilan calendar
94!$OMP THREADPRIVATE(date0_save)
95  REAL(r_std), PUBLIC                 :: julian_diff        !! Days since the beginning of current year
96!$OMP THREADPRIVATE(julian_diff)
97  REAL(r_std), PUBLIC                 :: julian_start       !! Beginning of the interval for current time step, in juilan calendar
98!$OMP THREADPRIVATE(julian_start)
99  REAL(r_std), PUBLIC                 :: julian_end         !! End of the interval for current time step, in juilan calendar
100!$OMP THREADPRIVATE(julian_end)
101  REAL(r_std), SAVE, PUBLIC           :: julian0            !! First day of this year in julian caledrier
102!$OMP THREADPRIVATE(julian0)
103  INTEGER(i_std), SAVE, PRIVATE       :: printlev_loc       !! Local level of text output for current module
104!$OMP THREADPRIVATE(printlev_loc)
105 
106
107CONTAINS
108
109!!  =============================================================================================================================
110!! SUBROUTINE:    time_initialize()
111!!
112!>\BRIEF          Initalize time information
113!!
114!! DESCRIPTION:   Initialize time information. This subroutine is called only in the intialization phase of the model and gives
115!!                the basic information on the calendar and time interval.
116!!
117!! \n
118!_ ==============================================================================================================================
119
120  SUBROUTINE time_initialize(kjit, date0_loc, dt_sechiba_loc, tstepint)
121
122    !! 0.1 Input arguments
123    INTEGER(i_std), INTENT(in)   :: kjit           !! Time step of the restart file
124    REAL(r_std), INTENT(in)      :: date0_loc      !! The date at which kjit=0
125    REAL(r_std), INTENT(in)      :: dt_sechiba_loc !! Time step of sechiba component
126    CHARACTER(LEN=*), INTENT(in) :: tstepint       !! Position of the time stamp: beginning, centre or end of time step
127                                                   !! Possible values for tstepint : START, CENTER, END
128
129    !! Initialize local printlev variable
130    !! It is not possible here to use the function get_printlev for problems with circular dependecies between modules
131    printlev_loc=printlev
132    CALL getin_p('PRINTLEV_time', printlev_loc)
133    IF (printlev_loc .EQ. 1) THEN
134       IF (is_mpi_root.AND.is_omp_root) THEN
135          ! Keep output level 1 only for the master processor
136          printlev_loc=1
137       ELSE
138          ! Change output level for all other processors
139          printlev_loc=0
140       END IF
141    END IF
142 
143
144
145    !! Save length of sechiba time step in module variable
146    !! Time step for sechiba comes from the atmospheric model or from the
147    !! offline driver which reads it from parameter DT_SECHIBA
148    dt_sechiba = dt_sechiba_loc
149
150    !! Save tstepint in global variable
151    tstepint_type = tstepint
152    IF (tstepint_type /= "START" .AND. tstepint_type /= "END") THEN
153       WRITE(numout,*) 'Unknown option for time interval, tstepint_type=', tstepint_type
154       CALL ipslerr_p(3,'time_initialize', 'Unknown time iterval type.',&
155            'The time stamp given can have 2 position on the interval :',' START or END')
156    END IF
157
158    !! Save the start date in the module
159    date0_save = date0_loc
160
161    !! Get the calendar from IOIPSL, it is already initialized
162    CALL ioget_calendar(calendar_str)
163
164    !! Get year lenght in days and day lenght in seconds
165    CALL ioget_calendar(one_year, one_day)
166
167    !Config Key   = DT_STOMATE
168    !Config Desc  = Time step of STOMATE and other slow processes
169    !Config If    = OK_STOMATE
170    !Config Def   = one_day
171    !Config Help  = Time step (s) of regular update of vegetation
172    !Config         cover, LAI etc. This is also the time step of STOMATE.
173    !Config Units = [seconds]
174    dt_stomate = one_day
175    CALL getin_p('DT_STOMATE', dt_stomate)
176
177 
178    IF (printlev_loc >=1) THEN
179       WRITE(numout,*) "time_initialize : calendar_str= ",calendar_str
180       WRITE(numout,*) "time_initialize : dt_sechiba(s)= ",dt_sechiba," dt_stomate(s)= ", dt_stomate
181       WRITE(numout,*) "time_initialize : date0_save= ",date0_save," kjit= ",kjit
182    ENDIF
183   
184    CALL time_nextstep(kjit)
185   
186  END SUBROUTINE time_initialize
187 
188!!  =============================================================================================================================
189!! SUBROUTINE:    time_nextstep()
190!!
191!>\BRIEF          Update the time information for the next time step.
192!!
193!! DESCRIPTION:   This subroutine will place in the public variables of the module all the time information
194!!                needed by ORCHIDEE for this new time step.
195!!
196!! \n
197!_ ==============================================================================================================================
198  SUBROUTINE time_nextstep(kjit)
199   
200    !! 0.1 Input variables
201    INTEGER(i_std), INTENT(in)   :: kjit       !! Current time step
202
203
204    !! Calculate the new time interval for current time step
205    CALL time_interval(kjit, year_start, month_start, day_start, sec_start, &
206                             year_end,   month_end,   day_end,   sec_end)
207   
208    !! Calculate julian0: the julian date for the 1st of January in current year
209    CALL ymds2ju(year_start,1,1,zero, julian0)
210
211    !! Caluclate julian_diff: The diffrence of the end of current time-step and the beginning of the year in julian days
212    julian_diff = julian_end - julian0
213
214    !! Update variables for year length
215    CALL ioget_calendar(one_year, one_day)
216
217    !! Calculate number of days in the current month, using the start of the time-interval for current time-step
218    month_len = ioget_mon_len(year_start,month_start)
219
220
221    !! Calculate logical variables true if the current time-step corresponds to the end or beggining of a day, month or year
222    FirstTsDay = .FALSE.
223    FirstTsMonth = .FALSE.
224    FirstTsYear = .FALSE.
225    LastTsDay = .FALSE.
226    LastTsMonth = .FALSE.
227    LastTsYear = .FALSE.
228 
229    IF (sec_start >= -1 .AND. sec_start < dt_sechiba-1 ) THEN
230       FirstTsDay = .TRUE.
231       IF ( day_start == 1 ) THEN
232          FirstTsMonth = .TRUE.
233          IF ( month_start == 1) THEN
234             FirstTsYear = .TRUE.
235          END IF
236       END IF
237    ELSE IF (sec_start >= one_day-dt_sechiba-1 .AND. sec_start < one_day-1 ) THEN
238       LastTsDay = .TRUE.
239       IF ( day_start == month_len ) THEN
240          LastTsMonth = .TRUE.
241          IF ( month_start == 12) THEN
242             LastTsYear = .TRUE.
243          END IF
244       END IF
245    END IF
246
247
248    !! Write debug information depending on printlev_loc.
249    IF ( ((printlev_loc >= 4) .OR. (printlev_loc >=2 .AND. FirstTsMonth)) .OR. (printlev_loc>=1 .AND. FirstTsYear)) THEN
250       WRITE(numout,*) "time_nextstep: Time interval for time step :", kjit
251       WRITE(numout,"(' time_nextstep: Start of interval         ', I4.4,'-',I2.2,'-',I2.2,' ',F12.4)") &
252            year_start, month_start, day_start, sec_start
253       WRITE(numout,"(' time_nextstep: End of interval           ', I4.4,'-',I2.2,'-',I2.2,' ',F12.4)") &
254            year_end, month_end, day_end, sec_end
255       WRITE(numout,*) "time_nextstep: month_len=",month_len, " one_year=",one_year
256       WRITE(numout,*) ""
257    END IF
258    IF (printlev_loc >= 4) THEN
259       WRITE(numout,*) "time_nextstep: FirstTsDay=", FirstTsDay," FirstTsMonth=",FirstTsMonth," FirstTsYear=", FirstTsYear
260       WRITE(numout,*) "time_nextstep: LastTsDay=", LastTsDay," LastTsMonth=",LastTsMonth," LastTsYear=", LastTsYear
261       WRITE(numout,*) "time_nextstep: julian0=",julian0, " julian_diff=",julian_diff
262       WRITE(numout,*) ""
263    END IF
264    IF ((printlev_loc >= 2) .AND. FirstTsDay) THEN
265       WRITE(numout,"(' Date: ', I4.4,'-',I2.2,'-',I2.2,' ',F8.4,'sec at timestep ',I12.4)") &
266            year_start, month_start, day_start, sec_start, kjit
267    END IF
268
269  END SUBROUTINE time_nextstep
270
271!!  =============================================================================================================================
272!! SUBROUTINE:    time_interval()
273!!
274!>\BRIEF          Computes the interval corresponging to the given time step.
275!!
276!! DESCRIPTION:   This subroutine will compute the interval of time for the given time step.
277!!                It will use the tstepint_type variable which was set at initilisation.
278!!
279!! \n
280!_ ==============================================================================================================================
281
282  SUBROUTINE time_interval(kjit, year_s, month_s, day_s, sec_s, &
283                                 year_e, month_e, day_e, sec_e)
284
285    !! 0.1 Input variables
286    INTEGER(i_std), INTENT(in)                  :: kjit      !! Current time step
287
288    !! 0.2 Output variables
289    INTEGER(i_std), INTENT(out)                 :: year_s, month_s, day_s
290    INTEGER(i_std), INTENT(out)                 :: year_e, month_e, day_e
291    REAL(r_std), INTENT(out)                    :: sec_s
292    REAL(r_std), INTENT(out)                    :: sec_e
293   
294
295    !! Calculate the interval for current time step
296    !! tstepint_type is used to know how the interval is defined around the time-stamp of the time-step
297    SELECT CASE (TRIM(tstepint_type))
298       CASE ("START ")
299          !! Calculate the start date of the interval
300          julian_start = itau2date(kjit, date0_save, dt_sechiba)
301          !! Calculate the end date of the interval using kjti+1
302          julian_end = itau2date(kjit+1, date0_save, dt_sechiba)
303       CASE("END")
304          !! Calculate the start date of the interval
305          julian_start = itau2date(kjit-1, date0_save, dt_sechiba)
306          !! Calculate the end date of the interval
307          julian_end = itau2date(kjit, date0_save, dt_sechiba)
308       CASE DEFAULT
309          WRITE(numout,*) "time_interval: tstepint_type = ", tstepint_type
310          CALL ipslerr_p(3,'time_interval', 'Unknown time iterval type.', &
311               'The time stamp given can have 3 position on the interval :',' START, CENTER or END')
312       END SELECT
313
314       !! Calculate year, month, day and sec for julian_start date
315       CALL ju2ymds (julian_start, year_s, month_s, day_s, sec_s)
316
317       !! Calculate year, month, day and sec for julian_end date
318       CALL ju2ymds (julian_end, year_e, month_e, day_e, sec_e)
319
320   
321  END SUBROUTINE time_interval
322
323END MODULE time
Note: See TracBrowser for help on using the repository browser.