Line data Source code
1 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
3 : !!!!
4 : !!!! MIT License
5 : !!!!
6 : !!!! ParaMonte: plain powerful parallel Monte Carlo library.
7 : !!!!
8 : !!!! Copyright (C) 2012-present, The Computational Data Science Lab
9 : !!!!
10 : !!!! This file is part of the ParaMonte library.
11 : !!!!
12 : !!!! Permission is hereby granted, free of charge, to any person obtaining a
13 : !!!! copy of this software and associated documentation files (the "Software"),
14 : !!!! to deal in the Software without restriction, including without limitation
15 : !!!! the rights to use, copy, modify, merge, publish, distribute, sublicense,
16 : !!!! and/or sell copies of the Software, and to permit persons to whom the
17 : !!!! Software is furnished to do so, subject to the following conditions:
18 : !!!!
19 : !!!! The above copyright notice and this permission notice shall be
20 : !!!! included in all copies or substantial portions of the Software.
21 : !!!!
22 : !!!! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
23 : !!!! EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
24 : !!!! MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
25 : !!!! IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM,
26 : !!!! DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR
27 : !!!! OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE
28 : !!!! OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
29 : !!!!
30 : !!!! ACKNOWLEDGMENT
31 : !!!!
32 : !!!! ParaMonte is an honor-ware and its currency is acknowledgment and citations.
33 : !!!! As per the ParaMonte library license agreement terms, if you use any parts of
34 : !!!! this library for any purposes, kindly acknowledge the use of ParaMonte in your
35 : !!!! work (education/research/industry/development/...) by citing the ParaMonte
36 : !!!! library as described on this page:
37 : !!!!
38 : !!!! https://github.com/cdslaborg/paramonte/blob/main/ACKNOWLEDGMENT.md
39 : !!!!
40 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
41 : !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
42 :
43 : !> \brief This module contains classes and procedures relevant to wall-time timing.
44 : !> \author Amir Shahmoradi
45 :
46 : module Timer_mod
47 :
48 : use, intrinsic :: iso_fortran_env, only: int64
49 : use Constants_mod, only: RK
50 : implicit none
51 :
52 : ! Doxygen does not comprehend the following statements. Therefore, these are commented out.
53 : !private
54 : !public :: MODULE_NAME, Timer_type
55 :
56 : character(*), parameter :: MODULE_NAME = "@Timer_mod"
57 :
58 : type :: Count_type
59 : integer(int64) :: start !< The first processor clock count.
60 : integer(int64) :: stop !< The last fetched processor clock count.
61 : integer(int64) :: total !< The total processor clock count since start.
62 : integer(int64) :: delta !< The total processor clock count since the last measurement.
63 : integer(int64) :: max !< The maximum value that the processor count may take, or zero if there is no clock.
64 : real(RK) :: rate !< The number of clock counts per second, or zero if there is no clock.
65 : end type Count_type
66 :
67 : type :: Time_type
68 : real(RK) :: start !< The start time in seconds.
69 : real(RK) :: stop !< The stop time in seconds.
70 : real(RK) :: total !< The total time in seconds since the start.
71 : real(RK) :: delta !< The total time in seconds since the last timing.
72 : character(7) :: unit = "seconds" !< The unit of time.
73 : end type Time_type
74 :
75 : !> The `Timer_type` class, containing method for setting up a wall-time timer.
76 : type :: Timer_type
77 : type(Count_type) :: Count !< An object of type [Count_type](@ref count_type) containing information about the processor clock count.
78 : type(Time_type) :: Time !< An object of type [Time_type](@ref time_type) containing information about the processor time.
79 : real(RK) :: period !< The time between the processor clock tics in seconds.
80 : contains
81 : procedure, pass :: tic => setTic
82 : procedure, pass :: toc => setToc
83 : procedure, pass :: delta => getTimeSinceLastCall
84 : procedure, pass :: total => getTimeSinceStart
85 : end type Timer_type
86 :
87 : interface Timer_type
88 : module procedure :: constructTimer
89 : end interface Timer_type
90 :
91 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
92 :
93 : contains
94 :
95 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
96 :
97 : !> \brief
98 : !> This is the constructor of the class [Timer_type](@ref timer_type).
99 : !> Before returning the object, this function also calls the [tic()](@ref settic)
100 : !> method of the `Timer_type` object to reset the timer.
101 : !>
102 : !> \param[out] Err : An object of class [Err_type](@ref err_mod::err_type) indicating
103 : !> the occurrence of error during the object construction.
104 : !>
105 : !> \return
106 : !> `Timer` : An object of class [Timer_type](@ref timer_type).
107 : !>
108 : !> \author
109 : !> Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
110 2202 : function constructTimer(Err) result(Timer)
111 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
112 : !DEC$ ATTRIBUTES DLLEXPORT :: constructTimer
113 : #endif
114 : use Constants_mod, only: RK
115 : use Err_mod, only: Err_type
116 : implicit none
117 : type(Err_type), intent(out) :: Err
118 : type(Timer_type) :: Timer
119 : character(*), parameter :: PROCEDURE_NAME = "@constructTimer()"
120 1155 : Err%occurred = .false.
121 1155 : Err%msg = ""
122 1155 : call system_clock( count=Timer%Count%start, count_rate=Timer%Count%rate, count_max=Timer%Count%max )
123 1155 : if ( Timer%Count%start==-huge(0) .or. Timer%Count%rate==0._RK .or. Timer%Count%max==0 ) then
124 : ! LCOV_EXCL_START
125 : Err%occurred = .true.
126 : Err%msg = PROCEDURE_NAME // ": Error occurred. There is no processor clock."
127 : return
128 : ! LCOV_EXCL_STOP
129 : end if
130 1155 : call Timer%tic()
131 1155 : end function constructTimer
132 :
133 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
134 :
135 : !> \brief
136 : !> This procedure is a method of the class [Timer_type](@ref timer_type).
137 : !> Reset the timer object and return.
138 : !>
139 : !> \param[inout] Timer : An object of class [Timer_type](@ref timer_type) whose components are manipulated by this method.
140 : !>
141 : !> \author
142 : !> Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
143 1842 : subroutine setTic(Timer)
144 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
145 : !DEC$ ATTRIBUTES DLLEXPORT :: setTic
146 : #endif
147 1155 : use Constants_mod, only: RK
148 : implicit none
149 : class(Timer_type), intent(inout) :: Timer
150 3684 : call system_clock( count=Timer%Count%start, count_rate=Timer%Count%rate, count_max=Timer%Count%max )
151 1842 : Timer%period = 1._RK / Timer%Count%rate
152 1842 : Timer%Count%stop = Timer%Count%start
153 1842 : Timer%Count%total = 0
154 1842 : Timer%Count%delta = 0
155 1842 : Timer%Time%start = real(Timer%Count%start,kind=RK) * Timer%period
156 1842 : Timer%Time%stop = Timer%Time%start
157 1842 : Timer%Time%total = 0._RK
158 1842 : Timer%Time%delta = 0._RK
159 1842 : end subroutine setTic
160 :
161 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
162 :
163 : !> \brief
164 : !> This procedure is a method of the class [Timer_type](@ref timer_type).
165 : !> Mark the timer and compute the time spent since last [toc()](@ref settoc) method call and return.
166 : !>
167 : !> \param[inout] Timer : An object of class [Timer_type](@ref timer_type) whose components are manipulated by this method.
168 : !>
169 : !> \remark
170 : !> Specifically, this method will set/update the following components of the object of type `Timer_type`:
171 : !> + `Timer%Count%delta` : The total counts since the last `toc()` call.
172 : !> + `Timer%Count%total` : The total counts since the object creation or since the last `tic()` call.
173 : !> + `Timer%Count%stop` : The current count as inferred from the Fortran intrinsic procedure `system_clock()`.
174 : !> + `Timer%Timer%delta` : The total time in seconds since the last `toc()` call.
175 : !> + `Timer%Timer%total` : The total time in seconds since the object creation or since the last `tic()` call.
176 : !> + `Timer%Timer%stop` : The current time in seconds as inferred from the Fortran intrinsic procedure `system_clock()`.
177 : !>
178 : !> \author
179 : !> Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
180 2374760 : subroutine setToc(Timer)
181 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
182 : !DEC$ ATTRIBUTES DLLEXPORT :: setToc
183 : #endif
184 : implicit none
185 : class(Timer_type), intent(inout) :: Timer
186 : integer(int64) :: stopCount
187 2374760 : real(RK) :: stopTime
188 4749510 : call system_clock( count=stopCount )
189 2374760 : Timer%Count%delta = stopCount - Timer%Count%stop
190 2374760 : Timer%Count%total = stopCount - Timer%Count%start
191 2374760 : Timer%Count%stop = stopCount
192 2374760 : stopTime = real(stopCount,kind=RK) * Timer%period
193 2374760 : Timer%Time%delta = stopTime - Timer%Time%stop
194 2374760 : Timer%Time%total = stopTime - Timer%Time%start
195 2374760 : Timer%Time%stop = stopTime
196 1842 : end subroutine setToc
197 :
198 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
199 :
200 : !> \brief
201 : !> This procedure is a method of the class [Timer_type](@ref timer_type).
202 : !> Report the time spent in seconds since the last timing.
203 : !>
204 : !> \param[inout] Timer : An object of class [Timer_type](@ref timer_type) whose components are manipulated by this method.
205 : !>
206 : !> \return
207 : !> `timeSinceLastCall` : The time spent in seconds since the last timing.
208 : !>
209 : !> \author
210 : !> Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
211 3 : function getTimeSinceLastCall(Timer) result(timeSinceLastCall)
212 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
213 : !DEC$ ATTRIBUTES DLLEXPORT :: getTimeSinceLastCall
214 : #endif
215 : implicit none
216 : class(Timer_type), intent(inout) :: Timer
217 : real(RK) :: timeSinceLastCall
218 3 : call Timer%toc()
219 3 : timeSinceLastCall = Timer%Time%delta
220 2374760 : end function getTimeSinceLastCall
221 :
222 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
223 :
224 : !> \brief
225 : !> This procedure is a method of the class [Timer_type](@ref timer_type).
226 : !> Report the time spent in seconds since the start of the timing.
227 : !>
228 : !> \param[inout] Timer : An object of class [Timer_type](@ref timer_type) whose components are manipulated by this method.
229 : !>
230 : !> \return
231 : !> `timeSinceStart` : The time spent in seconds since the start of the timing.
232 : !>
233 : !> \author
234 : !> Amir Shahmoradi, Sep 1, 2017, 12:00 AM, ICES, UT Austin
235 3 : function getTimeSinceStart(Timer) result(timeSinceStart)
236 : #if INTEL_COMPILER_ENABLED && defined DLL_ENABLED && (OS_IS_WINDOWS || defined OS_IS_DARWIN)
237 : !DEC$ ATTRIBUTES DLLEXPORT :: getTimeSinceStart
238 : #endif
239 : implicit none
240 : class(Timer_type), intent(inout) :: Timer
241 : real(RK) :: timeSinceStart
242 3 : call Timer%toc()
243 3 : timeSinceStart = Timer%Time%delta
244 6 : end function getTimeSinceStart
245 :
246 : !%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
247 :
248 : end module Timer_mod ! LCOV_EXCL_LINE
|