{-# LANGUAGE CPP #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, GADTs, RecordWildCards #-}
{-# OPTIONS_GHC -funbox-strict-fields #-}

-- |
-- Module      : Criterion.Measurement.Types
-- Copyright   : (c) 2009-2014 Bryan O'Sullivan
--
-- License     : BSD-style
-- Maintainer  : bos@serpentine.com
-- Stability   : experimental
-- Portability : GHC
--
-- Types for benchmarking.
--
-- The core type is 'Benchmarkable', which admits both pure functions
-- and 'IO' actions.
--
-- For a pure function of type @a -> b@, the benchmarking harness
-- calls this function repeatedly, each time with a different 'Int64'
-- argument (the number of times to run the function in a loop), and
-- reduces the result the function returns to weak head normal form.
--
-- For an action of type @IO a@, the benchmarking harness calls the
-- action repeatedly, but does not reduce the result.


module Criterion.Measurement.Types
  (
      -- * Benchmark descriptions
      Benchmarkable(..)
    , Benchmark(..)
    -- * Measurements
    , Measured(..)
    , fromInt
    , toInt
    , fromDouble
    , toDouble
    , measureAccessors
    , measureKeys
    , measure
    , rescale
    -- * Benchmark construction
    , env
    , envWithCleanup
    , perBatchEnv
    , perBatchEnvWithCleanup
    , perRunEnv
    , perRunEnvWithCleanup
    , toBenchmarkable
    , bench
    , bgroup
    , addPrefix
    , benchNames
    -- ** Evaluation control
    , 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


-- | A pure function or impure action that can be benchmarked. The
-- 'Int64' parameter indicates the number of times to run the given
-- function or action.
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 :: a -> m ()
noop = m () -> a -> m ()
forall a b. a -> b -> a
const (m () -> a -> m ()) -> m () -> a -> m ()
forall a b. (a -> b) -> a -> b
$ () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# INLINE noop #-}

-- | Construct a 'Benchmarkable' value from an impure action, where the 'Int64'
-- parameter indicates the number of times to run the action.
toBenchmarkable :: (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable :: (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable Int64 -> IO ()
f = (Int64 -> IO ())
-> (Int64 -> () -> IO ())
-> (() -> Int64 -> IO ())
-> Bool
-> Benchmarkable
forall a.
NFData a =>
(Int64 -> IO a)
-> (Int64 -> a -> IO ())
-> (a -> Int64 -> IO ())
-> Bool
-> Benchmarkable
Benchmarkable Int64 -> IO ()
forall (m :: * -> *) a. Monad m => a -> m ()
noop ((() -> IO ()) -> Int64 -> () -> IO ()
forall a b. a -> b -> a
const () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m ()
noop) ((Int64 -> IO ()) -> () -> Int64 -> IO ()
forall a b. a -> b -> a
const Int64 -> IO ()
f) Bool
False
{-# INLINE toBenchmarkable #-}


-- | A collection of measurements made while benchmarking.
--
-- Measurements related to garbage collection are tagged with __GC__.
-- They will only be available if a benchmark is run with @\"+RTS
-- -T\"@.
--
-- __Packed storage.__ When GC statistics cannot be collected, GC
-- values will be set to huge negative values.  If a field is labeled
-- with \"__GC__\" below, use 'fromInt' and 'fromDouble' to safely
-- convert to \"real\" values.
data Measured = Measured {
      Measured -> Double
measTime               :: !Double
      -- ^ Total wall-clock time elapsed, in seconds.
    , Measured -> Double
measCpuTime            :: !Double
      -- ^ Total CPU time elapsed, in seconds.  Includes both user and
      -- kernel (system) time.
    , Measured -> Int64
measCycles             :: !Int64
      -- ^ Cycles, in unspecified units that may be CPU cycles.  (On
      -- i386 and x86_64, this is measured using the @rdtsc@
      -- instruction.)
    , Measured -> Int64
measIters              :: !Int64
      -- ^ Number of loop iterations measured.

    , Measured -> Int64
measAllocated          :: !Int64
      -- ^ __(GC)__ Number of bytes allocated.  Access using 'fromInt'.
    , Measured -> Int64
measNumGcs             :: !Int64
      -- ^ __(GC)__ Number of garbage collections performed.  Access
      -- using 'fromInt'.
    , Measured -> Int64
measBytesCopied        :: !Int64
      -- ^ __(GC)__ Number of bytes copied during garbage collection.
      -- Access using 'fromInt'.
    , Measured -> Double
measMutatorWallSeconds :: !Double
      -- ^ __(GC)__ Wall-clock time spent doing real work
      -- (\"mutation\"), as distinct from garbage collection.  Access
      -- using 'fromDouble'.
    , Measured -> Double
measMutatorCpuSeconds  :: !Double
      -- ^ __(GC)__ CPU time spent doing real work (\"mutation\"), as
      -- distinct from garbage collection.  Access using 'fromDouble'.
    , Measured -> Double
measGcWallSeconds      :: !Double
      -- ^ __(GC)__ Wall-clock time spent doing garbage collection.
      -- Access using 'fromDouble'.
    , Measured -> Double
measGcCpuSeconds       :: !Double
      -- ^ __(GC)__ CPU time spent doing garbage collection.  Access
      -- using 'fromDouble'.
    } deriving (Measured -> Measured -> Bool
(Measured -> Measured -> Bool)
-> (Measured -> Measured -> Bool) -> Eq Measured
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]
(Int -> ReadS Measured)
-> ReadS [Measured]
-> ReadPrec Measured
-> ReadPrec [Measured]
-> Read 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
(Int -> Measured -> ShowS)
-> (Measured -> String) -> ([Measured] -> ShowS) -> Show Measured
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
DataType
Constr
Typeable Measured
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Measured -> c Measured)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Measured)
-> (Measured -> Constr)
-> (Measured -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> Measured -> Measured)
-> (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 u. (forall d. Data d => d -> u) -> Measured -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Measured -> u)
-> (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 (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Measured -> m Measured)
-> Data Measured
Measured -> DataType
Measured -> Constr
(forall b. Data b => b -> b) -> Measured -> Measured
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Measured -> c Measured
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cMeasured :: Constr
$tMeasured :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> Measured -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Measured -> u
gmapQ :: (forall d. Data d => d -> u) -> Measured -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Measured -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable Measured
Data, (forall x. Measured -> Rep Measured x)
-> (forall x. Rep Measured x -> Measured) -> Generic Measured
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 Double
h,Maybe Double
i,Maybe Double
j,Maybe Double
k) <- Value
-> Parser
     (Double, Double, Int64, Int64, Maybe Int64, Maybe Int64,
      Maybe Int64, Maybe Double, Maybe Double, Maybe Double,
      Maybe Double)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
      -- The first four fields are not subject to the encoding policy:
      Measured -> Parser Measured
forall (m :: * -> *) a. Monad m => a -> m a
return (Measured -> Parser Measured) -> Measured -> Parser Measured
forall a b. (a -> b) -> a -> b
$ Double
-> Double
-> 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 Double -> Double
db Maybe Double
h) (Maybe Double -> Double
db Maybe Double
i) (Maybe Double -> Double
db Maybe Double
j) (Maybe Double -> Double
db Maybe Double
k)
      where int :: Maybe Int64 -> Int64
int = Maybe Int64 -> Int64
toInt; db :: Maybe Double -> Double
db = Maybe Double -> Double
toDouble

-- Here we treat the numeric fields as `Maybe Int64` and `Maybe Double`
-- and we use a specific policy for deciding when they should be Nothing,
-- which becomes null in JSON.
instance ToJSON Measured where
    toJSON :: Measured -> Value
toJSON Measured{Double
Int64
measGcCpuSeconds :: Double
measGcWallSeconds :: Double
measMutatorCpuSeconds :: Double
measMutatorWallSeconds :: Double
measBytesCopied :: Int64
measNumGcs :: 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
measAllocated :: Measured -> Int64
measIters :: Measured -> Int64
measCycles :: Measured -> Int64
measCpuTime :: Measured -> Double
measTime :: Measured -> Double
..} = (Double, Double, Int64, Int64, Maybe Int64, Maybe Int64,
 Maybe Int64, Maybe Double, Maybe Double, Maybe Double,
 Maybe Double)
-> Value
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
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{} = ()

-- THIS MUST REFLECT THE ORDER OF FIELDS IN THE DATA TYPE.
--
-- The ordering is used by Javascript code to pick out the correct
-- index into the vector that represents a Measured value in that
-- world.
measureAccessors_ :: [(String, (Measured -> Maybe Double, String))]
measureAccessors_ :: [(String, (Measured -> Maybe Double, String))]
measureAccessors_ = [
    (String
"time",               (Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (Measured -> Double) -> Measured -> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Double
measTime,
                            String
"wall-clock time"))
  , (String
"cpuTime",            (Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (Measured -> Double) -> Measured -> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Double
measCpuTime,
                            String
"CPU time"))
  , (String
"cycles",             (Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (Measured -> Double) -> Measured -> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Double) -> (Measured -> Int64) -> Measured -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Int64
measCycles,
                            String
"CPU cycles"))
  , (String
"iters",              (Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (Measured -> Double) -> Measured -> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Double) -> (Measured -> Int64) -> Measured -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Int64
measIters,
                            String
"loop iterations"))
  , (String
"allocated",          ((Int64 -> Double) -> Maybe Int64 -> Maybe Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Maybe Int64 -> Maybe Double)
-> (Measured -> Maybe Int64) -> Measured -> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Maybe Int64
fromInt (Int64 -> Maybe Int64)
-> (Measured -> Int64) -> Measured -> Maybe Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Int64
measAllocated,
                            String
"(+RTS -T) bytes allocated"))
  , (String
"numGcs",             ((Int64 -> Double) -> Maybe Int64 -> Maybe Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Maybe Int64 -> Maybe Double)
-> (Measured -> Maybe Int64) -> Measured -> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Maybe Int64
fromInt (Int64 -> Maybe Int64)
-> (Measured -> Int64) -> Measured -> Maybe Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Int64
measNumGcs,
                            String
"(+RTS -T) number of garbage collections"))
  , (String
"bytesCopied",        ((Int64 -> Double) -> Maybe Int64 -> Maybe Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Maybe Int64 -> Maybe Double)
-> (Measured -> Maybe Int64) -> Measured -> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Maybe Int64
fromInt (Int64 -> Maybe Int64)
-> (Measured -> Int64) -> Measured -> Maybe Int64
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 (Double -> Maybe Double)
-> (Measured -> Double) -> Measured -> Maybe Double
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 (Double -> Maybe Double)
-> (Measured -> Double) -> Measured -> Maybe Double
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 (Double -> Maybe Double)
-> (Measured -> Double) -> Measured -> Maybe Double
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 (Double -> Maybe Double)
-> (Measured -> Double) -> Measured -> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Measured -> Double
measGcCpuSeconds,
                            String
"(+RTS -T) CPU time spent doing GC"))
  ]


