Skip to content

Commit dc324b2

Browse files
time checkpoint
1 parent 89f2908 commit dc324b2

File tree

1 file changed

+47
-0
lines changed
  • core/src/Streamly/Internal/Data/Time

1 file changed

+47
-0
lines changed

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

Lines changed: 47 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -172,6 +172,15 @@ newtype NanoSecond64 = NanoSecond64 Int64
172172
, Unbox
173173
)
174174

175+
-- XXX timed
176+
177+
timed :: IO a -> IO (NanoSecond64, a)
178+
timed = undefined
179+
180+
-- ghcStats :: IO a -> IO (GHCStats, a)
181+
-- measuredBy :: Diff s => IO s -> IO a -> IO (s, a)
182+
-- timed = measuredBy (getTime Monotonic)
183+
175184
-- | An 'Int64' time representation with a microsecond resolution.
176185
-- It can represent time up to ~292,000 years.
177186
newtype MicroSecond64 = MicroSecond64 Int64
@@ -264,6 +273,8 @@ instance TimeUnit TimeSpec where
264273
toTimeSpec = id
265274
fromTimeSpec = id
266275

276+
-- XXX Remove 64 suffix, regular units should be considered 64 bit.
277+
267278
instance TimeUnit NanoSecond64 where
268279
{-# INLINE toTimeSpec #-}
269280
toTimeSpec (NanoSecond64 t) = TimeSpec s ns
@@ -356,6 +367,34 @@ fromAbsTime (AbsTime t) = fromTimeSpec t
356367
-- Relative time using NaonoSecond64 as the underlying representation
357368
-------------------------------------------------------------------------------
358369

370+
-- XXX Use NanoSecond etc. instead of RelTime. They already denote relative
371+
-- time. Maybe its a good idea to keep RelTime as a wrapper around time units
372+
-- so that we can switch the underlying representation any time. we can use
373+
-- Double or Int64 or Fixed or TimeSpec.
374+
--
375+
-- Can we design it such that we can switch to Double as the underlying
376+
-- representation any time if we want? We can just switch the module to switch
377+
-- the impl.
378+
--
379+
-- We can use AbsTime and RelTime as generic types so that we have the ability
380+
-- to switch the underlying repr.
381+
--
382+
-- Use "Time" for AbsTime relative to Posix epoch, basically the system
383+
-- time. For Time, use a 64-bit value or 64+64? A fixed epoch + relative time.
384+
-- For relative times in a stream we can use rollingMap (-). As long as the
385+
-- epoch is fixed we only need to diff the reltime which should be efficient.
386+
--
387+
-- We can do the same to paths as well. As long as the root is fixed we can
388+
-- diff only the relative components.
389+
--
390+
-- Also type Time = PosixTime
391+
-- newtype PosixTime = AbsTime Posix days ns
392+
-- newtype UTCTime = AbsTime UTC days ns
393+
-- newtype RelTime = AbsTime Rel days ns
394+
--
395+
-- The max value of ns won't be limited to 10^9 so we can keep the epoch fixed
396+
-- and only manipulate ns.
397+
--
359398
-- We use a separate type to represent relative time for safety and speed.
360399
-- RelTime has a Num instance, absolute time doesn't. Relative times are
361400
-- usually shorter and for our purposes an Int64 nanoseconds can hold close to
@@ -435,10 +474,12 @@ fromRelTime (RelTime t) = fromTimeSpec t
435474
{-# RULES "toRelTime/fromRelTime" forall a. fromRelTime (toRelTime a) = a #-}
436475

437476
-- XXX rename to diffAbsTimes?
477+
-- SemigroupR?
438478
{-# INLINE diffAbsTime #-}
439479
diffAbsTime :: AbsTime -> AbsTime -> RelTime
440480
diffAbsTime (AbsTime t1) (AbsTime t2) = RelTime (t1 - t2)
441481

482+
-- SemigroupR?
442483
{-# INLINE addToAbsTime #-}
443484
addToAbsTime :: AbsTime -> RelTime -> AbsTime
444485
addToAbsTime (AbsTime t1) (RelTime t2) = AbsTime $ t1 + t2
@@ -474,6 +515,12 @@ showNanoSecond64 time@(NanoSecond64 ns)
474515
| t >= 1e1 = printf "%.2f %s" t u
475516
| otherwise = printf "%.3f %s" t u
476517

518+
-- The unit Second may be implicit. We can then use modifiers to convert it
519+
-- e.g. Nano 1 for 1 nanosec, Micro 1 for 1 microsec. These can work in general
520+
-- for any unit.
521+
--
522+
-- We can also use Minute x for 60x, and Hour x for 3600x etc.
523+
--
477524
-- In general we should be able to show the time in a specified unit, if we
478525
-- omit the unit we can show it in an automatically chosen one.
479526
{-

0 commit comments

Comments
 (0)