{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
module Crypto.Lol.Utils.PrettyPrint
( getTableName
, getBenchParams
, getBenchLvl
, getBenchFunc
, getReports
, getRuntime
, col
, testName
, OptsInternal(..)
, Verb(..)
) where
import Control.Monad (foldM, when)
import Control.Monad.IO.Class (liftIO)
import Criterion.Internal (runAndAnalyseOne)
import Criterion.Main.Options (defaultConfig)
import Criterion.Measurement (initializeTime, secs)
import Criterion.Monad (Criterion, withConfig)
import Criterion.Types
import qualified Data.Map as Map
import Statistics.Types (Estimate (..))
data Verb = Progress
| Abridged
| Full
deriving (Eq)
data OptsInternal = OptsInternal
{verb :: Verb,
levels :: [String],
benches :: [String],
params :: [String],
redThreshold :: Double,
colWidth :: Int,
testNameWidth :: Int}
col, testName :: OptsInternal -> String
testName OptsInternal{..} = "%-" ++ show testNameWidth ++ "s "
col OptsInternal{..} = "%-" ++ show colWidth ++ "s "
wordBy :: Int -> String -> String
wordBy 0 = takeWhile (/= '/')
wordBy i = wordBy (i-1) . tail . dropWhile (/= '/')
getTableName :: String -> String
getTableName = wordBy 0
getBenchParams :: String -> String
getBenchParams = wordBy 1
getBenchLvl :: String -> String
getBenchLvl = wordBy 2
getBenchFunc :: String -> String
getBenchFunc = wordBy 3
getReports :: OptsInternal -> Benchmark -> IO [Report]
getReports o = withConfig (config o) . summarizeBenchReports o
config :: OptsInternal -> Config
config OptsInternal{..} = defaultConfig {verbosity = if verb == Full then Normal else Quiet}
summarizeBenchReports :: OptsInternal -> Benchmark -> Criterion [Report]
summarizeBenchReports OptsInternal{..} b = do
liftIO initializeTime
snd <$> go (0, []) ("", b)
where
select name =
let param = getBenchParams name
lvl = getBenchLvl name
func = getBenchFunc name
in (lvl `elem` levels) && (func `elem` benches) && (param `elem` params)
go r@(rptIdx, reports) (benchPrefix, Benchmark desc b') |
select benchName = do
when (verb == Abridged || verb == Full) $ liftIO $ putStr $ "benchmark " ++ benchName
when (verb == Full) $ liftIO $ putStrLn ""
dr <- runAndAnalyseOne rptIdx benchName b'
case dr of
Measurement{} -> error "PrettyPrint Measurement"
(Analysed rpt) -> do
when (verb == Progress) $ liftIO $ putStr "."
when (verb == Abridged) $ liftIO $ putStrLn $ "..." ++ secs (getRuntime rpt)
return (rptIdx, rpt:reports)
|
otherwise = do
liftIO $ putStrLn benchName
return r
where benchName = addPrefix benchPrefix desc
go r (benchPrefix, BenchGroup desc bs) =
let lvlName = addPrefix benchPrefix desc
bs' = map (lvlName,) bs
in foldM go r bs'
getRuntime :: Report -> Double
getRuntime Report{..} =
let SampleAnalysis{..} = reportAnalysis
Regression{..} = head anRegress
Estimate{..} = regCoeffs Map.! "iters"
in estPoint