source: branches/publications/ORCHIDEE_DFv1.0_site/src_global/time.f90 @ 6715

Last change on this file since 6715 was 4693, checked in by josefine.ghattas, 7 years ago

Clean in text output, see ticket #394

File size: 15.2 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
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  INTEGER(i_std), PRIVATE             :: year_length        !! Lenght of current year in time step (tstp)
76!$OMP THREADPRIVATE(year_length)
77  REAL(r_std), PUBLIC                 :: one_day            !! Lenght of one day in seconds (s)
78!$OMP THREADPRIVATE(one_day)
79  REAL(r_std), PUBLIC                 :: one_year           !! Length of current year in days (d)
80!$OMP THREADPRIVATE(one_year)
81  REAL(r_std), PARAMETER, PUBLIC      :: one_hour = 3600.0  !! Lenght of hour in seconds (s) 
82
83  LOGICAL, PUBLIC                     :: FirstTsYear        !! Flag is true for the first sechiba time step on the year.
84!$OMP THREADPRIVATE(FirstTsYear)
85  LOGICAL, PUBLIC                     :: LastTsYear         !! Flag is true for the last sechiba time step of the year, previously named EndOfYear
86!$OMP THREADPRIVATE(LastTsYear)
87  LOGICAL, PUBLIC                     :: FirstTsMonth       !! Flag is true for the first sechiba time step of the month.
88!$OMP THREADPRIVATE(FirstTsMonth)
89  LOGICAL, PUBLIC                     :: LastTsMonth        !! Flag is true for the last sechiba time step of the month.
90!$OMP THREADPRIVATE(LastTsMonth)
91  LOGICAL, PUBLIC                     :: FirstTsDay         !! Flag is true for the first sechiba time step of the day.
92!$OMP THREADPRIVATE(FirstTsDay)
93  LOGICAL, PUBLIC                     :: LastTsDay          !! Flag is true for the last sechiba time step of the day.
94!$OMP THREADPRIVATE(LastTsDay)
95  REAL(r_std), SAVE, PUBLIC           :: date0_save         !! Start date of simulation, in juilan calendar
96!$OMP THREADPRIVATE(date0_save)
97  REAL(r_std), PUBLIC                 :: julian_diff        !! Days since the beginning of current year
98!$OMP THREADPRIVATE(julian_diff)
99  REAL(r_std), PUBLIC                 :: julian_start       !! Beginning of the interval for current time step, in juilan calendar
100!$OMP THREADPRIVATE(julian_start)
101  REAL(r_std), PUBLIC                 :: julian_end         !! End of the interval for current time step, in juilan calendar
102!$OMP THREADPRIVATE(julian_end)
103  REAL(r_std), SAVE, PUBLIC           :: julian0            !! First day of this year in julian caledrier
104!$OMP THREADPRIVATE(julian0)
105  INTEGER(i_std), SAVE, PRIVATE       :: printlev_loc       !! Local level of text output for current module
106!$OMP THREADPRIVATE(printlev_loc)
107 
108
109CONTAINS
110
111!!  =============================================================================================================================
112!! SUBROUTINE:    time_initialize()
113!!
114!>\BRIEF          Initalize time information
115!!
116!! DESCRIPTION:   Initialize time information. This subroutine is called only in the intialization phase of the model and gives
117!!                the basic information on the calendar and time interval.
118!!
119!! \n
120!_ ==============================================================================================================================
121
122  SUBROUTINE time_initialize(kjit, date0_loc, dt_sechiba_loc, tstepint)
123
124    !! 0.1 Input arguments
125    INTEGER(i_std), INTENT(in)   :: kjit           !! Time step of the restart file
126    REAL(r_std), INTENT(in)      :: date0_loc      !! The date at which kjit=0
127    REAL(r_std), INTENT(in)      :: dt_sechiba_loc !! Time step of sechiba component
128    CHARACTER(LEN=*), INTENT(in) :: tstepint       !! Position of the time stamp: beginning, centre or end of time step
129                                                   !! Possible values for tstepint : START, CENTER, END
130
131    !! Initialize local printlev variable
132    !! It is not possible here to use the function get_printlev for problems with circular dependecies between modules
133    printlev_loc=printlev
134    CALL getin_p('PRINTLEV_time', printlev_loc)
135
136    !! Save length of sechiba time step in module variable
137    !! Time step for sechiba comes from the atmospheric model or from the
138    !! offline driver which reads it from parameter DT_SECHIBA
139    dt_sechiba = dt_sechiba_loc
140
141    !! Save tstepint in global variable
142    tstepint_type = tstepint
143    IF (tstepint_type /= "START" .AND. tstepint_type /= "END") THEN
144       WRITE(numout,*) 'Unknown option for time interval, tstepint_type=', tstepint_type
145       CALL ipslerr_p(3,'time_initialize', 'Unknown time iterval type.',&
146            'The time stamp given can have 2 position on the interval :',' START or END')
147    END IF
148
149    !! Save the start date in the module
150    date0_save = date0_loc
151
152    !! Get the calendar from IOIPSL, it is already initialized
153    CALL ioget_calendar(calendar_str)
154
155    !! Get year lenght in days and day lenght in seconds
156    CALL ioget_calendar(one_year, one_day)
157
158    !! Get the number of sechiba time steps for 1 year (for the current year)
159    CALL tlen2itau('1Y', dt_sechiba, date0_save, year_length)
160
161    !Config Key   = DT_STOMATE
162    !Config Desc  = Time step of STOMATE and other slow processes
163    !Config If    = OK_STOMATE
164    !Config Def   = one_day
165    !Config Help  = Time step (s) of regular update of vegetation
166    !Config         cover, LAI etc. This is also the time step of STOMATE.
167    !Config Units = [seconds]
168    dt_stomate = one_day
169    CALL getin_p('DT_STOMATE', dt_stomate)
170
171 
172    IF (printlev_loc >=1) THEN
173       WRITE(numout,*) "time_initialize : calendar_str= ",calendar_str
174       WRITE(numout,*) "time_initialize : dt_sechiba(s)= ",dt_sechiba," dt_stomate(s)= ", dt_stomate
175       WRITE(numout,*) "time_initialize : date0_save= ",date0_save," kjit= ",kjit
176    ENDIF
177   
178    CALL time_nextstep(kjit)
179   
180  END SUBROUTINE time_initialize
181 
182!!  =============================================================================================================================
183!! SUBROUTINE:    time_nextstep()
184!!
185!>\BRIEF          Update the time information for the next time step.
186!!
187!! DESCRIPTION:   This subroutine will place in the public variables of the module all the time information
188!!                needed by ORCHIDEE for this new time step.
189!!
190!! \n
191!_ ==============================================================================================================================
192  SUBROUTINE time_nextstep(kjit)
193   
194    !! 0.1 Input variables
195    INTEGER(i_std), INTENT(in)   :: kjit       !! Current time step
196
197
198    !! Calculate the new time interval for current time step
199    CALL time_interval(kjit, year_start, month_start, day_start, sec_start, &
200                             year_end,   month_end,   day_end,   sec_end)
201   
202    !! Calculate julian0: the julian date for the 1st of January in current year
203    CALL ymds2ju(year_start,1,1,zero, julian0)
204
205    !! Caluclate julian_diff: The diffrence of the end of current time-step and the beginning of the year in julian days
206    julian_diff = julian_end - julian0
207
208    !! Update variables for year length
209    CALL ioget_calendar(one_year, one_day)
210    CALL tlen2itau('1Y', dt_sechiba, date0_save, year_length)
211
212    !! Calculate number of days in the current month, using the start of the time-interval for current time-step
213    month_len = ioget_mon_len(year_start,month_start)
214
215
216    !! Calculate logical variables true if the current time-step corresponds to the end or beggining of a day, month or year
217    FirstTsDay = .FALSE.
218    FirstTsMonth = .FALSE.
219    FirstTsYear = .FALSE.
220    LastTsDay = .FALSE.
221    LastTsMonth = .FALSE.
222    LastTsYear = .FALSE.
223 
224    IF (sec_start >= -1 .AND. sec_start < dt_sechiba-1 ) THEN
225       FirstTsDay = .TRUE.
226       IF ( day_start == 1 ) THEN
227          FirstTsMonth = .TRUE.
228          IF ( month_start == 1) THEN
229             FirstTsYear = .TRUE.
230          END IF
231       END IF
232    ELSE IF (sec_start >= one_day-dt_sechiba-1 .AND. sec_start < one_day-1 ) THEN
233       LastTsDay = .TRUE.
234       IF ( day_start == month_len ) THEN
235          LastTsMonth = .TRUE.
236          IF ( month_start == 12) THEN
237             LastTsYear = .TRUE.
238          END IF
239       END IF
240    END IF
241
242
243    !! Write debug information depending on printlev_loc.
244    IF ( ((printlev_loc >= 4) .OR. (printlev_loc >=2 .AND. FirstTsMonth)) .OR. (printlev_loc>=1 .AND. FirstTsYear)) THEN
245       WRITE(numout,*) "time_nextstep: Time interval for time step :", kjit
246       WRITE(numout,"(' time_nextstep: Start of interval         ', I4.4,'-',I2.2,'-',I2.2,' ',F12.4)") &
247            year_start, month_start, day_start, sec_start
248       WRITE(numout,"(' time_nextstep: End of interval           ', I4.4,'-',I2.2,'-',I2.2,' ',F12.4)") &
249            year_end, month_end, day_end, sec_end
250       WRITE(numout,*) "time_nextstep: month_len=",month_len, " one_year=",one_year
251       WRITE(numout,*) ""
252    END IF
253    IF (printlev_loc >= 4) THEN
254       WRITE(numout,*) "time_nextstep: FirstTsDay=", FirstTsDay," FirstTsMonth=",FirstTsMonth," FirstTsYear=", FirstTsYear
255       WRITE(numout,*) "time_nextstep: LastTsDay=", LastTsDay," LastTsMonth=",LastTsMonth," LastTsYear=", LastTsYear
256       WRITE(numout,*) "time_nextstep: julian0=",julian0, " julian_diff=",julian_diff
257       WRITE(numout,*) ""
258    END IF
259    IF ((printlev_loc >= 2) .AND. FirstTsDay) THEN
260       WRITE(numout,"(' Date: ', I4.4,'-',I2.2,'-',I2.2,' ',F8.4,'sec at timestep ',I12.4)") &
261            year_start, month_start, day_start, sec_start, kjit
262    END IF
263
264  END SUBROUTINE time_nextstep
265
266!!  =============================================================================================================================
267!! SUBROUTINE:    time_interval()
268!!
269!>\BRIEF          Computes the interval corresponging to the given time step.
270!!
271!! DESCRIPTION:   This subroutine will compute the interval of time for the given time step.
272!!                It will use the tstepint_type variable which was set at initilisation.
273!!
274!! \n
275!_ ==============================================================================================================================
276
277  SUBROUTINE time_interval(kjit, year_s, month_s, day_s, sec_s, &
278                                 year_e, month_e, day_e, sec_e)
279
280    !! 0.1 Input variables
281    INTEGER(i_std), INTENT(in)                  :: kjit      !! Current time step
282
283    !! 0.2 Output variables
284    INTEGER(i_std), INTENT(out)                 :: year_s, month_s, day_s
285    INTEGER(i_std), INTENT(out)                 :: year_e, month_e, day_e
286    REAL(r_std), INTENT(out)                    :: sec_s
287    REAL(r_std), INTENT(out)                    :: sec_e
288   
289
290    !! Calculate the interval for current time step
291    !! tstepint_type is used to know how the interval is defined around the time-stamp of the time-step
292    SELECT CASE (TRIM(tstepint_type))
293       CASE ("START ")
294          !! Calculate the start date of the interval
295          julian_start = itau2date(kjit, date0_save, dt_sechiba)
296          !! Calculate the end date of the interval using kjti+1
297          julian_end = itau2date(kjit+1, date0_save, dt_sechiba)
298       CASE("END")
299          !! Calculate the start date of the interval
300          julian_start = itau2date(kjit-1, date0_save, dt_sechiba)
301          !! Calculate the end date of the interval
302          julian_end = itau2date(kjit, date0_save, dt_sechiba)
303       CASE DEFAULT
304          WRITE(numout,*) "time_interval: tstepint_type = ", tstepint_type
305          CALL ipslerr_p(3,'time_interval', 'Unknown time iterval type.', &
306               'The time stamp given can have 3 position on the interval :',' START, CENTER or END')
307       END SELECT
308
309       !! Calculate year, month, day and sec for julian_start date
310       CALL ju2ymds (julian_start, year_s, month_s, day_s, sec_s)
311
312       !! Calculate year, month, day and sec for julian_end date
313       CALL ju2ymds (julian_end, year_e, month_e, day_e, sec_e)
314
315   
316  END SUBROUTINE time_interval
317
318END MODULE time
Note: See TracBrowser for help on using the repository browser.