module PlotTest where
import Prelude hiding (lines)
import Data.List (unfoldr)
import Data.Word (Word8)
import Data.Maybe
import Data.Accessor
import Data.Colour
import Data.Colour.Names
import Graphics.Rendering.Chart
import Graphics.Rendering.Chart.Grid
import Graphics.Rendering.Chart.Gtk
import Criterion
import Criterion.Environment
import Criterion.Monad
import Criterion.Types
import Criterion.Config
import Control.Monad
import Control.Monad.Trans
import Control.Monad.Trans.Reader
import Statistics.Types
import qualified System.Random as R
randomWord8s :: [Word8]
randomWord8s = map fromIntegral $ unfoldr (Just . R.next) (R.mkStdGen 666)
main :: IO ()
main = undefined
type MyCriterion a = ReaderT Environment Criterion a
runFlattenedBenchmarks :: [Benchmark] -> MyCriterion [([String],Sample)]
runFlattenedBenchmarks =
(concat `liftM`) . mapM (go id)
where
go path (Benchmark name b) = do
env <- ask
sample <- lift $ runBenchmark env b
return [(path [name], sample)]
go path (BenchGroup name bs) =
concat `liftM` mapM (go (path . (name:))) bs
runSeriesBenchmark :: (a -> Benchmark) -> [a] -> MyCriterion [(a,Sample)]
runSeriesBenchmark mkBench xs =
(zip xs . map snd) `liftM` runFlattenedBenchmarks (map mkBench xs)
runMyCriterion :: Config -> MyCriterion a -> IO a
runMyCriterion config criterion = do
env <- withConfig config measureEnvironment
withConfig config (runReaderT criterion env)
colorPalette :: [Colour Double]
colorPalette = [blue, green, red, yellow, magenta, cyan]
lineStylePalette :: [CairoLineStyle]
lineStylePalette =
map (solidLine 1 . opaque) colorPalette ++
map (dashedLine 1 [5, 5] . opaque) colorPalette
type PlotData = ((String, String, String), [(String, [(Int, Double)])])
layoutPlot :: PlotData -> Layout1 Int Double
layoutPlot ((title, xName, yName), lines) =
layout1_plots ^= map (Right . toPlot) plots $
layout1_title ^= title $
layout1_bottom_axis ^= mkLinearAxis xName $
layout1_right_axis ^= mkLogAxis yName $
defaultLayout1
where
(linesName, linesData) = unzip lines
plots = zipWith3 plotLine linesName (cycle lineStylePalette) linesData
plotLine :: String -> CairoLineStyle -> [(Int,Double)] -> PlotLines Int Double
plotLine name style points =
plot_lines_title ^= name $
plot_lines_style ^= style $
plot_lines_values ^= [points] $
defaultPlotLines
mkLinearAxis :: String -> LayoutAxis Int
mkLinearAxis name = laxis_title ^= name $ defaultLayoutAxis
mkLogAxis :: String -> LayoutAxis Double
mkLogAxis name =
laxis_title ^= name $
laxis_generate ^= autoScaledLogAxis defaultLogAxis $
defaultLayoutAxis