{-# LANGUAGE RecordWildCards #-}
module Benchmark.Types
( RaazBench
, toBenchmarkable
, nBytes
, nRuns
, runRaazBench
, header
) where
import Criterion.Measurement
import Criterion.Measurement.Types hiding (measure)
import Data.Int
import Text.PrettyPrint
import Raaz.Core
nBytes :: BYTES Int
nBytes :: BYTES Int
nBytes = BYTES Int
32 forall a. Num a => a -> a -> a
* BYTES Int
1024
nRuns :: Int64
nRuns :: Int64
nRuns = Int64
10000
type RaazBench = (String, Benchmarkable)
header :: Doc
= [Doc] -> Doc
hsep forall a b. (a -> b) -> a -> b
$ Doc -> [Doc] -> [Doc]
punctuate Doc
comma forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map String -> Doc
text
[ String
"Implementation"
, String
"time"
, String
"cycles"
, String
"rate (bits/sec)"
, String
"time/byte"
, String
"cycles/byte"
]
runRaazBench :: RaazBench -> IO Doc
runRaazBench :: RaazBench -> IO Doc
runRaazBench (String
nm, Benchmarkable
bm) = do
(Measured
memt,Double
_) <- Benchmarkable -> Int64 -> IO (Measured, Double)
measure Benchmarkable
bm Int64
nRuns
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Doc] -> Doc
hsep forall a b. (a -> b) -> a -> b
$ Doc -> [Doc] -> [Doc]
punctuate Doc
comma forall a b. (a -> b) -> a -> b
$ String -> Doc
text String
nm forall a. a -> [a] -> [a]
: Measured -> [Doc]
pprMeasured Measured
memt
pprMeasured :: Measured -> [Doc]
pprMeasured :: Measured -> [Doc]
pprMeasured Measured{Double
Int64
measTime :: Measured -> Double
measCpuTime :: Measured -> Double
measCycles :: Measured -> Int64
measIters :: Measured -> Int64
measAllocated :: Measured -> Int64
measPeakMbAllocated :: Measured -> Int64
measNumGcs :: Measured -> Int64
measBytesCopied :: Measured -> Int64
measMutatorWallSeconds :: Measured -> Double
measMutatorCpuSeconds :: Measured -> Double
measGcWallSeconds :: Measured -> Double
measGcCpuSeconds :: Measured -> Double
measGcCpuSeconds :: Double
measGcWallSeconds :: Double
measMutatorCpuSeconds :: Double
measMutatorWallSeconds :: Double
measBytesCopied :: Int64
measNumGcs :: Int64
measPeakMbAllocated :: Int64
measAllocated :: Int64
measIters :: Int64
measCycles :: Int64
measCpuTime :: Double
measTime :: Double
..} =
[ String -> Doc
text (Double -> String
secs Double
tm)
, String -> Doc
text (Double -> String
humanise Double
cy)
, String -> Doc
text String
rt
, String -> Doc
text String
secB
, String -> Doc
text (Double -> String
humanise Double
cycB)
]
where tm :: Double
tm = Double
measTime forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
nRuns
cy :: Double
cy = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
measCycles forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
nRuns
bytes :: Double
bytes = forall a b. (Integral a, Num b) => a -> b
fromIntegral BYTES Int
nBytes
secB :: String
secB = Double -> String
humanise (Double
tm forall a. Fractional a => a -> a -> a
/ Double
bytes) forall a. [a] -> [a] -> [a]
++ String
"s"
cycB :: Double
cycB = Double
cy forall a. Fractional a => a -> a -> a
/ Double
bytes
rt :: String
rt = Double -> String
humanise forall a b. (a -> b) -> a -> b
$ Double
8 forall a. Num a => a -> a -> a
* Double
bytes forall a. Fractional a => a -> a -> a
/ Double
tm
humanise :: Double -> String
humanise :: Double -> String
humanise Double
u | Double
u forall a. Ord a => a -> a -> Bool
< Double
1 = Int -> Double -> String
goL Int
0 Double
u
| Bool
otherwise = Int -> Double -> String
goU Int
0 Double
u
where goL :: Int -> Double -> String
goL Int
e Double
x | Double
x forall a. Ord a => a -> a -> Bool
> Double
1 Bool -> Bool -> Bool
|| Int
e forall a. Eq a => a -> a -> Bool
== -Int
3 = Int -> Double -> String
restrictDecimals Int
2 Double
x forall a. [a] -> [a] -> [a]
++ Int -> String
unitPrefix Int
e
| Bool
otherwise = Int -> Double -> String
goL (Int
e forall a. Num a => a -> a -> a
- Int
1) (Double
x forall a. Num a => a -> a -> a
* Double
1000)
goU :: Int -> Double -> String
goU Int
e Double
x | Double
x forall a. Ord a => a -> a -> Bool
< Double
100 Bool -> Bool -> Bool
|| Int
e forall a. Eq a => a -> a -> Bool
== Int
5 = Int -> Double -> String
restrictDecimals Int
2 Double
x forall a. [a] -> [a] -> [a]
++ Int -> String
unitPrefix Int
e
| Bool
otherwise = Int -> Double -> String
goU (Int
e forall a. Num a => a -> a -> a
+ Int
1) (Double
x forall a. Fractional a => a -> a -> a
/ Double
1000)
restrictDecimals :: Int -> Double -> String
restrictDecimals :: Int -> Double -> String
restrictDecimals Int
n Double
x = String
u forall a. [a] -> [a] -> [a]
++ forall a. Int -> [a] -> [a]
take (Int
nforall a. Num a => a -> a -> a
+Int
1) String
v
where (String
u,String
v) = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Eq a => a -> a -> Bool
/= Char
'.') forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Double
x
unitPrefix :: Int -> String
unitPrefix :: Int -> String
unitPrefix Int
ex
| Int
ex forall a. Ord a => a -> a -> Bool
< -Int
3 = forall a. HasCallStack => String -> a
error String
"exponent too small name"
| Int
ex forall a. Eq a => a -> a -> Bool
== -Int
3 = String
"n"
| Int
ex forall a. Eq a => a -> a -> Bool
== -Int
2 = String
"µ"
| Int
ex forall a. Eq a => a -> a -> Bool
== -Int
1 = String
"m"
| Int
ex forall a. Eq a => a -> a -> Bool
== Int
0 = String
""
| Int
ex forall a. Eq a => a -> a -> Bool
== Int
1 = String
"K"
| Int
ex forall a. Eq a => a -> a -> Bool
== Int
2 = String
"M"
| Int
ex forall a. Eq a => a -> a -> Bool
== Int
3 = String
"G"
| Int
ex forall a. Eq a => a -> a -> Bool
== Int
4 = String
"T"
| Int
ex forall a. Eq a => a -> a -> Bool
== Int
5 = String
"P"
| Bool
otherwise = forall a. HasCallStack => String -> a
error String
"exponent to large to name"