-- | 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 = () module Test.StrictBench ( -- * StrictBench bench, benchDesc, time, -- * Re-exported for convenience NFData, rnf) where import Control.Parallel.Strategies import Test.BenchPress hiding (bench) import Text.Printf -- | Print how long it takes to strictly evaluate the given -- value. -- -- Example: -- -- > main = bench [1..10000000 :: Integer] -- > -- > Output: -- > 515.625 ms bench :: NFData a => a -> IO () bench = (putStrLn . (++ " ms") . show =<<) . time -- | 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 benchDesc :: NFData a => String -> a -> IO () benchDesc s = (putStrLn . printf "%s: %s ms" s . show =<<) . time -- | 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 time :: NFData a => a -> IO Double time = fmap (median . fst) . benchmark 1 (return ()) (const $ return ()) . const . putStr . (`seq` "") . rnf