3

This code compiles and runs without problems:

module Main where

import Criterion.Main

main :: IO ()
main =
  defaultMain
    [env (return $ [1,2])
         (\is ->
            bgroup "group" (benchmarks is))]

timesTwo :: Int -> Int
timesTwo i = 2 * i

benchmarks :: [Int] -> [Benchmark]
benchmarks is = [ bench "foo" $ nf timesTwo (is !! 0)
                , bench "foo" $ nf timesTwo (is !! 1) ]

Yet if I change the benchmarks function to look like

benchmarks :: [Int] -> [Benchmark]
benchmarks is = map (\i -> bench "foo" $ nf timesTwo i) is

it still compiles but I get this runtime error:

ghci> main
*** Exception: Criterion atttempted to retrieve a non-existent environment!
        Perhaps you forgot to use lazy pattern matching in a function which
        constructs benchmarks from an environment?
        (see the documentation for `env` for details)

How do I resolve this?

As you can see, my goal is to map over a list from obtained from the environment in order to turn it into a list of Benchmarks that I can use with Criterion.

Note: I eventually want to use way more elements than just two, so tuples are not what I want here.

haskellHQ
  • 1,027
  • 6
  • 15
  • How is the list obtained from the environment? Will you know its length statically? – oisdk Jun 06 '18 at 18:18
  • 1
    @oisdk In practice, I will be using numbers I know myself at compile-time. Think of this: [100, 1000, 10000, 1000000] My goal is to do a "big O" benchmark. (Feel free to suggest better ways of doing "big O" analysis, if you know of any.) – haskellHQ Jun 06 '18 at 18:27

2 Answers2

2

For benchmarking at different sizes, I usually do something like this:

module Main (main) where

import Criterion.Main
import System.Random
import Control.Monad

import qualified Data.List
import qualified Data.Sequence

int :: Int -> IO Int
int n = randomRIO (0,n)

benchAtSize :: Int -> Benchmark
benchAtSize n =
    env (replicateM n (int n)) $
    \xs ->
         bgroup (show n)
           [ bench "Data.List"     $ nf Data.List.sort xs
           , bench "Data.Sequence" $ nf (Data.Sequence.sort . Data.Sequence.fromList) xs
           ]

main :: IO ()
main = defaultMain (map benchAtSize [100, 1000, 10000])

env is useful for ensuring that two different functions are compared on the same sample, and it's not designed to compute your whole dataset before running the benchmarks. Also, because all of the data created by env is kept in memory during the benchmarking of anything in its scope, you want to minimize it as much as is possible, to reduce overhead while benchmarking.

oisdk
  • 9,763
  • 4
  • 18
  • 36
1

env is very picky with strictness. You can't use it here. The structure of the benchmarks created under env cannot depend on the environment. That is, the environment can be used by the code that is being benchmarked, but the way the benchmarks themselves are organized, named, etc. cannot use it. This is because criterion will sometimes pass _|_ instead of the real environment, when it wants to just inspect the structure of the benchmarks without executing them. When you use !!, the organization of the benchmarks is given by hand, and is intact even when is = _|_:

benchmarks _|_ = [ bench "foo" $ nf timesTwo _|_ -- _|_ !! n = _|_; nf is not strict
                 , bench "foo" $ nf timesTwo _|_ ] -- "bench"s are still there

But map breaks this:

benchmarks _|_ = map _etc _|_
               = case _|_ of -- definition of map
                      [] -> []
                      x:xs -> _etc x : map _etc xs
               = _|_ -- benchmark structure gone

Your best bet is just not using env:

main = do is <- _ -- however you calculate is
          defaultMain $ bgroup "group" $ benchmark is
HTNW
  • 27,182
  • 1
  • 32
  • 60