@@ -180,6 +180,15 @@ newtype NanoSecond64 = NanoSecond64 Int64
180180 , Unbox
181181 )
182182
183+ -- XXX timed
184+
185+ timed :: IO a -> IO (NanoSecond64 , a )
186+ timed = undefined
187+
188+ -- ghcStats :: IO a -> IO (GHCStats, a)
189+ -- measuredBy :: Diff s => IO s -> IO a -> IO (s, a)
190+ -- timed = measuredBy (getTime Monotonic)
191+
183192-- | An 'Int64' time representation with a microsecond resolution.
184193-- It can represent time up to ~292,000 years.
185194newtype MicroSecond64 = MicroSecond64 Int64
@@ -272,6 +281,8 @@ instance TimeUnit TimeSpec where
272281 toTimeSpec = id
273282 fromTimeSpec = id
274283
284+ -- XXX Remove 64 suffix, regular units should be considered 64 bit.
285+
275286instance TimeUnit NanoSecond64 where
276287 {-# INLINE toTimeSpec #-}
277288 toTimeSpec (NanoSecond64 t) = TimeSpec s ns
@@ -364,6 +375,34 @@ fromAbsTime (AbsTime t) = fromTimeSpec t
364375-- Relative time using NaonoSecond64 as the underlying representation
365376-------------------------------------------------------------------------------
366377
378+ -- XXX Use NanoSecond etc. instead of RelTime. They already denote relative
379+ -- time. Maybe its a good idea to keep RelTime as a wrapper around time units
380+ -- so that we can switch the underlying representation any time. we can use
381+ -- Double or Int64 or Fixed or TimeSpec.
382+ --
383+ -- Can we design it such that we can switch to Double as the underlying
384+ -- representation any time if we want? We can just switch the module to switch
385+ -- the impl.
386+ --
387+ -- We can use AbsTime and RelTime as generic types so that we have the ability
388+ -- to switch the underlying repr.
389+ --
390+ -- Use "Time" for AbsTime relative to Posix epoch, basically the system
391+ -- time. For Time, use a 64-bit value or 64+64? A fixed epoch + relative time.
392+ -- For relative times in a stream we can use rollingMap (-). As long as the
393+ -- epoch is fixed we only need to diff the reltime which should be efficient.
394+ --
395+ -- We can do the same to paths as well. As long as the root is fixed we can
396+ -- diff only the relative components.
397+ --
398+ -- Also type Time = PosixTime
399+ -- newtype PosixTime = AbsTime Posix days ns
400+ -- newtype UTCTime = AbsTime UTC days ns
401+ -- newtype RelTime = AbsTime Rel days ns
402+ --
403+ -- The max value of ns won't be limited to 10^9 so we can keep the epoch fixed
404+ -- and only manipulate ns.
405+ --
367406-- We use a separate type to represent relative time for safety and speed.
368407-- RelTime has a Num instance, absolute time doesn't. Relative times are
369408-- usually shorter and for our purposes an Int64 nanoseconds can hold close to
@@ -443,10 +482,12 @@ fromRelTime (RelTime t) = fromTimeSpec t
443482{-# RULES "toRelTime/fromRelTime" forall a. fromRelTime (toRelTime a) = a #-}
444483
445484-- XXX rename to diffAbsTimes?
485+ -- SemigroupR?
446486{-# INLINE diffAbsTime #-}
447487diffAbsTime :: AbsTime -> AbsTime -> RelTime
448488diffAbsTime (AbsTime t1) (AbsTime t2) = RelTime (t1 - t2)
449489
490+ -- SemigroupR?
450491{-# INLINE addToAbsTime #-}
451492addToAbsTime :: AbsTime -> RelTime -> AbsTime
452493addToAbsTime (AbsTime t1) (RelTime t2) = AbsTime $ t1 + t2
@@ -482,6 +523,12 @@ showNanoSecond64 time@(NanoSecond64 ns)
482523 | t >= 1e1 = printf " %.2f %s" t u
483524 | otherwise = printf " %.3f %s" t u
484525
526+ -- The unit Second may be implicit. We can then use modifiers to convert it
527+ -- e.g. Nano 1 for 1 nanosec, Micro 1 for 1 microsec. These can work in general
528+ -- for any unit.
529+ --
530+ -- We can also use Minute x for 60x, and Hour x for 3600x etc.
531+ --
485532-- In general we should be able to show the time in a specified unit, if we
486533-- omit the unit we can show it in an automatically chosen one.
487534{-
0 commit comments