{-# LANGUAGE BangPatterns #-}

-- Ensure that nf' and whnf' are always optimized, even if
-- criterion-measurement is compiled with -O0 or -fprof-auto (see #184).
{-# OPTIONS_GHC -O2 -fno-prof-auto #-}
-- Make the function applications in nf' and whnf' strict (avoiding allocation)
-- and avoid floating out the computations.
{-# OPTIONS_GHC -fno-full-laziness #-}

-- |
-- Module      : Criterion.Measurement.Types.Internal
-- Copyright   : (c) 2017 Ryan Scott
--
-- License     : BSD-style
-- Maintainer  : bos@serpentine.com
-- Stability   : experimental
-- Portability : GHC
--
-- Exports 'fakeEnvironment'.
module Criterion.Measurement.Types.Internal (fakeEnvironment, nf', whnf') where

import Data.Int (Int64)

-- | A dummy environment that is passed to functions that create benchmarks
-- from environments when no concrete environment is available.
fakeEnvironment :: env
fakeEnvironment :: env
fakeEnvironment = [Char] -> env
forall a. HasCallStack => [Char] -> a
error ([Char] -> env) -> [Char] -> env
forall a b. (a -> b) -> a -> b
$ [[Char]] -> [Char]
unlines
  [ [Char]
"Criterion atttempted to retrieve a non-existent environment!"
  , [Char]
"\tPerhaps you forgot to use lazy pattern matching in a function which"
  , [Char]
"\tconstructs benchmarks from an environment?"
  , [Char]
"\t(see the documentation for `env` for details)"
  ]

-- Along with Criterion.Types.nfIO' and Criterion.Types.whnfIO', the following
-- two functions are the core benchmarking loops. They have been carefully
-- constructed to avoid allocation while also evaluating @f x@.
--
-- Because these functions are pure, GHC is particularly smart about optimizing
-- them. We must turn off @-ffull-laziness@ to prevent the computation from
-- being floated out of the loop.
--
-- For a similar reason, 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 which applies an argument to a function a
-- given number of times, reducing the result to normal form.
nf' :: (b -> ()) -> (a -> b) -> a -> (Int64 -> IO ())
nf' :: (b -> ()) -> (a -> b) -> a -> Int64 -> IO ()
nf' b -> ()
reduce a -> b
f a
x = Int64 -> IO ()
forall t (m :: * -> *). (Ord t, Num t, Monad m) => t -> m ()
go
  where
    go :: t -> m ()
go t
n | t
n t -> t -> Bool
forall a. Ord a => a -> a -> Bool
<= t
0    = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
         | Bool
otherwise = let !y :: b
y = a -> b
f a
x
                       in b -> ()
reduce b
y () -> m () -> m ()
`seq` t -> m ()
go (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1)
{-# NOINLINE nf' #-}

-- | Generate a function which applies an argument to a function a
-- given number of times.
whnf' :: (a -> b) -> a -> (Int64 -> IO ())
whnf' :: (a -> b) -> a -> Int64 -> IO ()
whnf' a -> b
f a
x = Int64 -> IO ()
forall t (m :: * -> *). (Ord t, Num t, Monad m) => t -> m ()
go
  where
    go :: t -> m ()
go t
n | t
n t -> t -> Bool
forall a. Ord a => a -> a -> Bool
<= t
0    = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
         | Bool
otherwise = a -> b
f a
x b -> m () -> m ()
`seq` t -> m ()
go (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
1)
{-# NOINLINE whnf' #-}