{-# LANGUAGE CPP #-}
module Foundation.Timing
( Timing(..)
, Measure(..)
, stopWatch
, measure
) where
import Basement.Imports hiding (from)
import Basement.From (from)
#if __GLASGOW_HASKELL__ < 802
import Basement.Cast (cast)
#endif
import Basement.Monad
import Basement.UArray.Mutable (MUArray)
import Foundation.Collection
import Foundation.Time.Types
import Foundation.Numerical
import Foundation.Time.Bindings
import Control.Exception (evaluate)
import System.Mem (performGC)
import Data.Function (on)
import qualified GHC.Stats as GHC
data Timing = Timing
{ Timing -> NanoSeconds
timeDiff :: !NanoSeconds
, Timing -> Maybe Word64
timeBytesAllocated :: !(Maybe Word64)
}
data Measure = Measure
{ Measure -> UArray NanoSeconds
measurements :: UArray NanoSeconds
, Measure -> Word
iters :: Word
}
#if __GLASGOW_HASKELL__ >= 802
type GCStats = GHC.RTSStats
getGCStats :: IO (Maybe GCStats)
getGCStats :: IO (Maybe GCStats)
getGCStats = do
r <- IO Bool
GHC.getRTSStatsEnabled
if r then pure Nothing else Just <$> GHC.getRTSStats
diffGC :: Maybe GHC.RTSStats -> Maybe GHC.RTSStats -> Maybe Word64
diffGC :: Maybe GCStats -> Maybe GCStats -> Maybe Word64
diffGC Maybe GCStats
gc2 Maybe GCStats
gc1 = ((-) (Word64 -> Word64 -> Word64)
-> (GCStats -> Word64) -> GCStats -> GCStats -> Word64
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` GCStats -> Word64
GHC.allocated_bytes) (GCStats -> GCStats -> Word64)
-> Maybe GCStats -> Maybe (GCStats -> Word64)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe GCStats
gc2 Maybe (GCStats -> Word64) -> Maybe GCStats -> Maybe Word64
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe GCStats
gc1
#else
type GCStats = GHC.GCStats
getGCStats :: IO (Maybe GCStats)
getGCStats = do
r <- GHC.getGCStatsEnabled
if r then pure Nothing else Just <$> GHC.getGCStats
diffGC :: Maybe GHC.GCStats -> Maybe GHC.GCStats -> Maybe Word64
diffGC gc2 gc1 = cast <$> (((-) `on` GHC.bytesAllocated) <$> gc2 <*> gc1)
#endif
stopWatch :: (a -> b) -> a -> IO Timing
stopWatch :: forall a b. (a -> b) -> a -> IO Timing
stopWatch a -> b
f !a
a = do
IO ()
performGC
gc1 <- IO (Maybe GCStats)
getGCStats
(_, ns) <- measuringNanoSeconds (evaluate $ f a)
gc2 <- getGCStats
return $ Timing ns (diffGC gc2 gc1)
measure :: Word -> (a -> b) -> a -> IO Measure
measure :: forall a b. Word -> (a -> b) -> a -> IO Measure
measure Word
nbIters a -> b
f a
a = do
d <- CountOf (MutableValue (MUArray NanoSeconds))
-> IO (MUArray NanoSeconds (PrimState IO))
forall (prim :: * -> *).
PrimMonad prim =>
CountOf (MutableValue (MUArray NanoSeconds))
-> prim (MUArray NanoSeconds (PrimState prim))
forall (c :: * -> *) (prim :: * -> *).
(MutableCollection c, PrimMonad prim) =>
CountOf (MutableValue c) -> prim (c (PrimState prim))
mutNew (Word -> CountOf NanoSeconds
forall a b. From a b => a -> b
from Word
nbIters) :: IO (MUArray NanoSeconds (PrimState IO))
loop d 0
Measure <$> unsafeFreeze d
<*> pure nbIters
where
loop :: MUArray NanoSeconds RealWorld -> Word -> IO ()
loop MUArray NanoSeconds RealWorld
d !Word
i
| Word
i Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Word
nbIters = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
(_, r) <- IO b -> IO (b, NanoSeconds)
forall a. IO a -> IO (a, NanoSeconds)
measuringNanoSeconds (b -> IO b
forall a. a -> IO a
evaluate (b -> IO b) -> b -> IO b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
a)
mutUnsafeWrite d (from i) r
loop d (i+1)