-- | Field names in a 'Measured' record, in the order in which they
-- appear.
measureKeys :: [String]
measureKeys :: [String]
measureKeys = ((String, (Measured -> Maybe Double, String)) -> String)
-> [(String, (Measured -> Maybe Double, String))] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, (Measured -> Maybe Double, String)) -> String
forall a b. (a, b) -> a
fst [(String, (Measured -> Maybe Double, String))]
measureAccessors_

-- | Field names and accessors for a 'Measured' record.
measureAccessors :: Map String (Measured -> Maybe Double, String)
measureAccessors :: Map String (Measured -> Maybe Double, String)
measureAccessors = [(String, (Measured -> Maybe Double, String))]
-> Map String (Measured -> Maybe Double, String)
forall k a. Ord k => [(k, a)] -> Map k a
fromList [(String, (Measured -> Maybe Double, String))]
measureAccessors_

-- | Normalise every measurement as if 'measIters' was 1.
--
-- ('measIters' itself is left unaffected.)
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
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
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
    -- skip measIters
    , 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 = Double -> (Double -> Double) -> Maybe Double -> Double
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Double
k (Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
iters) (Double -> Maybe Double
fromDouble Double
k)
        i :: Int64 -> Int64
i Int64
k = Int64 -> (Double -> Int64) -> Maybe Double -> Int64
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int64
k (Double -> Int64
forall a b. (RealFrac a, Integral b) => a -> b
round (Double -> Int64) -> (Double -> Double) -> Double -> Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
iters)) (Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Double) -> Maybe Int64 -> Maybe Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int64 -> Maybe Int64
fromInt Int64
k)
        iters :: Double
