Skip to content

Commit d269717

Browse files
Update docs/refactor for time modules
1 parent d78fa87 commit d269717

File tree

3 files changed

+126
-33
lines changed

3 files changed

+126
-33
lines changed

core/src/Streamly/Internal/Data/Time/TimeSpec.hsc

Lines changed: 33 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -1,30 +1,33 @@
1-
{-# LANGUAGE CPP #-}
2-
{-# LANGUAGE ScopedTypeVariables #-}
3-
41
{-# OPTIONS_GHC -Wno-identities #-}
52

6-
#ifndef __GHCJS__
7-
#include "config.h"
8-
#endif
9-
10-
#include "Streamly/Internal/Data/Time/Clock/config-clock.h"
11-
12-
#include "MachDeps.h"
13-
143
-- |
154
-- Module : Streamly.Internal.Data.Time.TimeSpec
165
-- Copyright : (c) 2019 Composewell Technologies
176
-- License : BSD3
187
-- Maintainer : [email protected]
198
-- Stability : experimental
209
-- Portability : GHC
10+
--
11+
-- 'TimeSpec' can store upto a duration of ~292 billion years at nanosecond
12+
-- precision. An 'Int64' data type is much faster to manipulate but has a
13+
-- smaller maximum limit (~292 years) at nanosecond precision. An 'Integer'
14+
-- type can possibly be used for unbounded fixed precision time. 'Double' can
15+
-- be used for floating precision time.
2116

2217
module Streamly.Internal.Data.Time.TimeSpec
2318
(
2419
TimeSpec(..)
2520
)
2621
where
2722

23+
#ifndef __GHCJS__
24+
#include "config.h"
25+
#endif
26+
27+
#include "Streamly/Internal/Data/Time/config-clock.h"
28+
29+
#include "MachDeps.h"
30+
2831
import Data.Int (Int64)
2932
#if (WORD_SIZE_IN_BITS == 32)
3033
import Data.Int (Int32)
@@ -44,20 +47,27 @@ tenPower9 :: Int64
4447
tenPower9 = 1000000000
4548

4649
-------------------------------------------------------------------------------
47-
-- TimeSpec representation
50+
-- TimeSpec
4851
-------------------------------------------------------------------------------
4952

50-
-- A structure storing seconds and nanoseconds as 'Int64' is the simplest and
51-
-- fastest way to store practically large quantities of time with efficient
52-
-- arithmetic operations. If we store nanoseconds using 'Integer' it can store
53-
-- practically unbounded quantities but it may not be as efficient to
54-
-- manipulate in performance critical applications. XXX need to measure the
55-
-- performance.
53+
-- XXX Should we use "SystemTime" from the "time" package instead?
54+
--
55+
-- | 'TimeSpec' can hold up to ~292 billion years at nanosecond precision.
56+
--
57+
-- In addition to using the 'TimeSpec' constructor you can also use
58+
-- 'fromInteger' from the 'Num' type class to create a 'TimeSpec' from
59+
-- nanoseconds. Like any 'Num', 'TimeSpec' can be negative.
60+
--
61+
-- Note, we assume that 'nsec' is always less than 10^9. Also, when 'TimeSpec'
62+
-- is negative then both 'sec' and 'nsec' must be negative.
63+
-- TODO: Use smart constructors to enforce the assumptions.
64+
--
65+
-- Use 'Eq' and 'Ord' instances for comparisons and the 'Num' instance to
66+
-- perform arithmetic operations on 'TimeSpec'.
5667
--
57-
-- | Data type to represent practically large quantities of time efficiently.
58-
-- It can represent time up to ~292 billion years at nanosecond resolution.
5968
data TimeSpec = TimeSpec
6069
{ sec :: {-# UNPACK #-} !Int64 -- ^ seconds
70+
-- XXX this could be Int32 instead
6171
, nsec :: {-# UNPACK #-} !Int64 -- ^ nanoseconds
6272
} deriving (Eq, Read, Show)
6373

@@ -91,11 +101,12 @@ adjustSign t@(TimeSpec s ns)
91101
timeSpecToInteger :: TimeSpec -> Integer
92102
timeSpecToInteger (TimeSpec s ns) = toInteger $ s * tenPower9 + ns
93103

104+
-- | Note that the arithmetic operations may overflow silently.
94105
instance Num TimeSpec where
95106
{-# INLINE (+) #-}
96107
t1 + t2 = adjustSign (addWithOverflow t1 t2)
97108

98-
-- XXX will this be more optimal if imlemented without "negate"?
109+
-- XXX will this be more optimal if implemented without "negate"?
99110
{-# INLINE (-) #-}
100111
t1 - t2 = t1 + negate t2
101112
t1 * t2 = fromInteger $ timeSpecToInteger t1 * timeSpecToInteger t2
@@ -107,7 +118,7 @@ instance Num TimeSpec where
107118
{-# INLINE signum #-}
108119
signum (TimeSpec s ns) | s == 0 = TimeSpec (signum ns) 0
109120
| otherwise = TimeSpec (signum s) 0
110-
-- This is fromNanoSecond64 Integer
121+
-- | Convert 'Integer' nanoseconds to 'TimeSpec'.
111122
{-# INLINE fromInteger #-}
112123
fromInteger nanosec = TimeSpec (fromInteger s) (fromInteger ns)
113124
where (s, ns) = nanosec `divMod` toInteger tenPower9

core/src/Streamly/Internal/Data/Time/Units.hs

Lines changed: 88 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -4,11 +4,80 @@
44
-- |
55
-- Module : Streamly.Internal.Data.Time.Units
66
-- Copyright : (c) 2019 Composewell Technologies
7-
--
8-
-- License : BSD3
7+
-- License : BSD-3-Clause
98
-- Maintainer : [email protected]
109
-- Stability : pre-release
1110
-- Portability : GHC
11+
--
12+
-- Fast time manipulation.
13+
--
14+
-- = Representing Time
15+
--
16+
-- Numbers along with an associated unit (e.g. 'MilliSecond64') are used to
17+
-- represent durations and points in time. Durations are relative but points
18+
-- are absolute and defined with respect to some fixed or well known point in
19+
-- time e.g. the Unix epoch (01-Jan-1970). Absolute and relative times are
20+
-- numbers that can be represented and manipulated like 'Num'.
21+
--
22+
-- = Fixed Precision 64-bit Units
23+
--
24+
-- * 'NanoSecond64': 292 years at nanosecond precision.
25+
-- * 'MicroSecond64': 292K years at nanosecond precision.
26+
-- * 'MilliSecond64': 292M years at nanosecond precision.
27+
--
28+
-- These units are 'Integral' 'Num' types. We can use 'fromIntegral' to convert
29+
-- any integral type to/from these types.
30+
--
31+
-- = TimeSpec
32+
--
33+
-- * 'TimeSpec': 292G years at nanosecond precision
34+
--
35+
-- = RelTime64
36+
--
37+
-- Relative time, not relative to any specific epoch. Represented using
38+
-- 'NanoSecond64'. 'fromRelTime64' and 'toRelTime64' can be used to convert a
39+
-- time unit to/from RelTime. Note that a larger unit e.g. 'MicroSecond64' may
40+
-- get truncated if it is larger than 292 years. RelTime64 is also generated by
41+
-- diffing two AbsTime.
42+
--
43+
-- RelTime is a 'Num', we can do number arithmetic on RelTime, and use
44+
-- 'fromInteger' to convert an 'Integer' nanoseconds to 'RelTime'.
45+
--
46+
-- = AbsTime
47+
--
48+
-- Time measured relative to the POSIX epoch i.e. 01-Jan-1970. Represented
49+
-- using 'TimeSpec'. 'fromAbsTime' and 'toAbsTime' can be used to convert a
50+
-- time unit to/from AbsTime.
51+
--
52+
-- AbsTime is not a 'Num'. We can use 'diffAbsTime' to diff abstimes to get
53+
-- a 'RelTime'. We can add RelTime to AbsTime to get another AbsTime.
54+
--
55+
-- = TimeSpec vs 64-bit Units
56+
--
57+
-- TimeSpec can represent up to 292 billion years of time at nanosecond
58+
-- precision while 64-bit units can represent only 292 years at the same
59+
-- precision. However, 64-bit units are much faster to manipulate. In high
60+
-- performance code it is recommended to use the 64-bit units if possible.
61+
--
62+
-- = Working with the "time" package
63+
--
64+
-- AbsTime is essentially the same as 'SystemTime' from the time package. We
65+
-- can use 'SystemTime' to interconvert between time package and this module.
66+
--
67+
-- = Alternative Representations
68+
--
69+
-- Double or Fixed would be a much better representation so that we do not lose
70+
-- information between conversions. However, for faster arithmetic operations
71+
-- we use an 'Int64' here. When we need convservation of values we can use a
72+
-- different system of units with a Fixed precision.
73+
--
74+
-- = TODO
75+
--
76+
-- Split the Timespec/TimeUnit in a separate module?
77+
-- Keep *64/TimeUnit64 in this module, remove the 64 suffix because these are
78+
-- common units.
79+
-- Rename TimeUnit to IsTimeSpec, TimeUnit64 to IsTimeUnit.
80+
--
1281

1382
module Streamly.Internal.Data.Time.Units
1483
(
@@ -85,11 +154,6 @@ tenPower9 = 1000000000
85154
-- NanoSecond Int64
86155
-- ...
87156

88-
-- Double or Fixed would be a much better representation so that we do not lose
89-
-- information between conversions. However, for faster arithmetic operations
90-
-- we use an 'Int64' here. When we need convservation of values we can use a
91-
-- different system of units with a Fixed precision.
92-
93157
-------------------------------------------------------------------------------
94158
-- Integral Units
95159
-------------------------------------------------------------------------------
@@ -151,19 +215,21 @@ newtype MilliSecond64 = MilliSecond64 Int64
151215
-- performance boost. If not then we can just use Integer nanoseconds and get
152216
-- rid of TimeUnitWide.
153217
--
218+
{-
154219
-- | A type class for converting between time units using 'Integer' as the
155220
-- intermediate and the widest representation with a nanosecond resolution.
156221
-- This system of units can represent arbitrarily large times but provides
157222
-- least efficient arithmetic operations due to 'Integer' arithmetic.
158223
--
159224
-- NOTE: Converting to and from units may truncate the value depending on the
160225
-- original value and the size and resolution of the destination unit.
161-
{-
162226
class TimeUnitWide a where
163227
toTimeInteger :: a -> Integer
164228
fromTimeInteger :: Integer -> a
165229
-}
166230

231+
-- XXX Rename to IsTimeUnit?
232+
--
167233
-- | A type class for converting between units of time using 'TimeSpec' as the
168234
-- intermediate representation. This system of units can represent up to ~292
169235
-- billion years at nanosecond resolution with reasonably efficient arithmetic
@@ -253,18 +319,27 @@ instance TimeUnit64 MilliSecond64 where
253319
-- Absolute time
254320
-------------------------------------------------------------------------------
255321

322+
-- Have a Fixed64 type with an Int64 as underlying type
323+
-- XXX Use AbsTime64 for faster arithmetic on AbsTimes?
324+
--
325+
-- data Epoch = Posix | UTC | Rel
326+
--
327+
-- XXX data Time epoch = Time TimeSpec
328+
--
256329
-- | Absolute times are relative to a predefined epoch in time. 'AbsTime'
257330
-- represents times using 'TimeSpec' which can represent times up to ~292
258331
-- billion years at a nanosecond resolution.
259332
newtype AbsTime = AbsTime TimeSpec
260333
deriving (Eq, Ord, Show)
261334

262-
-- | Convert a 'TimeUnit' to an absolute time.
335+
-- | Convert a 'TimeUnit' representing relative time from the Unix epoch to an
336+
-- absolute time.
263337
{-# INLINE_NORMAL toAbsTime #-}
264338
toAbsTime :: TimeUnit a => a -> AbsTime
265339
toAbsTime = AbsTime . toTimeSpec
266340

267-
-- | Convert absolute time to a 'TimeUnit'.
341+
-- | Convert absolute time to a relative 'TimeUnit' representing time relative
342+
-- to the Unix epoch.
268343
{-# INLINE_NORMAL fromAbsTime #-}
269344
fromAbsTime :: TimeUnit a => AbsTime -> a
270345
fromAbsTime (AbsTime t) = fromTimeSpec t
@@ -285,8 +360,10 @@ fromAbsTime (AbsTime t) = fromTimeSpec t
285360
-- usually shorter and for our purposes an Int64 nanoseconds can hold close to
286361
-- thousand year duration. It is also faster to manipulate. We do not check for
287362
-- overflows during manipulations so use it only when you know the time cannot
288-
-- be too big. If you need a bigger RelTime representation then use RelTimeBig.
363+
-- be too big. If you need a bigger RelTime representation then use RelTime.
289364

365+
-- This is the same as the DiffTime in time package.
366+
--
290367
-- | Relative times are relative to some arbitrary point of time. Unlike
291368
-- 'AbsTime' they are not relative to a predefined epoch.
292369
newtype RelTime64 = RelTime64 NanoSecond64

src/Streamly/Internal/Data/Stream/IsStream/Transform.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1433,6 +1433,11 @@ indexedR n = fromStreamD . D.indexedR n . toStreamD
14331433
-- Time Indexing
14341434
-------------------------------------------------------------------------------
14351435

1436+
-- XXX Use the timestamp as (AbsTime, RelTime, a). AbsTime is the time when we
1437+
-- started evaluating the stream and RelTime is the time relative to that.
1438+
-- When we use only RelTime, AbsTime would be discarded by the compiler so it
1439+
-- should not pose any overhead. Have some benchmarks to prove that.
1440+
14361441
-- Note: The timestamp stream must be the second stream in the zip so that the
14371442
-- timestamp is generated after generating the stream element and not before.
14381443
-- If we do not do that then the following example will generate the same

0 commit comments

Comments
 (0)