-
Notifications
You must be signed in to change notification settings - Fork 10
/
Copy pathcriterion.hs
142 lines (118 loc) · 4.09 KB
/
criterion.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TupleSections #-}
-- | This example requires cassava for csv parsing.
module Criterion where
import Plots
import Plots.Types.Bar
import Diagrams.Prelude
import Diagrams.Backend.Rasterific.CmdLine
import Data.Csv hiding ((.=))
import qualified Data.ByteString.Lazy as BS
import qualified Data.Vector as V
import Control.Applicative (empty)
import Data.Function (on)
import Data.List (groupBy)
import Control.Monad.State (execStateT, modify, MonadIO, liftIO)
import qualified Data.Foldable as Foldable
-- Misc stuff ----------------------------------------------------------
barAxis :: Axis B V2 Double
barAxis = r2Axis &~ hideGridLines
-- Criterion csv parsing -----------------------------------------------
data CResult = CResult
{ _name :: !String
, _mean :: !Double
, _meanLB :: !Double
, _meanUB :: !Double
, _stddev :: !Double
, _stddevLB :: !Double
, _stddevUB :: !Double
} deriving Show
makeLenses ''CResult
instance FromNamedRecord CResult where
parseNamedRecord m =
CResult <$> m .: "Name" <*> m .: "Mean" <*>
m .: "MeanLB" <*> m .: "MeanUB" <*>
m .: "Stddev" <*> m .: "StddevUB" <*>
m .: "StddevLB"
instance FromRecord CResult where
parseRecord v
| V.length v == 7 =
CResult <$> v .! 0 <*> v .! 1 <*> v .! 2 <*>
v .! 3 <*> v .! 4 <*> v .! 5 <*>
v .! 6
| otherwise = empty
-- | Read a @.csv@ file from criterion's output.
readCriterion :: MonadIO m => FilePath -> m (V.Vector CResult)
readCriterion path = liftIO $ do
csv <- BS.readFile path
let Right v = decode HasHeader csv
return v
-- | Group criterion results by name.
groupCriterion :: [CResult] -> [(String, [CResult])]
groupCriterion = map collate . groupBy ((==) `on` fst) . map splitName
where
splitName r = (a, r & name .~ tail b)
where (a,b) = break (=='/') (r ^. name)
collate [] = ("",[])
collate as@((n,_):_) = (n, map snd as)
-- Making criterion plots ----------------------------------------------
-- => BarPlotOpts n -> [a] -> (a -> [n]) -> (a -> State (PlotProperties b V2 n) ()) -> m ()
-- | Given a filepath to a criterion @.csv@ file, make an axis.
criterionAxis :: FilePath -> IO (Axis B V2 Double)
criterionAxis path = execStateT ?? barAxis $ do
results <- readCriterion path
let rss = groupCriterion (Foldable.toList results)
multiBars rss (map _mean . snd) $ do
runningBars
horizontal .= True
labelBars (rss ^.. each . _2 . each . name)
barWidth .= 0.6
onBars $ \cresults -> key (fst cresults)
minorTicks . visible .= False
xAxis . axisLabelText .= "average time (s)"
xAxis . majorGridLines . visible .= True
-- instance HasOrientation p => HasOrientation (Plot p b) where
-- orientation = rawPlot . orientation
-- Groups bars ---------------------------------------------------------
-- groupedData :: [(String, [Double])]
-- groupedData =
-- [ ( "green"
-- , [ 7, 14, 3, 17 ]
-- )
-- , ( "blue"
-- , [ 12, 8, 12, 10 ]
-- )
-- , ( "orange"
-- , [ 20, 2, 19, 7 ]
-- )
-- ]
-- groupedAxis :: Axis B V2 Double
-- groupedAxis = barAxis &~ do
-- multiBars groupedData snd $ do
-- groupedBars' 0.4
-- labelBars ["fun", "professional", "bright", "cost"]
-- barWidth *= 0.7
-- horizontal .= True
-- onBars $ \ (l,_) -> do
-- key l
-- areaStyle . mapped . _lw .= none
-- case readColourName l of
-- Just c -> plotColor .= c
-- Nothing -> error l -- return ()
-- simpleBarAxis :: Axis B V2 Double
-- simpleBarAxis = barAxis &~ do
-- Plots.Types.Bar.barPlot [5,3,6,7,2] $ orientation .= Vertical
main :: IO ()
main = do
dia <- criterionAxis "examples/criterion.csv"
r2AxisMain dia