5.13.2-dev0
mHM
The mesoscale Hydrological Model
Loading...
Searching...
No Matches
mo_common_datetime_type.f90
Go to the documentation of this file.
1!> \file mo_common_datetime_type.f90
2!> \brief \copybrief mo_common_datetime_type
3!> \details \copydetails mo_common_datetime_type
4
5!> \brief type for date time information with an increment subroutine
6!> \details Contains a current day, month, year, hour matching newTime, aswell as
7!! previous day, month, year. Theses all get updated on increment
8!! also contains nTimestep, and tIndex_out for writing
9!! finally, contains iLAI and yId that are time dependent and updating routines
10!! for these, and a function returning a boolean for writeout, dependent on the
11!! timestep_model_input
12!> \author Maren Kaluza
13!> \date March 2019
14!> \copyright Copyright 2005-\today, the mHM Developers, Luis Samaniego, Sabine Attinger: All rights reserved.
15!! mHM is released under the LGPLv3+ license \license_note
16!> \ingroup f_common
18 use mo_kind, only : i4, dp
19
20 ! Written Maren Kaluza, March 2019
21
22 IMPLICIT NONE
23
24 public :: datetimeinfo
25
26 private
27
29 !> number of timesteps in simulation period
30 integer(i4) :: ntimesteps
31 !> starts with simPer(iDomain)%julStart, then increments with
32 !> julday(...)
33 real(dp) :: newtime
34
35 !> current day
36 integer(i4) :: day
37 !> current month
38 integer(i4) :: month
39 !> current year
40 integer(i4) :: year
41 ! hour is only local, only used for calculating other output
42 integer(i4) :: hour
43
44 ! prev_day, prev_month, prev_year also are only used to store data to
45 ! calculate is_new_day/month/year. These are only used locally
46 integer(i4), private :: prev_day
47 integer(i4), private :: prev_month
48 integer(i4), private :: prev_year
49
50 ! flags for stepping into new period
51 logical :: is_new_day
52 logical :: is_new_month
53 logical :: is_new_year
54
55 integer(i4) :: ilai
56 integer(i4) :: yid
57
58 ! for writing netcdf file
59 integer(i4) :: tindex_out
60
61 contains
62 procedure :: init => datetimeinfo_init
63 procedure :: increment => datetimeinfo_increment
64 procedure :: update_lai_timestep => datetimeinfo_update_lai_timestep
65 ! function, returns boolean dependent on tIndex_out and is_new_{period}
66 procedure :: writeout => datetimeinfo_writeout
67 end type datetimeinfo
68
69 contains
70
71 subroutine datetimeinfo_init(this, iDomain)
73 use mo_julian, only : caldat
74 class(datetimeinfo), intent(inout) :: this
75 integer(i4), intent(in) :: iDomain
76
77 ! calculate NtimeSteps for this basin
78 this%nTimeSteps = (simper(idomain)%julEnd - simper(idomain)%julStart + 1) * ntstepday
79
80 ! reinitialize time counter for LCover and MPR
81 ! -0.5 is due to the fact that dec2date routine
82 ! changes the day at 12:00 in NOON
83 ! Whereas mHM needs day change at 00:00 h
84 ! initialize the julian day as real
85 this%newTime = real(simper(idomain)%julStart, dp)
86 ! initialize the date
87 call caldat(int(this%newTime), yy = this%year, mm = this%month, dd = this%day)
88 ! initialize flags for period changes, they are true for first time step
89 this%is_new_day = .true.
90 this%is_new_month = .true.
91 this%is_new_year = .true.
92
93 ! initialize arrays and counters
94 this%yId = lcyearid(this%year, idomain)
95 this%hour = 0
96 this%iLAI = 0
97
98 ! this has no relevance yet. it is only so the variables are initialized
99 this%prev_day = this%day
100 this%prev_month = this%month
101 this%prev_year = this%year
102
103 this%tIndex_out = 0 ! tt if write out of warming period
104 end subroutine datetimeinfo_init
105
106 subroutine datetimeinfo_increment(this)
107 use mo_julian, only : caldat, julday
109 class(datetimeinfo), intent(inout) :: this
110
111 ! prepare the date and time information for next iteration step...
112 ! set the current year as previous
113 this%prev_day = this%day
114 this%prev_month = this%month
115 this%prev_year = this%year
116 ! set the flags to false
117 this%is_new_day = .false.
118 this%is_new_month = .false.
119 this%is_new_year = .false.
120
121 ! increment of timestep
122 this%hour = this%hour + timestep
123 this%newTime = julday(this%day, this%month, this%year) + real(this%hour, dp) / 24._dp
124 ! get correct hour for current day
125 this%hour = mod(this%hour, 24)
126
127 ! calculate new year, month and day
128 call caldat(int(this%newTime), yy = this%year, mm = this%month, dd = this%day)
129 ! update the flags
130 if (this%prev_day /= this%day) this%is_new_day = .true.
131 if (this%prev_month /= this%month) this%is_new_month = .true.
132 if (this%prev_year /= this%year) this%is_new_year = .true.
133 end subroutine datetimeinfo_increment
134
137 class(datetimeinfo), intent(inout) :: this
138
139 select case (timestep_lai_input)
140 case(0 : 1) ! long term mean monthly gridded fields or LUT-based values
141 this%iLAI = this%month
142 case(-1) ! daily timestep
143 if (this%is_new_day) then
144 this%iLAI = this%iLAI + 1
145 end if
146 case(-2) ! monthly timestep
147 if (this%is_new_month) then
148 this%iLAI = this%iLAI + 1
149 end if
150 case(-3) ! yearly timestep
151 if (this%is_new_year) then
152 this%iLAI = this%iLAI + 1
153 end if
154 end select
156
157 function datetimeinfo_writeout(this, timeStep_model_outputs, tt) result(writeout)
158 class(datetimeinfo), intent(in) :: this
159 integer(i4), intent(in) :: timestep_model_outputs
160 integer(i4), intent(in) :: tt
161
162 logical :: writeout
163
164 writeout = .false.
165 if (timestep_model_outputs > 0) then
166 if ((mod(this%tIndex_out, timestep_model_outputs) == 0) &
167 .or. (tt == this%nTimeSteps)) writeout = .true.
168 else
169 select case(timestep_model_outputs)
170 case(0) ! only at last time step
171 if (tt == this%nTimeSteps) writeout = .true.
172 case(-1) ! daily
173 if (((this%tIndex_out > 0) .and. this%is_new_day) .or. &
174 (tt == this%nTimeSteps)) writeout = .true.
175 case(-2) ! monthly
176 if (((this%tIndex_out > 0) .and. this%is_new_month) .or.&
177 (tt == this%nTimeSteps)) writeout = .true.
178 case(-3) ! yearly
179 if (((this%tIndex_out > 0) .and. this%is_new_year) .or. &
180 (tt == this%nTimeSteps)) writeout = .true.
181 case default ! no output at all
182
183 end select
184 end if
185
186 end function datetimeinfo_writeout
187
type for date time information with an increment subroutine
logical function datetimeinfo_writeout(this, timestep_model_outputs, tt)
subroutine datetimeinfo_init(this, idomain)
subroutine datetimeinfo_update_lai_timestep(this)
Provides structures needed by mHM, mRM and/or mpr.
integer(i4), dimension(:, :), allocatable, public lcyearid
type(period), dimension(:), allocatable, public simper
Global variables for mpr only.
integer(i4), public timestep_lai_input