StrictBench-0.1.1: Benchmarking code through strict evaluation

Test.StrictBench

Contents

Description

A library to benchmark how long it takes to fully evaluate a value. Can be useful to identify the slow part of an algorithm, since Haskell's lazy evaluation can make it hard to see where the bottleneck lies.

Full evalution of a value is achieved by the rnf function, which requires that the data type of the value being tested is an instance of NFData. Making a data type an instance of NFData is trivially done by applying rnf to all of its fields and seq-ing those together.

Example:

  data Tree3 a = Leaf a | Branch (Tree3 a) (Tree3 a) (Tree3 a)
  
  instance NFData a => NFData (Tree3 a) where
      rnf (Leaf x) = rnf x
      rnf (Branch l c r) = rnf l `seq` rnf c `seq` rnf r
      
  main = bench . take 13 $ iterate (\x -> Branch x x x) (Leaf 'a')

  Output:
  765.625 ms

If a data constructor has no fields you can suffice with (), e.g.:

  data Answer = Yes | No

  instance NFData Answer where
      rnf Yes = ()
      rnf No  = ()

Synopsis

StrictBench

bench :: NFData a => a -> IO ()Source

Print how long it takes to strictly evaluate the given value.

Example:

  main = bench [1..10000000 :: Integer]

  Output:
  515.625 ms

benchDesc :: NFData a => String -> a -> IO ()Source

Like bench, benchDesc prints the time needed to fully evaluate the given value. Additionally, it prefixes the time taken with the provided string, which can be useful to distinguish between different benchmarks.

Example:

  main = benchDesc "Long string" $ replicate 10000000 'a'

  Output:
  Long string: 375.0 ms

time :: NFData a => a -> IO DoubleSource

The function used by bench and benchpress to determine how long (in milliseconds) the value takes to calculate. You can use this function for instance if you wish to sum the time of several different values.

Example:

  main = do t1 <- time $ filter (< 10) $ take 1000000 $ repeat (9 :: Int)
            t2 <- time $ reverse $ take 1000000 $ cycle "StrictBench"
            print $ t1 + t2
  
  Output:
  562.5

Re-exported for convenience

class NFData a where

Methods

rnf :: a -> ()

rnf should reduce its argument to normal form (that is, fully evaluate all sub-components), and then return '()'.

The default implementation of rnf is

 rnf a = a `seq` ()

which may be convenient when defining instances for data types with no unevaluated fields (e.g. enumerations).

Instances

NFData Bool 
NFData Char 
NFData Double 
NFData Float 
NFData Int 
NFData Int8 
NFData Int16 
NFData Int32 
NFData Int64 
NFData Integer 
NFData Word 
NFData Word8 
NFData Word16 
NFData Word32 
NFData Word64 
NFData () 
NFData IntSet 
NFData a => NFData [a] 
(Integral a, NFData a) => NFData (Ratio a) 
(RealFloat a, NFData a) => NFData (Complex a) 
NFData a => NFData (Maybe a) 
NFData a => NFData (Tree a) 
NFData a => NFData (IntMap a) 
NFData a => NFData (Set a) 
(NFData a, NFData b) => NFData (Either a b) 
(NFData a, NFData b) => NFData (a, b) 
(Ix a, NFData a, NFData b) => NFData (Array a b) 
(NFData k, NFData a) => NFData (Map k a) 
(NFData a, NFData b, NFData c) => NFData (a, b, c) 
(NFData a, NFData b, NFData c, NFData d) => NFData (a, b, c, d) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => NFData (a1, a2, a3, a4, a5, a6, a7, a8) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) 

rnf :: NFData a => a -> ()

rnf should reduce its argument to normal form (that is, fully evaluate all sub-components), and then return '()'.

The default implementation of rnf is

 rnf a = a `seq` ()

which may be convenient when defining instances for data types with no unevaluated fields (e.g. enumerations).