{-# LANGUAGE CPP #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, GADTs, RecordWildCards #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}
module Criterion.Measurement.Types
(
Benchmarkable(..)
, Benchmark(..)
, Measured(..)
, fromInt
, toInt
, fromDouble
, toDouble
, measureAccessors
, measureKeys
, measure
, rescale
, env
, envWithCleanup
, perBatchEnv
, perBatchEnvWithCleanup
, perRunEnv
, perRunEnvWithCleanup
, toBenchmarkable
, bench
, bgroup
, addPrefix
, benchNames
, nf
, whnf
, nfIO
, whnfIO
, nfAppIO
, whnfAppIO
)
where
import Control.DeepSeq (NFData(rnf))
import Criterion.Measurement.Types.Internal (fakeEnvironment, nf', whnf')
import Data.Aeson (FromJSON(..), ToJSON(..))
import Data.Binary (Binary(..))
import Data.Data (Data, Typeable)
import Data.Int (Int64)
import Data.Map (Map, fromList)
import GHC.Generics (Generic)
import Prelude ()
import Prelude.Compat
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed as U
data Benchmarkable = forall a . NFData a =>
Benchmarkable
{ ()
allocEnv :: Int64 -> IO a
, ()
cleanEnv :: Int64 -> a -> IO ()
, ()
runRepeatedly :: a -> Int64 -> IO ()
, Benchmarkable -> Bool
perRun :: Bool
}
noop :: Monad m => a -> m ()
noop :: forall (m :: * -> *) a. Monad m => a -> m ()
noop = forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# INLINE noop #-}
toBenchmarkable :: (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable :: (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable Int64 -> IO ()
f = forall a.
NFData a =>
(Int64 -> IO a)
-> (Int64 -> a -> IO ())
-> (a -> Int64 -> IO ())
-> Bool
-> Benchmarkable
Benchmarkable forall (m :: * -> *) a. Monad m => a -> m ()
noop (forall a b. a -> b -> a
const forall (m :: * -> *) a. Monad m => a -> m ()
noop) (forall a b. a -> b -> a
const Int64 -> IO ()
f) Bool
False
{-# INLINE toBenchmarkable #-}
data Measured = Measured {
Measured -> Double
measTime :: !Double
, Measured -> Double
measCpuTime :: !Double
, Measured -> Int64
measCycles :: !Int64
, Measured -> Int64
measIters :: !Int64
, Measured -> Int64
measAllocated :: !Int64
, Measured -> Int64
measPeakMbAllocated :: !Int64
, Measured -> Int64
measNumGcs :: !Int64
, Measured -> Int64
measBytesCopied :: !Int64
, Measured -> Double
measMutatorWallSeconds :: !Double
, Measured -> Double
measMutatorCpuSeconds :: !Double
, Measured -> Double
measGcWallSeconds :: !Double
, Measured -> Double
measGcCpuSeconds :: !Double
} deriving (Measured -> Measured -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Measured -> Measured -> Bool
$c/= :: Measured -> Measured -> Bool
== :: Measured -> Measured -> Bool
$c== :: Measured -> Measured -> Bool
Eq, ReadPrec [Measured]
ReadPrec Measured
Int -> ReadS Measured
ReadS [Measured]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Measured]
$creadListPrec :: ReadPrec [Measured]
readPrec :: ReadPrec Measured
$creadPrec :: ReadPrec Measured
readList :: ReadS [Measured]
$creadList :: ReadS [Measured]
readsPrec :: Int -> ReadS Measured
$creadsPrec :: Int -> ReadS Measured
Read, Int -> Measured -> ShowS
[Measured] -> ShowS
Measured -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Measured] -> ShowS
$cshowList :: [Measured] -> ShowS
show :: Measured -> String
$cshow :: Measured -> String
showsPrec :: Int -> Measured -> ShowS
$cshowsPrec :: Int -> Measured -> ShowS
Show, Typeable, Typeable Measured
Measured -> DataType
Measured -> Constr
(forall b. Data b => b -> b) -> Measured -> Measured
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Measured -> u
forall u. (forall d. Data d => d -> u) -> Measured -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Measured -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Measured -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Measured -> m Measured
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Measured -> m Measured
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Measured
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Measured -> c Measured
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Measured)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Measured)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Measured -> m Measured
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Measured -> m Measured
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Measured -> m Measured
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Measured -> m Measured
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Measured -> m Measured
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Measured -> m Measured
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Measured -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Measured -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Measured -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Measured -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Measured -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Measured -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Measured -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Measured -> r
gmapT :: (forall b. Data b => b -> b) -> Measured -> Measured
$cgmapT :: (forall b. Data b => b -> b) -> Measured -> Measured
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Measured)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Measured)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Measured)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Measured)
dataTypeOf :: Measured -> DataType
$cdataTypeOf :: Measured -> DataType
toConstr :: Measured -> Constr
$ctoConstr :: Measured -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Measured
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Measured
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Measured -> c Measured
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Measured -> c Measured
Data, forall x. Rep Measured x -> Measured
forall x. Measured -> Rep Measured x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Measured x -> Measured
$cfrom :: forall x. Measured -> Rep Measured x
Generic)
instance FromJSON Measured where
parseJSON :: Value -> Parser Measured
parseJSON Value
v = do
(Double
a,Double
b,Int64
c,Int64
d,Maybe Int64
e,Maybe Int64
f,Maybe Int64
g,Maybe Int64
h,Maybe Double
i,Maybe Double
j,Maybe Double
k,Maybe Double
l) <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Double
-> Double
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Double
-> Double
-> Double
-> Double
-> Measured
Measured Double
a Double
b Int64
c Int64
d
(Maybe Int64 -> Int64
int Maybe Int64
e) (Maybe Int64 -> Int64
int Maybe Int64
f) (Maybe Int64 -> Int64
int Maybe Int64
g) (Maybe Int64 -> Int64
int Maybe Int64
h)
(Maybe Double -> Double
db Maybe Double
i) (Maybe Double -> Double
db Maybe Double
j) (Maybe Double -> Double
db Maybe Double
k) (Maybe Double -> Double
db Maybe Double
l)
where int :: Maybe Int64 -> Int64
int = Maybe Int64 -> Int64
toInt; db :: Maybe Double -> Double
db = Maybe Double -> Double
toDouble
instance ToJSON Measured where
toJSON :: Measured -> Value
toJSON Measured{Double
Int64
measGcCpuSeconds :: Double
measGcWallSeconds :: Double
measMutatorCpuSeconds :: Double
measMutatorWallSeconds :: Double
measBytesCopied :: Int64
measNumGcs :: Int64
measPeakMbAllocated :: Int64
measAllocated :: Int64
measIters :: Int64
measCycles :: Int64
measCpuTime :: Double
measTime :: Double
measGcCpuSeconds :: Measured -> Double
measGcWallSeconds :: Measured -> Double
measMutatorCpuSeconds :: Measured -> Double
measMutatorWallSeconds :: Measured -> Double
measBytesCopied :: Measured -> Int64
measNumGcs :: Measured -> Int64
measPeakMbAllocated :: Measured -> Int64
measAllocated :: Measured -> Int64
measIters :: Measured -> Int64
measCycles :: Measured -> Int64
measCpuTime :: Measured -> Double
measTime :: Measured -> Double
..} = forall a. ToJSON a => a -> Value
toJSON
(Double
measTime, Double
measCpuTime, Int64
measCycles, Int64
measIters,
Int64 -> Maybe Int64
i Int64
measAllocated, Int64 -> Maybe Int64
i Int64
measPeakMbAllocated, Int64 -> Maybe Int64
i Int64
measNumGcs, Int64 -> Maybe Int64
i Int64
measBytesCopied,
Double -> Maybe Double
d Double
measMutatorWallSeconds, Double -> Maybe Double
d Double
measMutatorCpuSeconds,
Double -> Maybe Double
d Double
measGcWallSeconds, Double -> Maybe Double
d Double
measGcCpuSeconds)
where i :: Int64 -> Maybe Int64
i = Int64 -> Maybe Int64
fromInt; d :: Double -> Maybe Double
d = Double -> Maybe Double
fromDouble
instance NFData Measured where
rnf :: Measured -> ()
rnf Measured{} = ()
measureAccessors_ :: [(String, (Measured -> Maybe Double, String))]
measureAccessors_ :: [(String, (Measured -> Maybe Double, String))]
measureAccessors_ = [
(String
"time", (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Double
measTime,
String
"wall-clock time"))
, (String
"cpuTime", (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Double
measCpuTime,
String
"CPU time"))
, (String
"cycles", (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Int64
measCycles,
String
"CPU cycles"))
, (String
"iters", (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Int64
measIters,
String
"loop iterations"))
, (String
"allocated", (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Maybe Int64
fromInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Int64
measAllocated,
String
"(+RTS -T) bytes allocated"))
, (String
"peakMbAllocated", (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Maybe Int64
fromInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Int64
measPeakMbAllocated,
String
"(+RTS -T) peak megabytes allocated"))
, (String
"numGcs", (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Maybe Int64
fromInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Int64
measNumGcs,
String
"(+RTS -T) number of garbage collections"))
, (String
"bytesCopied", (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Maybe Int64
fromInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Int64
measBytesCopied,
String
"(+RTS -T) number of bytes copied during GC"))
, (String
"mutatorWallSeconds", (Double -> Maybe Double
fromDouble forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Double
measMutatorWallSeconds,
String
"(+RTS -T) wall-clock time for mutator threads"))
, (String
"mutatorCpuSeconds", (Double -> Maybe Double
fromDouble forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Double
measMutatorCpuSeconds,
String
"(+RTS -T) CPU time spent running mutator threads"))
, (String
"gcWallSeconds", (Double -> Maybe Double
fromDouble forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Double
measGcWallSeconds,
String
"(+RTS -T) wall-clock time spent doing GC"))
, (String
"gcCpuSeconds", (Double -> Maybe Double
fromDouble forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Double
measGcCpuSeconds,
String
"(+RTS -T) CPU time spent doing GC"))
]
measureKeys :: [String]
measureKeys :: [String]
measureKeys = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(String, (Measured -> Maybe Double, String))]
measureAccessors_
measureAccessors :: Map String (Measured -> Maybe Double, String)
measureAccessors :: Map String (Measured -> Maybe Double, String)
measureAccessors = forall k a. Ord k => [(k, a)] -> Map k a
fromList [(String, (Measured -> Maybe Double, String))]
measureAccessors_
rescale :: Measured -> Measured
rescale :: Measured -> Measured
rescale m :: Measured
m@Measured{Double
Int64
measGcCpuSeconds :: Double
measGcWallSeconds :: Double
measMutatorCpuSeconds :: Double
measMutatorWallSeconds :: Double
measBytesCopied :: Int64
measNumGcs :: Int64
measPeakMbAllocated :: Int64
measAllocated :: Int64
measIters :: Int64
measCycles :: Int64
measCpuTime :: Double
measTime :: Double
measGcCpuSeconds :: Measured -> Double
measGcWallSeconds :: Measured -> Double
measMutatorCpuSeconds :: Measured -> Double
measMutatorWallSeconds :: Measured -> Double
measBytesCopied :: Measured -> Int64
measNumGcs :: Measured -> Int64
measPeakMbAllocated :: Measured -> Int64
measAllocated :: Measured -> Int64
measIters :: Measured -> Int64
measCycles :: Measured -> Int64
measCpuTime :: Measured -> Double
measTime :: Measured -> Double
..} = Measured
m {
measTime :: Double
measTime = Double -> Double
d Double
measTime
, measCpuTime :: Double
measCpuTime = Double -> Double
d Double
measCpuTime
, measCycles :: Int64
measCycles = Int64 -> Int64
i Int64
measCycles
, measNumGcs :: Int64
measNumGcs = Int64 -> Int64
i Int64
measNumGcs
, measBytesCopied :: Int64
measBytesCopied = Int64 -> Int64
i Int64
measBytesCopied
, measMutatorWallSeconds :: Double
measMutatorWallSeconds = Double -> Double
d Double
measMutatorWallSeconds
, measMutatorCpuSeconds :: Double
measMutatorCpuSeconds = Double -> Double
d Double
measMutatorCpuSeconds
, measGcWallSeconds :: Double
measGcWallSeconds = Double -> Double
d Double
measGcWallSeconds
, measGcCpuSeconds :: Double
measGcCpuSeconds = Double -> Double
d Double
measGcCpuSeconds
} where
d :: Double -> Double
d Double
k = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Double
k (forall a. Fractional a => a -> a -> a
/ Double
iters) (Double -> Maybe Double
fromDouble Double
k)
i :: Int64 -> Int64
i Int64
k = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int64
k (forall a b. (RealFrac a, Integral b) => a -> b
round forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Fractional a => a -> a -> a
/ Double
iters)) (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int64 -> Maybe Int64
fromInt Int64
k)
iters :: Double
iters = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
measIters :: Double
fromInt :: Int64 -> Maybe Int64
fromInt :: Int64 -> Maybe Int64
fromInt Int64
i | Int64
i forall a. Eq a => a -> a -> Bool
== forall a. Bounded a => a
minBound = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just Int64
i
toInt :: Maybe Int64 -> Int64
toInt :: Maybe Int64 -> Int64
toInt Maybe Int64
Nothing = forall a. Bounded a => a
minBound
toInt (Just Int64
i) = Int64
i
fromDouble :: Double -> Maybe Double
fromDouble :: Double -> Maybe Double
fromDouble Double
d | forall a. RealFloat a => a -> Bool
isInfinite Double
d Bool -> Bool -> Bool
|| forall a. RealFloat a => a -> Bool
isNaN Double
d = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just Double
d
toDouble :: Maybe Double -> Double
toDouble :: Maybe Double -> Double
toDouble Maybe Double
Nothing = -Double
1forall a. Fractional a => a -> a -> a
/Double
0
toDouble (Just Double
d) = Double
d
instance Binary Measured where
put :: Measured -> Put
put Measured{Double
Int64
measGcCpuSeconds :: Double
measGcWallSeconds :: Double
measMutatorCpuSeconds :: Double
measMutatorWallSeconds :: Double
measBytesCopied :: Int64
measNumGcs :: Int64
measPeakMbAllocated :: Int64
measAllocated :: Int64
measIters :: Int64
measCycles :: Int64
measCpuTime :: Double
measTime :: Double
measGcCpuSeconds :: Measured -> Double
measGcWallSeconds :: Measured -> Double
measMutatorCpuSeconds :: Measured -> Double
measMutatorWallSeconds :: Measured -> Double
measBytesCopied :: Measured -> Int64
measNumGcs :: Measured -> Int64
measPeakMbAllocated :: Measured -> Int64
measAllocated :: Measured -> Int64
measIters :: Measured -> Int64
measCycles :: Measured -> Int64
measCpuTime :: Measured -> Double
measTime :: Measured -> Double
..} = do
forall t. Binary t => t -> Put
put Double
measTime; forall t. Binary t => t -> Put
put Double
measCpuTime; forall t. Binary t => t -> Put
put Int64
measCycles; forall t. Binary t => t -> Put
put Int64
measIters
forall t. Binary t => t -> Put
put Int64
measAllocated; forall t. Binary t => t -> Put
put Int64
measPeakMbAllocated; forall t. Binary t => t -> Put
put Int64
measNumGcs; forall t. Binary t => t -> Put
put Int64
measBytesCopied
forall t. Binary t => t -> Put
put Double
measMutatorWallSeconds; forall t. Binary t => t -> Put
put Double
measMutatorCpuSeconds
forall t. Binary t => t -> Put
put Double
measGcWallSeconds; forall t. Binary t => t -> Put
put Double
measGcCpuSeconds
get :: Get Measured
get = Double
-> Double
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Double
-> Double
-> Double
-> Double
-> Measured
Measured forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall t. Binary t => Get t
get
nf :: NFData b => (a -> b) -> a -> Benchmarkable
nf :: forall b a. NFData b => (a -> b) -> a -> Benchmarkable
nf a -> b
f a
x = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable (forall b a. (b -> ()) -> (a -> b) -> a -> Int64 -> IO ()
nf' forall a. NFData a => a -> ()
rnf a -> b
f a
x)
whnf :: (a -> b) -> a -> Benchmarkable
whnf :: forall a b. (a -> b) -> a -> Benchmarkable
whnf a -> b
f a
x = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable (forall a b. (a -> b) -> a -> Int64 -> IO ()
whnf' a -> b
f a
x)
nfIO :: NFData a => IO a -> Benchmarkable
nfIO :: forall a. NFData a => IO a -> Benchmarkable
nfIO IO a
a = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable (forall a. (a -> ()) -> IO a -> Int64 -> IO ()
nfIO' forall a. NFData a => a -> ()
rnf IO a
a)
whnfIO :: IO a -> Benchmarkable
whnfIO :: forall a. IO a -> Benchmarkable
whnfIO IO a
a = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable (forall a. IO a -> Int64 -> IO ()
whnfIO' IO a
a)
nfAppIO :: NFData b => (a -> IO b) -> a -> Benchmarkable
nfAppIO :: forall b a. NFData b => (a -> IO b) -> a -> Benchmarkable
nfAppIO a -> IO b
f a
v = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable (forall b a. (b -> ()) -> (a -> IO b) -> a -> Int64 -> IO ()
nfAppIO' forall a. NFData a => a -> ()
rnf a -> IO b
f a
v)
whnfAppIO :: (a -> IO b) -> a -> Benchmarkable
whnfAppIO :: forall a b. (a -> IO b) -> a -> Benchmarkable
whnfAppIO a -> IO b
f a
v = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable (forall a b. (a -> IO b) -> a -> Int64 -> IO ()
whnfAppIO' a -> IO b
f a
v)
nfIO' :: (a -> ()) -> IO a -> (Int64 -> IO ())
nfIO' :: forall a. (a -> ()) -> IO a -> Int64 -> IO ()
nfIO' a -> ()
reduce IO a
a = Int64 -> IO ()
go
where go :: Int64 -> IO ()
go Int64
n
| Int64
n forall a. Ord a => a -> a -> Bool
<= Int64
0 = forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
a
x <- IO a
a
a -> ()
reduce a
x seq :: forall a b. a -> b -> b
`seq` Int64 -> IO ()
go (Int64
nforall a. Num a => a -> a -> a
-Int64
1)
{-# NOINLINE nfIO' #-}
whnfIO' :: IO a -> (Int64 -> IO ())
whnfIO' :: forall a. IO a -> Int64 -> IO ()
whnfIO' IO a
a = Int64 -> IO ()
go
where
go :: Int64 -> IO ()
go Int64
n | Int64
n forall a. Ord a => a -> a -> Bool
<= Int64
0 = forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
a
x <- IO a
a
a
x seq :: forall a b. a -> b -> b
`seq` Int64 -> IO ()
go (Int64
nforall a. Num a => a -> a -> a
-Int64
1)
{-# NOINLINE whnfIO' #-}
nfAppIO' :: (b -> ()) -> (a -> IO b) -> a -> (Int64 -> IO ())
nfAppIO' :: forall b a. (b -> ()) -> (a -> IO b) -> a -> Int64 -> IO ()
nfAppIO' b -> ()
reduce a -> IO b
f a
v = Int64 -> IO ()
go
where go :: Int64 -> IO ()
go Int64
n
| Int64
n forall a. Ord a => a -> a -> Bool
<= Int64
0 = forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
b
x <- a -> IO b
f a
v
b -> ()
reduce b
x seq :: forall a b. a -> b -> b
`seq` Int64 -> IO ()
go (Int64
nforall a. Num a => a -> a -> a
-Int64
1)
{-# NOINLINE nfAppIO' #-}
whnfAppIO' :: (a -> IO b) -> a -> (Int64 -> IO ())
whnfAppIO' :: forall a b. (a -> IO b) -> a -> Int64 -> IO ()
whnfAppIO' a -> IO b
f a
v = Int64 -> IO ()
go
where go :: Int64 -> IO ()
go Int64
n
| Int64
n forall a. Ord a => a -> a -> Bool
<= Int64
0 = forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
b
x <- a -> IO b
f a
v
b
x seq :: forall a b. a -> b -> b
`seq` Int64 -> IO ()
go (Int64
nforall a. Num a => a -> a -> a
-Int64
1)
{-# NOINLINE whnfAppIO' #-}
data Benchmark where
Environment :: NFData env
=> IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
Benchmark :: String -> Benchmarkable -> Benchmark
BenchGroup :: String -> [Benchmark] -> Benchmark
env :: NFData env =>
IO env
-> (env -> Benchmark)
-> Benchmark
env :: forall env. NFData env => IO env -> (env -> Benchmark) -> Benchmark
env IO env
alloc = forall env a.
NFData env =>
IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
Environment IO env
alloc forall (m :: * -> *) a. Monad m => a -> m ()
noop
envWithCleanup
:: NFData env
=> IO env
-> (env -> IO a)
-> (env -> Benchmark)
-> Benchmark
envWithCleanup :: forall env a.
NFData env =>
IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
envWithCleanup = forall env a.
NFData env =>
IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
Environment
perBatchEnv
:: (NFData env, NFData b)
=> (Int64 -> IO env)
-> (env -> IO b)
-> Benchmarkable
perBatchEnv :: forall env b.
(NFData env, NFData b) =>
(Int64 -> IO env) -> (env -> IO b) -> Benchmarkable
perBatchEnv Int64 -> IO env
alloc = forall env b.
(NFData env, NFData b) =>
(Int64 -> IO env)
-> (Int64 -> env -> IO ()) -> (env -> IO b) -> Benchmarkable
perBatchEnvWithCleanup Int64 -> IO env
alloc (forall a b. a -> b -> a
const forall (m :: * -> *) a. Monad m => a -> m ()
noop)
perBatchEnvWithCleanup
:: (NFData env, NFData b)
=> (Int64 -> IO env)
-> (Int64 -> env -> IO ())
-> (env -> IO b)
-> Benchmarkable
perBatchEnvWithCleanup :: forall env b.
(NFData env, NFData b) =>
(Int64 -> IO env)
-> (Int64 -> env -> IO ()) -> (env -> IO b) -> Benchmarkable
perBatchEnvWithCleanup Int64 -> IO env
alloc Int64 -> env -> IO ()
clean env -> IO b
work
= forall a.
NFData a =>
(Int64 -> IO a)
-> (Int64 -> a -> IO ())
-> (a -> Int64 -> IO ())
-> Bool
-> Benchmarkable
Benchmarkable Int64 -> IO env
alloc Int64 -> env -> IO ()
clean (forall a. (a -> ()) -> IO a -> Int64 -> IO ()
nfIO' forall a. NFData a => a -> ()
rnf forall b c a. (b -> c) -> (a -> b) -> a -> c
. env -> IO b
work) Bool
False
perRunEnv
:: (NFData env, NFData b)
=> IO env
-> (env -> IO b)
-> Benchmarkable
perRunEnv :: forall env b.
(NFData env, NFData b) =>
IO env -> (env -> IO b) -> Benchmarkable
perRunEnv IO env
alloc = forall env b.
(NFData env, NFData b) =>
IO env -> (env -> IO ()) -> (env -> IO b) -> Benchmarkable
perRunEnvWithCleanup IO env
alloc forall (m :: * -> *) a. Monad m => a -> m ()
noop
perRunEnvWithCleanup
:: (NFData env, NFData b)
=> IO env
-> (env -> IO ())
-> (env -> IO b)
-> Benchmarkable
perRunEnvWithCleanup :: forall env b.
(NFData env, NFData b) =>
IO env -> (env -> IO ()) -> (env -> IO b) -> Benchmarkable
perRunEnvWithCleanup IO env
alloc env -> IO ()
clean env -> IO b
work = Benchmarkable
bm { perRun :: Bool
perRun = Bool
True }
where
bm :: Benchmarkable
bm = forall env b.
(NFData env, NFData b) =>
(Int64 -> IO env)
-> (Int64 -> env -> IO ()) -> (env -> IO b) -> Benchmarkable
perBatchEnvWithCleanup (forall a b. a -> b -> a
const IO env
alloc) (forall a b. a -> b -> a
const env -> IO ()
clean) env -> IO b
work
bench :: String
-> Benchmarkable
-> Benchmark
bench :: String -> Benchmarkable -> Benchmark
bench = String -> Benchmarkable -> Benchmark
Benchmark
bgroup :: String
-> [Benchmark]
-> Benchmark
bgroup :: String -> [Benchmark] -> Benchmark
bgroup = String -> [Benchmark] -> Benchmark
BenchGroup
addPrefix :: String
-> String
-> String
addPrefix :: String -> ShowS
addPrefix String
"" String
desc = String
desc
addPrefix String
pfx String
desc = String
pfx forall a. [a] -> [a] -> [a]
++ Char
'/' forall a. a -> [a] -> [a]
: String
desc
benchNames :: Benchmark -> [String]
benchNames :: Benchmark -> [String]
benchNames (Environment IO env
_ env -> IO a
_ env -> Benchmark
b) = Benchmark -> [String]
benchNames (env -> Benchmark
b forall env. env
fakeEnvironment)
benchNames (Benchmark String
d Benchmarkable
_) = [String
d]
benchNames (BenchGroup String
d [Benchmark]
bs) = forall a b. (a -> b) -> [a] -> [b]
map (String -> ShowS
addPrefix String
d) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Benchmark -> [String]
benchNames forall a b. (a -> b) -> a -> b
$ [Benchmark]
bs
instance Show Benchmark where
show :: Benchmark -> String
show (Environment IO env
_ env -> IO a
_ env -> Benchmark
b) = String
"Environment _ _" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (env -> Benchmark
b forall env. env
fakeEnvironment)
show (Benchmark String
d Benchmarkable
_) = String
"Benchmark " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show String
d
show (BenchGroup String
d [Benchmark]
_) = String
"BenchGroup " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show String
d
measure :: (U.Unbox a) => (Measured -> a) -> V.Vector Measured -> U.Vector a
measure :: forall a. Unbox a => (Measured -> a) -> Vector Measured -> Vector a
measure Measured -> a
f Vector Measured
v = forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
U.convert forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> Vector a -> Vector b
V.map Measured -> a
f forall a b. (a -> b) -> a -> b
$ Vector Measured
v