-- |
-- Module      : Foundation.Timing
-- License     : BSD-style
-- Maintainer  : Foundation maintainers
--
-- An implementation of a timing framework
--
{-# 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 hiding (unsafeFreeze)
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
    Bool
r <- IO Bool
GHC.getRTSStatsEnabled
    if Bool
r then forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO GCStats
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 = ((-) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` GCStats -> Word64
GHC.allocated_bytes) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe GCStats
gc2 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

-- | Simple one-time measurement of time & other metrics spent in a function
stopWatch :: (a -> b) -> a -> IO Timing
stopWatch :: forall a b. (a -> b) -> a -> IO Timing
stopWatch a -> b
f !a
a = do
    IO ()
performGC
    Maybe GCStats
gc1 <- IO (Maybe GCStats)
getGCStats
    (b
_, NanoSeconds
ns) <- forall a. IO a -> IO (a, NanoSeconds)
measuringNanoSeconds (forall a. a -> IO a
evaluate forall a b. (a -> b) -> a -> b
$ a -> b
f a
a)
    Maybe GCStats
gc2 <- IO (Maybe GCStats)
getGCStats
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ NanoSeconds -> Maybe Word64 -> Timing
Timing NanoSeconds
ns (Maybe GCStats -> Maybe GCStats -> Maybe Word64
diffGC Maybe GCStats
gc2 Maybe GCStats
gc1)

-- | In depth timing & other metrics analysis of a function
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
    MUArray NanoSeconds RealWorld
d <- forall (c :: * -> *) (prim :: * -> *).
(MutableCollection c, PrimMonad prim) =>
CountOf (MutableValue c) -> prim (c (PrimState prim))
mutNew (forall a b. From a b => a -> b
from Word
nbIters) :: IO (MUArray NanoSeconds (PrimState IO))
    MUArray NanoSeconds RealWorld -> Word -> IO ()
loop MUArray NanoSeconds RealWorld
d Word
0
    UArray NanoSeconds -> Word -> Measure
Measure forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (c :: * -> *) (prim :: * -> *).
(MutableCollection c, PrimMonad prim) =>
c (PrimState prim) -> prim (MutableFreezed c)
unsafeFreeze MUArray NanoSeconds RealWorld
d
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure Word
nbIters
  where
    loop :: MUArray NanoSeconds RealWorld -> Word -> IO ()
loop MUArray NanoSeconds RealWorld
d !Word
i
        | Word
i forall a. Eq a => a -> a -> Bool
== Word
nbIters = forall (m :: * -> *) a. Monad m => a -> m a
return ()
        | Bool
otherwise    = do
            (b
_, NanoSeconds
r) <- forall a. IO a -> IO (a, NanoSeconds)
measuringNanoSeconds (forall a. a -> IO a
evaluate forall a b. (a -> b) -> a -> b
$ a -> b
f a
a)
            forall (c :: * -> *) (prim :: * -> *).
(MutableCollection c, PrimMonad prim) =>
c (PrimState prim) -> MutableKey c -> MutableValue c -> prim ()
mutUnsafeWrite MUArray NanoSeconds RealWorld
d (forall a b. From a b => a -> b
from Word
i) NanoSeconds
r
            MUArray NanoSeconds RealWorld -> Word -> IO ()
loop MUArray NanoSeconds RealWorld
d (Word
iforall a. Additive a => a -> a -> a
+Word
1)