iters               = Int64 -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
measIters :: Double

-- | Convert a (possibly unavailable) GC measurement to a true value.
-- If the measurement is a huge negative number that corresponds to
-- \"no data\", this will return 'Nothing'.
fromInt :: Int64 -> Maybe Int64
fromInt :: Int64 -> Maybe Int64
fromInt Int64
i | Int64
i Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== Int64
forall a. Bounded a => a
minBound = Maybe Int64
forall a. Maybe a
Nothing
          | Bool
otherwise     = Int64 -> Maybe Int64
forall a. a -> Maybe a
Just Int64
i

-- | Convert from a true value back to the packed representation used
-- for GC measurements.
toInt :: Maybe Int64 -> Int64
toInt :: Maybe Int64 -> Int64
toInt Maybe Int64
Nothing  = Int64
forall a. Bounded a => a
minBound
toInt (Just Int64
i) = Int64
i

-- | Convert a (possibly unavailable) GC measurement to a true value.
-- If the measurement is a huge negative number that corresponds to
-- \"no data\", this will return 'Nothing'.
fromDouble :: Double -> Maybe Double
fromDouble :: Double -> Maybe Double
fromDouble Double
d | Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
d Bool -> Bool -> Bool
|| Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
d = Maybe Double
forall a. Maybe a
Nothing
             | Bool
otherwise               = Double -> Maybe Double
forall a. a -> Maybe a
Just Double
d

-- | Convert from a true value back to the packed representation used
-- for GC measurements.
toDouble :: Maybe Double -> Double
toDouble :: Maybe Double -> Double
toDouble Maybe Double
Nothing  = -Double
1Double -> Double -> Double
forall 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
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
measAllocated :: Measured -> Int64
measIters :: Measured -> Int64
measCycles :: Measured -> Int64
measCpuTime :: Measured -> Double
measTime :: Measured -> Double
..} = do
      Double -> Put
forall t. Binary t => t -> Put
put Double
measTime; Double -> Put
forall t. Binary t => t -> Put
put Double
measCpuTime; Int64 -> Put
forall t. Binary t => t -> Put
put Int64
measCycles; Int64 -> Put
forall t. Binary t => t -> Put
put Int64
measIters
      Int64 -> Put
