{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE BangPatterns, CPP, ForeignFunctionInterface,
ScopedTypeVariables #-}
module Criterion.Measurement
(
initializeTime
, getTime
, getCPUTime
, getCycles
, getGCStatistics
, GCStatistics(..)
, secs
, measure
, runBenchmark
, runBenchmarkable
, runBenchmarkable_
, measured
, applyGCStatistics
, threshold
) where
import Criterion.Measurement.Types (Benchmarkable(..), Measured(..))
import Control.DeepSeq (NFData(rnf))
import Control.Exception (finally,evaluate)
import Data.Data (Data, Typeable)
import Data.Int (Int64)
import Data.List (unfoldr)
import Data.Word (Word64)
import GHC.Generics (Generic)
#if MIN_VERSION_base(4,10,0)
import GHC.Stats (RTSStats(..), GCDetails(..))
#else
import GHC.Stats (GCStats(..))
#endif
import Prelude ()
import Prelude.Compat
#if MIN_VERSION_base(4,7,0)
import System.Mem (performGC, performMinorGC)
# else
import System.Mem (performGC)
#endif
import Text.Printf (printf)
import qualified Control.Exception as Exc
import qualified Data.Vector as V
import qualified GHC.Stats as Stats
#if !(MIN_VERSION_base(4,7,0))
foreign import ccall "performGC" performMinorGC :: IO ()
#endif
data GCStatistics = GCStatistics
{
gcStatsBytesAllocated :: !Int64
, gcStatsNumGcs :: !Int64
, gcStatsMaxBytesUsed :: !Int64
, gcStatsNumByteUsageSamples :: !Int64
, gcStatsCumulativeBytesUsed :: !Int64
, gcStatsBytesCopied :: !Int64
, gcStatsCurrentBytesUsed :: !Int64
, gcStatsCurrentBytesSlop :: !Int64
, gcStatsMaxBytesSlop :: !Int64
, gcStatsPeakMegabytesAllocated :: !Int64
, gcStatsMutatorCpuSeconds :: !Double
, gcStatsMutatorWallSeconds :: !Double
, gcStatsGcCpuSeconds :: !Double
, gcStatsGcWallSeconds :: !Double
, gcStatsCpuSeconds :: !Double
, gcStatsWallSeconds :: !Double
} deriving (Eq, Read, Show, Typeable, Data, Generic)
getGCStatistics :: IO (Maybe GCStatistics)
#if MIN_VERSION_base(4,10,0)
getGCStatistics = do
stats <- Stats.getRTSStats
let gcdetails :: Stats.GCDetails
gcdetails = gc stats
nsToSecs :: Int64 -> Double
nsToSecs ns = fromIntegral ns * 1.0E-9
return $ Just GCStatistics {
gcStatsBytesAllocated = fromIntegral $ allocated_bytes stats
, gcStatsNumGcs = fromIntegral $ gcs stats
, gcStatsMaxBytesUsed = fromIntegral $ max_live_bytes stats
, gcStatsNumByteUsageSamples = fromIntegral $ major_gcs stats
, gcStatsCumulativeBytesUsed = fromIntegral $ cumulative_live_bytes stats
, gcStatsBytesCopied = fromIntegral $ copied_bytes stats
, gcStatsCurrentBytesUsed = fromIntegral $ gcdetails_live_bytes gcdetails
, gcStatsCurrentBytesSlop = fromIntegral $ gcdetails_slop_bytes gcdetails
, gcStatsMaxBytesSlop = fromIntegral $ max_slop_bytes stats
, gcStatsPeakMegabytesAllocated = fromIntegral (max_mem_in_use_bytes stats) `quot` (1024*1024)
, gcStatsMutatorCpuSeconds = nsToSecs $ mutator_cpu_ns stats
, gcStatsMutatorWallSeconds = nsToSecs $ mutator_elapsed_ns stats
, gcStatsGcCpuSeconds = nsToSecs $ gc_cpu_ns stats
, gcStatsGcWallSeconds = nsToSecs $ gc_elapsed_ns stats
, gcStatsCpuSeconds = nsToSecs $ cpu_ns stats
, gcStatsWallSeconds = nsToSecs $ elapsed_ns stats
}
`Exc.catch`
\(_::Exc.SomeException) -> return Nothing
#else
getGCStatistics = do
stats <- Stats.getGCStats
return $ Just GCStatistics {
gcStatsBytesAllocated = bytesAllocated stats
, gcStatsNumGcs = numGcs stats
, gcStatsMaxBytesUsed = maxBytesUsed stats
, gcStatsNumByteUsageSamples = numByteUsageSamples stats
, gcStatsCumulativeBytesUsed = cumulativeBytesUsed stats
, gcStatsBytesCopied = bytesCopied stats
, gcStatsCurrentBytesUsed = currentBytesUsed stats
, gcStatsCurrentBytesSlop = currentBytesSlop stats
, gcStatsMaxBytesSlop = maxBytesSlop stats
, gcStatsPeakMegabytesAllocated = peakMegabytesAllocated stats
, gcStatsMutatorCpuSeconds = mutatorCpuSeconds stats
, gcStatsMutatorWallSeconds = mutatorWallSeconds stats
, gcStatsGcCpuSeconds = gcCpuSeconds stats
, gcStatsGcWallSeconds = gcWallSeconds stats
, gcStatsCpuSeconds = cpuSeconds stats
, gcStatsWallSeconds = wallSeconds stats
}
`Exc.catch`
\(_::Exc.SomeException) -> return Nothing
#endif
measure :: Benchmarkable
-> Int64
-> IO (Measured, Double)
measure bm iters = runBenchmarkable bm iters addResults $ \ !n act -> do
performMinorGC
initializeTime
startStats <- getGCStatistics
startTime <- getTime
startCpuTime <- getCPUTime
startCycles <- getCycles
act
endTime <- getTime
endCpuTime <- getCPUTime
endCycles <- getCycles
endStatsPreGC <- getGCStatistics
performMinorGC
endStatsPostGC <- getGCStatistics
let !m = applyGCStatistics endStatsPostGC endStatsPreGC startStats $ measured {
measTime = max 0 (endTime - startTime)
, measCpuTime = max 0 (endCpuTime - startCpuTime)
, measCycles = max 0 (fromIntegral (endCycles - startCycles))
, measIters = n
}
return (m, endTime)
where
addResults :: (Measured, Double) -> (Measured, Double) -> (Measured, Double)
addResults (!m1, _) (!m2, !d2) = (m3, d2)
where
add f = f m1 + f m2
m3 = Measured
{ measTime = add measTime
, measCpuTime = add measCpuTime
, measCycles = add measCycles
, measIters = add measIters
, measAllocated = add measAllocated
, measNumGcs = add measNumGcs
, measBytesCopied = add measBytesCopied
, measMutatorWallSeconds = add measMutatorWallSeconds
, measMutatorCpuSeconds = add measMutatorCpuSeconds
, measGcWallSeconds = add measGcWallSeconds
, measGcCpuSeconds = add measGcCpuSeconds
}
{-# INLINE measure #-}
threshold :: Double
threshold = 0.03
{-# INLINE threshold #-}
runBenchmarkable :: Benchmarkable -> Int64 -> (a -> a -> a) -> (Int64 -> IO () -> IO a) -> IO a
runBenchmarkable Benchmarkable{..} i comb f
| perRun = work >>= go (i - 1)
| otherwise = work
where
go 0 result = return result
go !n !result = work >>= go (n - 1) . comb result
count | perRun = 1
| otherwise = i
work = do
env <- allocEnv count
let clean = cleanEnv count env
run = runRepeatedly env count
clean `seq` run `seq` evaluate $ rnf env
f count run `finally` clean
{-# INLINE work #-}
{-# INLINE runBenchmarkable #-}
runBenchmarkable_ :: Benchmarkable -> Int64 -> IO ()
runBenchmarkable_ bm i = runBenchmarkable bm i (\() () -> ()) (const id)
{-# INLINE runBenchmarkable_ #-}
runBenchmark :: Benchmarkable
-> Double
-> IO (V.Vector Measured, Double)
runBenchmark bm timeLimit = do
initializeTime
runBenchmarkable_ bm 1
start <- performGC >> getTime
let loop [] !_ !_ _ = error "unpossible!"
loop (iters:niters) prev count acc = do
(m, endTime) <- measure bm iters
let overThresh = max 0 (measTime m - threshold) + prev
if endTime - start >= timeLimit &&
overThresh > threshold * 10 &&
count >= (4 :: Int)
then do
let !v = V.reverse (V.fromList acc)
return (v, endTime - start)
else loop niters overThresh (count+1) (m:acc)
loop (squish (unfoldr series 1)) 0 0 []
squish :: (Eq a) => [a] -> [a]
squish ys = foldr go [] ys
where go x xs = x : dropWhile (==x) xs
series :: Double -> Maybe (Int64, Double)
series k = Just (truncate l, l)
where l = k * 1.05
measured :: Measured
measured = Measured {
measTime = 0
, measCpuTime = 0
, measCycles = 0
, measIters = 0
, measAllocated = minBound
, measNumGcs = minBound
, measBytesCopied = minBound
, measMutatorWallSeconds = bad
, measMutatorCpuSeconds = bad
, measGcWallSeconds = bad
, measGcCpuSeconds = bad
} where bad = -1/0
applyGCStatistics :: Maybe GCStatistics
-> Maybe GCStatistics
-> Maybe GCStatistics
-> Measured
-> Measured
applyGCStatistics (Just endPostGC) (Just endPreGC) (Just start) m = m {
measAllocated = diff endPostGC gcStatsBytesAllocated
, measNumGcs = diff endPreGC gcStatsNumGcs
, measBytesCopied = diff endPostGC gcStatsBytesCopied
, measMutatorWallSeconds = diff endPostGC gcStatsMutatorWallSeconds
, measMutatorCpuSeconds = diff endPostGC gcStatsMutatorCpuSeconds
, measGcWallSeconds = diff endPreGC gcStatsGcWallSeconds
, measGcCpuSeconds = diff endPreGC gcStatsGcCpuSeconds
} where diff a f = f a - f start
applyGCStatistics _ _ _ m = m
secs :: Double -> String
secs k
| k < 0 = '-' : secs (-k)
| k >= 1 = k `with` "s"
| k >= 1e-3 = (k*1e3) `with` "ms"
| k >= 1e-6 = (k*1e6) `with` "μs"
| k >= 1e-9 = (k*1e9) `with` "ns"
| k >= 1e-12 = (k*1e12) `with` "ps"
| k >= 1e-15 = (k*1e15) `with` "fs"
| k >= 1e-18 = (k*1e18) `with` "as"
| otherwise = printf "%g s" k
where with (t :: Double) (u :: String)
| t >= 1e9 = printf "%.4g %s" t u
| t >= 1e3 = printf "%.0f %s" t u
| t >= 1e2 = printf "%.1f %s" t u
| t >= 1e1 = printf "%.2f %s" t u
| otherwise = printf "%.3f %s" t u
foreign import ccall unsafe "criterion_inittime" initializeTime :: IO ()
foreign import ccall unsafe "criterion_rdtsc" getCycles :: IO Word64
foreign import ccall unsafe "criterion_gettime" getTime :: IO Double
foreign import ccall unsafe "criterion_getcputime" getCPUTime :: IO Double