forall t. Binary t => t -> Put
put Int64
measAllocated; Int64 -> Put
forall t. Binary t => t -> Put
put Int64
measNumGcs; Int64 -> Put
forall t. Binary t => t -> Put
put Int64
measBytesCopied
      Double -> Put
forall t. Binary t => t -> Put
put Double
measMutatorWallSeconds; Double -> Put
forall t. Binary t => t -> Put
put Double
measMutatorCpuSeconds
      Double -> Put
forall t. Binary t => t -> Put
put Double
measGcWallSeconds; Double -> Put
forall t. Binary t => t -> Put
put Double
measGcCpuSeconds
    get :: Get Measured
get = Double
-> Double
-> Int64
-> Int64
-> Int64
-> Int64
-> Int64
-> Double
-> Double
-> Double
-> Double
-> Measured
Measured (Double
 -> Double
 -> Int64
 -> Int64
 -> Int64
 -> Int64
 -> Int64
 -> Double
 -> Double
 -> Double
 -> Double
 -> Measured)
-> Get Double
-> Get
     (Double
      -> Int64
      -> Int64
      -> Int64
      -> Int64
      -> Int64
      -> Double
      -> Double
      -> Double
      -> Double
      -> Measured)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Double
forall t. Binary t => Get t
get Get
  (Double
   -> Int64
   -> Int64
   -> Int64
   -> Int64
   -> Int64
   -> Double
   -> Double
   -> Double
   -> Double
   -> Measured)
-> Get Double
-> Get
     (Int64
      -> Int64
      -> Int64
      -> Int64
      -> Int64
      -> Double
      -> Double
      -> Double
      -> Double
      -> Measured)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Double
forall t. Binary t => Get t
get Get
  (Int64
   -> Int64
   -> Int64
   -> Int64
   -> Int64
   -> Double
   -> Double
   -> Double
   -> Double
   -> Measured)
-> Get Int64
-> Get
     (Int64
      -> Int64
      -> Int64
      -> Int64
      -> Double
      -> Double
      -> Double
      -> Double
      -> Measured)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Int64
forall t. Binary t => Get t
get Get
  (Int64
   -> Int64
   -> Int64
   -> Int64
   -> Double
   -> Double
   -> Double
   -> Double
   -> Measured)
-> Get Int64
-> Get
     (Int64
      -> Int64
      -> Int64
      -> Double
      -> Double
      -> Double
      -> Double
      -> Measured)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Int64
forall t. Binary t => Get t
get
                   Get
  (Int64
   -> Int64
   -> Int64
   -> Double
   -> Double
   -> Double
   -> Double
   -> Measured)
-> Get Int64
-> Get
     (Int64
      -> Int64 -> Double -> Double -> Double -> Double -> Measured)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Int64
forall t. Binary t => Get t
get Get
  (Int64
   -> Int64 -> Double -> Double -> Double -> Double -> Measured)
-> Get Int64
-> Get (Int64 -> Double -> Double -> Double -> Double -> Measured)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Int64
forall t. Binary t => Get t
get Get (Int64 -> Double -> Double -> Double -> Double -> Measured)
-> Get Int64
-> Get (Double -> Double -> Double -> Double -> Measured)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Int64
forall t. Binary t => Get t
get Get (Double -> Double -> Double -> Double -> Measured)
-> Get Double -> Get (Double -> Double -> Double -> Measured)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Double
forall t. Binary t => Get t
get Get (Double -> Double -> Double -> Measured)
-> Get Double -> Get (Double -> Double -> Measured)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Double
forall t. Binary t => Get t
get Get (Double -> Double -> Measured)
-> Get Double -> Get (Double -> Measured)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Double
forall t. Binary t => Get t
get Get (Double -> Measured) -> Get Double -> Get Measured
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Get Double
forall t. Binary t => Get t
get

-- | Apply an argument to a function, and evaluate the result to
-- normal form (NF).
nf :: NFData b => (a -> b) -> a -> Benchmarkable
nf :: (a -> b) -> a -> Benchmarkable
nf a -> b
f a
x = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable ((b -> ()) -> (a -> b) -> a -> Int64 -> IO ()
forall b a. (b -> ()) -> (a -> b) -> a -> Int64 -> IO ()
nf' b -> ()
forall a. NFData a => a -> ()
rnf a -> b
f a
x)

-- | Apply an argument to a function, and evaluate the result to weak
-- head normal form (WHNF).
whnf :: (a -> b) -> a -> Benchmarkable
whnf :: (a -> b) -> a -> Benchmarkable
whnf a -> b
f a
x = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable ((a -> b) -> a -> Int64 -> IO ()
forall a b. (a -> b) -> a -> Int64 -> IO ()
whnf' a -> b
f a
x)

-- | Perform an action, then evaluate its result to normal form (NF).
-- This is particularly useful for forcing a lazy 'IO' action to be
-- completely performed.
--
-- If the construction of the 'IO a' value is an important factor
-- in the benchmark, it is best to use 'nfAppIO' instead.
nfIO :: NFData a => IO a -> Benchmarkable
nfIO :: IO a -> Benchmarkable
nfIO IO a
a = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable ((a -> ()) -> IO a -> Int64 -> IO ()
forall a. (a -> ()) -> IO a -> Int64 -> IO ()
nfIO' a -> ()
forall a. NFData a => a -> ()
rnf IO a
a)

-- | Perform an action, then evaluate its result to weak head normal
-- form (WHNF).  This is useful for forcing an 'IO' action whose result
-- is an expression to be evaluated down to a more useful value.
--
-- If the construction of the 'IO a' value is an important factor
-- in the benchmark, it is best to use 'whnfAppIO' instead.
whnfIO :: IO a -> Benchmarkable
whnfIO :: IO a -> Benchmarkable
whnfIO IO a
a = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable (IO a -> Int64 -> IO ()
forall a. IO a -> Int64 -> IO ()
whnfIO' IO a
a)

-- | Apply an argument to a function which performs an action, then
-- evaluate its result to normal form (NF).
-- This function constructs the 'IO b' value on each iteration,
-- similar to 'nf'.
-- This is particularly useful for 'IO' actions where the bulk of the
-- work is not bound by IO, but by pure computations that may
-- optimize away if the argument is known statically, as in 'nfIO'.

-- See issue #189 for more info.
nfAppIO :: NFData b => (a -> IO b) -> a -> Benchmarkable
nfAppIO :: (a -> IO b) -> a -> Benchmarkable
nfAppIO a -> IO b
f a
v = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable ((b -> ()) -> (a -> IO b) -> a -> Int64 -> IO ()
forall b a. (b -> ()) -> (a -> IO b) -> a -> Int64 -> IO ()
nfAppIO' b -> ()
forall a. NFData a => a -> ()
rnf a -> IO b
f a
v)

-- | Perform an action, then evaluate its result to weak head normal
-- form (WHNF).
-- This function constructs the 'IO b' value on each iteration,
-- similar to 'whnf'.
-- This is particularly useful for 'IO' actions where the bulk of the
-- work is not bound by IO, but by pure computations that may
-- optimize away if the argument is known statically, as in 'nfIO'.

-- See issue #189 for more info.
whnfAppIO :: (a -> IO b) -> a -> Benchmarkable
whnfAppIO :: (a -> IO b) -> a -> Benchmarkable
whnfAppIO a -> IO b
f a
v = (Int64 -> IO ()) -> Benchmarkable
toBenchmarkable ((a -> IO b) -> a -> Int64 -> IO ()
forall a b. (a -> IO b) -> a -> Int64 -> IO ()
whnfAppIO' a -> IO b
f a
v)

-- Along with nf' and whnf', the following two functions are the core
-- benchmarking loops. They have been carefully constructed to avoid
-- allocation while also evaluating @a@.
--
-- These functions must not be inlined. There are two possible issues that
-- can arise if they are inlined. First, the work is often floated out of
-- the loop, which creates a nonsense benchmark. Second, the benchmark code
-- itself could be changed by the user's optimization level. By marking them
-- @NOINLINE@, the core benchmark code is always the same.
--
-- See #183 and #184 for discussion.

-- | Generate a function that will run an action a given number of times,
-- reducing it to normal form each time.
nfIO' :: (a -> ()) -> IO a -> (Int64 -> IO ())
nfIO' :: (a -> ()) -> IO a -> Int64 -> IO ()
nfIO' a -> ()
reduce IO a
a = Int64 -> IO ()
go
  where go :: Int64 -> IO ()
go Int64
n
          | Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0    = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          | Bool
otherwise = do
              a
x <- IO a
a
              a -> ()
reduce a
x () -> IO () -> IO ()
`seq` Int64 -> IO ()
go (Int64
nInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int64
1)
{-# NOINLINE nfIO' #-}

-- | Generate a function that will run an action a given number of times.
whnfIO' :: IO a -> (Int64 -> IO ())
whnfIO' :: IO a -> Int64 -> IO ()
whnfIO' IO a
a = Int64 -> IO ()
go
  where
    go :: Int64 -> IO ()
go Int64
n | Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0    = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
         | Bool
otherwise = do
             a
x <- IO a
a
             a
x a -> IO () -> IO ()
`seq` Int64 -> IO ()
go (Int64
nInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int64
1)
{-# NOINLINE whnfIO' #-}

-- | Generate a function which applies an argument to a function a given
-- number of times, running its action and reducing the result to normal form.
nfAppIO' :: (b -> ()) -> (a -> IO b) -> a -> (Int64 -> IO ())
nfAppIO' :: (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 Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0    = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          | Bool
otherwise = do
              b
x <- a -> IO b
f a
v
              b -> ()
reduce b
x () -> IO () -> IO ()
`seq` Int64 -> IO ()
go (Int64
nInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int64
1)
{-# NOINLINE nfAppIO' #-}

-- | Generate a function which applies an argument to a function a given
-- number of times, running its action and reducing the result to
-- weak-head normal form.
whnfAppIO' :: (a -> IO b) -> a -> (Int64 -> IO ())
whnfAppIO' :: (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 Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0    = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
          | Bool
otherwise = do
              b
x <- a -> IO b
f a
v
              b
x b -> IO () -> IO ()
`seq` Int64 -> IO ()
go (Int64
nInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int64
1)
{-# NOINLINE whnfAppIO' #-}

-- | Specification of a collection of benchmarks and environments. A
-- benchmark may consist of:
--
-- * An environment that creates input data for benchmarks, created
--   with 'env'.
--
-- * A single 'Benchmarkable' item with a name, created with 'bench'.
--
-- * A (possibly nested) group of 'Benchmark's, created with 'bgroup'.
data Benchmark where
    Environment  :: NFData env
                 => IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
    Benchmark    :: String -> Benchmarkable -> Benchmark
    BenchGroup   :: String -> [Benchmark] -> Benchmark


-- | Run a benchmark (or collection of benchmarks) in the given
-- environment.  The purpose of an environment is to lazily create
-- input data to pass to the functions that will be benchmarked.
--
-- A common example of environment data is input that is read from a
-- file.  Another is a large data structure constructed in-place.
--
-- __Motivation.__ In earlier versions of criterion, all benchmark
-- inputs were always created when a program started running.  By
-- deferring the creation of an environment when its associated
-- benchmarks need the its, we avoid two problems that this strategy
-- caused:
--
-- * Memory pressure distorted the results of unrelated benchmarks.
--   If one benchmark needed e.g. a gigabyte-sized input, it would
--   force the garbage collector to do extra work when running some
--   other benchmark that had no use for that input.  Since the data
--   created by an environment is only available when it is in scope,
--   it should be garbage collected before other benchmarks are run.
--
-- * The time cost of generating all needed inputs could be
--   significant in cases where no inputs (or just a few) were really
--   needed.  This occurred often, for instance when just one out of a
--   large suite of benchmarks was run, or when a user would list the
--   collection of benchmarks without running any.
--
-- __Creation.__ An environment is created right before its related
-- benchmarks are run.  The 'IO' action that creates the environment
-- is run, then the newly created environment is evaluated to normal
-- form (hence the 'NFData' constraint) before being passed to the
-- function that receives the environment.
--
-- __Complex environments.__ If you need to create an environment that
-- contains multiple values, simply pack the values into a tuple.
--
-- __Lazy pattern matching.__ In situations where a \"real\"
-- environment is not needed, e.g. if a list of benchmark names is
-- being generated, a value which throws an exception will be passed
-- to the function that receives the environment.  This avoids the
-- overhead of generating an environment that will not actually be
-- used.
--
-- The function that receives the environment must use lazy pattern
-- matching to deconstruct the tuple (e.g., @~(x, y)@, not @(x, y)@),
-- as use of strict pattern matching will cause a crash if an
-- exception-throwing value is passed in.
--
-- __Example.__ This program runs benchmarks in an environment that
-- contains two values.  The first value is the contents of a text
-- file; the second is a string.  Pay attention to the use of a lazy
-- pattern to deconstruct the tuple in the function that returns the
-- benchmarks to be run.
--
-- > setupEnv = do
-- >   let small = replicate 1000 (1 :: Int)
-- >   big <- map length . words <$> readFile "/usr/dict/words"
-- >   return (small, big)
-- >
-- > main = defaultMain [
-- >    -- notice the lazy pattern match here!
-- >    env setupEnv $ \ ~(small,big) -> bgroup "main" [
-- >    bgroup "small" [
-- >      bench "length" $ whnf length small
-- >    , bench "length . filter" $ whnf (length . filter (==1)) small
-- >    ]
-- >  ,  bgroup "big" [
-- >      bench "length" $ whnf length big
-- >    , bench "length . filter" $ whnf (length . filter (==1)) big
-- >    ]
-- >  ] ]
--
-- __Discussion.__ The environment created in the example above is
-- intentionally /not/ ideal.  As Haskell's scoping rules suggest, the
-- variable @big@ is in scope for the benchmarks that use only
-- @small@.  It would be better to create a separate environment for
-- @big@, so that it will not be kept alive while the unrelated
-- benchmarks are being run.
env :: NFData env =>
       IO env
    -- ^ Create the environment.  The environment will be evaluated to
    -- normal form before being passed to the benchmark.
    -> (env -> Benchmark)
    -- ^ Take the newly created environment and make it available to
    -- the given benchmarks.
    -> Benchmark
env :: IO env -> (env -> Benchmark) -> Benchmark
env IO env
alloc = IO env -> (env -> IO ()) -> (env -> Benchmark) -> Benchmark
forall env a.
NFData env =>
IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
Environment IO env
alloc env -> IO ()
forall (m :: * -> *) a. Monad m => a -> m ()
noop

-- | Same as `env`, but but allows for an additional callback
-- to clean up the environment. Resource clean up is exception safe, that is,
-- it runs even if the 'Benchmark' throws an exception.
envWithCleanup
    :: NFData env
    => IO env
    -- ^ Create the environment.  The environment will be evaluated to
    -- normal form before being passed to the benchmark.
    -> (env -> IO a)
    -- ^ Clean up the created environment.
    -> (env -> Benchmark)
    -- ^ Take the newly created environment and make it available to
    -- the given benchmarks.
    -> Benchmark
envWithCleanup :: IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
envWithCleanup = IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
forall env a.
NFData env =>
IO env -> (env -> IO a) -> (env -> Benchmark) -> Benchmark
Environment

-- | Create a Benchmarkable where a fresh environment is allocated for every
-- batch of runs of the benchmarkable.
--
-- The environment is evaluated to normal form before the benchmark is run.
--
-- When using 'whnf', 'whnfIO', etc. Criterion creates a 'Benchmarkable'
-- whichs runs a batch of @N@ repeat runs of that expressions. Criterion may
-- run any number of these batches to get accurate measurements. Environments
-- created by 'env' and 'envWithCleanup', are shared across all these batches
-- of runs.
--
-- This is fine for simple benchmarks on static input, but when benchmarking
-- IO operations where these operations can modify (and especially grow) the
-- environment this means that later batches might have their accuracy effected
-- due to longer, for example, longer garbage collection pauses.
--
-- An example: Suppose we want to benchmark writing to a Chan, if we allocate
-- the Chan using environment and our benchmark consists of @writeChan env ()@,
-- the contents and thus size of the Chan will grow with every repeat. If
-- Criterion runs a 1,000 batches of 1,000 repeats, the result is that the
-- channel will have 999,000 items in it by the time the last batch is run.
-- Since GHC GC has to copy the live set for every major GC this means our last
-- set of writes will suffer a lot of noise of the previous repeats.
--
-- By allocating a fresh environment for every batch of runs this function
-- should eliminate this effect.
perBatchEnv
    :: (NFData env, NFData b)
    => (Int64 -> IO env)
    -- ^ Create an environment for a batch of N runs. The environment will be
    -- evaluated to normal form before running.
    -> (env -> IO b)
    -- ^ Function returning the IO action that should be benchmarked with the
    -- newly generated environment.
    -> Benchmarkable
perBatchEnv :: (Int64 -> IO env) -> (env -> IO b) -> Benchmarkable
perBatchEnv Int64 -> IO env
alloc = (Int64 -> IO env)
-> (Int64 -> env -> IO ()) -> (env -> IO b) -> Benchmarkable
forall env b.
(NFData env, NFData b) =>
(Int64 -> IO env)
-> (Int64 -> env -> IO ()) -> (env -> IO b) -> Benchmarkable
perBatchEnvWithCleanup Int64 -> IO env
alloc ((env -> IO ()) -> Int64 -> env -> IO ()
forall a b. a -> b -> a
const env -> IO ()
forall (m :: * -> *) a. Monad m => a -> m ()
noop)

-- | Same as `perBatchEnv`, but but allows for an additional callback
-- to clean up the environment. Resource clean up is exception safe, that is,
-- it runs even if the 'Benchmark' throws an exception.
perBatchEnvWithCleanup
    :: (NFData env, NFData b)
    => (Int64 -> IO env)
    -- ^ Create an environment for a batch of N runs. The environment will be
    -- evaluated to normal form before running.
    -> (Int64 -> env -> IO ())
    -- ^ Clean up the created environment.
    -> (env -> IO b)
    -- ^ Function returning the IO action that should be benchmarked with the
    -- newly generated environment.
    -> Benchmarkable
perBatchEnvWithCleanup :: (Int64 -> IO env)
-> (Int64 -> env -> IO ()) -> (env -> IO b) -> Benchmarkable
perBatchEnvWithCleanup Int64 -> IO env
alloc Int64 -> env -> IO ()
clean env -> IO b
work
    = (Int64 -> IO env)
-> (Int64 -> env -> IO ())
-> (env -> Int64 -> IO ())
-> Bool
-> Benchmarkable
forall a.
NFData a =>
(Int64 -> IO a)
-> (Int64 -> a -> IO ())
-> (a -> Int64 -> IO ())
-> Bool
-> Benchmarkable
Benchmarkable Int64 -> IO env
alloc Int64 -> env -> IO ()
clean ((b -> ()) -> IO b -> Int64 -> IO ()
forall a. (a -> ()) -> IO a -> Int64 -> IO ()
nfIO' b -> ()
forall a. NFData a => a -> ()
rnf (IO b -> Int64 -> IO ()) -> (env -> IO b) -> env -> Int64 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. env -> IO b
work) Bool
False

-- | Create a Benchmarkable where a fresh environment is allocated for every
-- run of the operation to benchmark. This is useful for benchmarking mutable
-- operations that need a fresh environment, such as sorting a mutable Vector.
--
-- As with 'env' and 'perBatchEnv' the environment is evaluated to normal form
-- before the benchmark is run.
--
-- This introduces extra noise and result in reduce accuracy compared to other
-- Criterion benchmarks. But allows easier benchmarking for mutable operations
-- than was previously possible.
perRunEnv
    :: (NFData env, NFData b)
    => IO env
    -- ^ Action that creates the environment for a single run.
    -> (env -> IO b)
    -- ^ Function returning the IO action that should be benchmarked with the
    -- newly genereted environment.
    -> Benchmarkable
perRunEnv :: IO env -> (env -> IO b) -> Benchmarkable
perRunEnv IO env
alloc = IO env -> (env -> IO ()) -> (env -> IO b) -> Benchmarkable
forall env b.
(NFData env, NFData b) =>
IO env -> (env -> IO ()) -> (env -> IO b) -> Benchmarkable
perRunEnvWithCleanup IO env
alloc env -> IO ()
forall (m :: * -> *) a. Monad m => a -> m ()
noop

-- | Same as `perRunEnv`, but but allows for an additional callback
-- to clean up the environment. Resource clean up is exception safe, that is,
-- it runs even if the 'Benchmark' throws an exception.
perRunEnvWithCleanup
    :: (NFData env, NFData b)
    => IO env
    -- ^ Action that creates the environment for a single run.
    -> (env -> IO ())
    -- ^ Clean up the created environment.
    -> (env -> IO b)
    -- ^ Function returning the IO action that should be benchmarked with the
    -- newly genereted environment.
    -> Benchmarkable
perRunEnvWithCleanup :: 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 = (Int64 -> IO env)
-> (Int64 -> env -> IO ()) -> (env -> IO b) -> Benchmarkable
forall env b.
(NFData env, NFData b) =>
(Int64 -> IO env)
-> (Int64 -> env -> IO ()) -> (env -> IO b) -> Benchmarkable
perBatchEnvWithCleanup (IO env -> Int64 -> IO env
forall a b. a -> b -> a
const IO env
alloc) ((env -> IO ()) -> Int64 -> env -> IO ()
forall a b. a -> b -> a
const env -> IO ()
clean) env -> IO b
work

-- | Create a single benchmark.
bench :: String                 -- ^ A name to identify the benchmark.
      -> Benchmarkable          -- ^ An activity to be benchmarked.
      -> Benchmark
bench :: String -> Benchmarkable -> Benchmark
bench = String -> Benchmarkable -> Benchmark
Benchmark

-- | Group several benchmarks together under a common name.
bgroup :: String                -- ^ A name to identify the group of benchmarks.
       -> [Benchmark]           -- ^ Benchmarks to group under this name.
       -> Benchmark
bgroup :: String -> [Benchmark] -> Benchmark
bgroup = String -> [Benchmark] -> Benchmark
BenchGroup

-- | Add the given prefix to a name.  If the prefix is empty, the name
-- is returned unmodified.  Otherwise, the prefix and name are
-- separated by a @\'\/\'@ character.
addPrefix :: String             -- ^ Prefix.
          -> String             -- ^ Name.
          -> String
addPrefix :: String -> ShowS
addPrefix String
""  String
desc = String
desc
addPrefix String
pfx String
desc = String
pfx String -> ShowS
forall a. [a] -> [a] -> [a]
++ Char
'/' Char -> ShowS
forall a. a -> [a] -> [a]
: String
desc

-- | Retrieve the names of all benchmarks.  Grouped benchmarks are
-- prefixed with the name of the group they're in.
benchNames :: Benchmark -> [String]
benchNames :: Benchmark -> [String]
benchNames (Environment IO env
_ env -> IO a
_ env -> Benchmark
b) = Benchmark -> [String]
benchNames (env -> Benchmark
b env
forall env. env
fakeEnvironment)
benchNames (Benchmark String
d Benchmarkable
_)   = [String
d]
benchNames (BenchGroup String
d [Benchmark]
bs) = ShowS -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> ShowS
addPrefix String
d) ([String] -> [String])
-> ([Benchmark] -> [String]) -> [Benchmark] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Benchmark -> [String]) -> [Benchmark] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Benchmark -> [String]
benchNames ([Benchmark] -> [String]) -> [Benchmark] -> [String]
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 _ _" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Benchmark -> String
forall a. Show a => a -> String
show (env -> Benchmark
b env
forall env. env
fakeEnvironment)
    show (Benchmark String
d Benchmarkable
_)   = String
"Benchmark " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
d
    show (BenchGroup String
d [Benchmark]
_)  = String
"BenchGroup " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show String
d

measure :: (U.Unbox a) => (Measured -> a) -> V.Vector Measured -> U.Vector a
measure :: (Measured -> a) -> Vector Measured -> Vector a
measure Measured -> a
f Vector Measured
v = Vector a -> Vector a
forall (v :: * -> *) a (w :: * -> *).
(Vector v a, Vector w a) =>
v a -> w a
U.convert (Vector a -> Vector a)
-> (Vector Measured -> Vector a) -> Vector Measured -> Vector a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Measured -> a) -> Vector Measured -> Vector a
forall a b. (a -> b) -> Vector a -> Vector b
V.map Measured -> a
f (Vector Measured -> Vector a) -> Vector Measured -> Vector a
forall a b. (a -> b) -> a -> b
$ Vector Measured
v