{-# LANGUAGE MultiParamTypeClasses #-}
module Simulation.Aivika.Experiment.Chart.XYChartView
(XYChartView(..),
defaultXYChartView) where
import Control.Monad
import Control.Monad.Trans
import Control.Lens
import qualified Data.Map as M
import Data.IORef
import Data.Maybe
import Data.Either
import Data.Array
import Data.Monoid
import Data.List
import Data.Default.Class
import System.IO
import System.FilePath
import Graphics.Rendering.Chart
import Simulation.Aivika
import Simulation.Aivika.Experiment
import Simulation.Aivika.Experiment.Base
import Simulation.Aivika.Experiment.Chart.Types
import Simulation.Aivika.Experiment.Chart.Utils (colourisePlotLines)
data XYChartView =
XYChartView { XYChartView -> String
xyChartTitle :: String,
XYChartView -> String
xyChartDescription :: String,
XYChartView -> Int
xyChartWidth :: Int,
XYChartView -> Int
xyChartHeight :: Int,
XYChartView -> Maybe Int
xyChartGridSize :: Maybe Int,
XYChartView -> ExperimentFilePath
xyChartFileName :: ExperimentFilePath,
XYChartView -> Event Bool
xyChartPredicate :: Event Bool,
XYChartView -> ResultTransform
xyChartTransform :: ResultTransform,
XYChartView -> ResultTransform
xyChartXSeries :: ResultTransform,
XYChartView -> ResultTransform
xyChartLeftYSeries :: ResultTransform,
XYChartView -> ResultTransform
xyChartRightYSeries :: ResultTransform,
XYChartView -> String
xyChartPlotTitle :: String,
XYChartView -> String
xyChartRunPlotTitle :: String,
XYChartView -> [PlotLines Double Double -> PlotLines Double Double]
xyChartPlotLines :: [PlotLines Double Double ->
PlotLines Double Double],
XYChartView -> LayoutAxis Double -> LayoutAxis Double
xyChartBottomAxis :: LayoutAxis Double ->
LayoutAxis Double,
XYChartView
-> LayoutLR Double Double Double -> LayoutLR Double Double Double
xyChartLayout :: LayoutLR Double Double Double ->
LayoutLR Double Double Double
}
defaultXYChartView :: XYChartView
defaultXYChartView :: XYChartView
defaultXYChartView =
XYChartView { xyChartTitle :: String
xyChartTitle = String
"XY Chart",
xyChartDescription :: String
xyChartDescription = String
"It shows the XY chart(s).",
xyChartWidth :: Int
xyChartWidth = Int
640,
xyChartHeight :: Int
xyChartHeight = Int
480,
xyChartGridSize :: Maybe Int
xyChartGridSize = forall a. a -> Maybe a
Just (Int
2 forall a. Num a => a -> a -> a
* Int
640),
xyChartFileName :: ExperimentFilePath
xyChartFileName = String -> ExperimentFilePath
UniqueFilePath String
"XYChart($RUN_INDEX)",
xyChartPredicate :: Event Bool
xyChartPredicate = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True,
xyChartTransform :: ResultTransform
xyChartTransform = forall a. a -> a
id,
xyChartXSeries :: ResultTransform
xyChartXSeries = forall a. Monoid a => a
mempty,
xyChartLeftYSeries :: ResultTransform
xyChartLeftYSeries = forall a. Monoid a => a
mempty,
xyChartRightYSeries :: ResultTransform
xyChartRightYSeries = forall a. Monoid a => a
mempty,
xyChartPlotTitle :: String
xyChartPlotTitle = String
"$TITLE",
xyChartRunPlotTitle :: String
xyChartRunPlotTitle = String
"$PLOT_TITLE / Run $RUN_INDEX of $RUN_COUNT",
xyChartPlotLines :: [PlotLines Double Double -> PlotLines Double Double]
xyChartPlotLines = forall x y. [PlotLines x y -> PlotLines x y]
colourisePlotLines,
xyChartBottomAxis :: LayoutAxis Double -> LayoutAxis Double
xyChartBottomAxis = forall a. a -> a
id,
xyChartLayout :: LayoutLR Double Double Double -> LayoutLR Double Double Double
xyChartLayout = forall a. a -> a
id }
instance ChartRendering r => ExperimentView XYChartView (WebPageRenderer r) where
outputView :: XYChartView -> ExperimentGenerator (WebPageRenderer r)
outputView XYChartView
v =
let reporter :: Experiment
-> WebPageRenderer r
-> String
-> ExperimentWriter (ExperimentReporter (WebPageRenderer a))
reporter Experiment
exp (WebPageRenderer r
renderer ExperimentFilePath
_) String
dir =
do XYChartViewState r
st <- forall r.
ChartRendering r =>
XYChartView
-> Experiment
-> r
-> String
-> ExperimentWriter (XYChartViewState r)
newXYChart XYChartView
v Experiment
exp r
renderer String
dir
let context :: ExperimentContext (WebPageRenderer a)
context =
forall a. WebPageWriter -> ExperimentContext (WebPageRenderer a)
WebPageContext forall a b. (a -> b) -> a -> b
$
WebPageWriter { reporterWriteTOCHtml :: Int -> HtmlWriter ()
reporterWriteTOCHtml = forall r. XYChartViewState r -> Int -> HtmlWriter ()
xyChartTOCHtml XYChartViewState r
st,
reporterWriteHtml :: Int -> HtmlWriter ()
reporterWriteHtml = forall r. XYChartViewState r -> Int -> HtmlWriter ()
xyChartHtml XYChartViewState r
st }
forall (m :: * -> *) a. Monad m => a -> m a
return ExperimentReporter { reporterInitialise :: ExperimentMonad (WebPageRenderer a) ()
reporterInitialise = forall (m :: * -> *) a. Monad m => a -> m a
return (),
reporterFinalise :: ExperimentMonad (WebPageRenderer a) ()
reporterFinalise = forall (m :: * -> *) a. Monad m => a -> m a
return (),
reporterSimulate :: ExperimentData -> Composite ()
reporterSimulate = forall r.
ChartRendering r =>
XYChartViewState r -> ExperimentData -> Composite ()
simulateXYChart XYChartViewState r
st,
reporterContext :: ExperimentContext (WebPageRenderer a)
reporterContext = forall {a}. ExperimentContext (WebPageRenderer a)
context }
in ExperimentGenerator { generateReporter :: Experiment
-> WebPageRenderer r
-> ExperimentEnvironment (WebPageRenderer r)
-> ExperimentMonad
(WebPageRenderer r) (ExperimentReporter (WebPageRenderer r))
generateReporter = forall {r} {a}.
ChartRendering r =>
Experiment
-> WebPageRenderer r
-> String
-> ExperimentWriter (ExperimentReporter (WebPageRenderer a))
reporter }
instance ChartRendering r => ExperimentView XYChartView (FileRenderer r) where
outputView :: XYChartView -> ExperimentGenerator (FileRenderer r)
outputView XYChartView
v =
let reporter :: Experiment
-> FileRenderer r
-> String
-> ExperimentWriter (ExperimentReporter (FileRenderer a))
reporter Experiment
exp (FileRenderer r
renderer ExperimentFilePath
_) String
dir =
do XYChartViewState r
st <- forall r.
ChartRendering r =>
XYChartView
-> Experiment
-> r
-> String
-> ExperimentWriter (XYChartViewState r)
newXYChart XYChartView
v Experiment
exp r
renderer String
dir
forall (m :: * -> *) a. Monad m => a -> m a
return ExperimentReporter { reporterInitialise :: ExperimentMonad (FileRenderer a) ()
reporterInitialise = forall (m :: * -> *) a. Monad m => a -> m a
return (),
reporterFinalise :: ExperimentMonad (FileRenderer a) ()
reporterFinalise = forall (m :: * -> *) a. Monad m => a -> m a
return (),
reporterSimulate :: ExperimentData -> Composite ()
reporterSimulate = forall r.
ChartRendering r =>
XYChartViewState r -> ExperimentData -> Composite ()
simulateXYChart XYChartViewState r
st,
reporterContext :: ExperimentContext (FileRenderer a)
reporterContext = forall a. ExperimentContext (FileRenderer a)
FileContext }
in ExperimentGenerator { generateReporter :: Experiment
-> FileRenderer r
-> ExperimentEnvironment (FileRenderer r)
-> ExperimentMonad
(FileRenderer r) (ExperimentReporter (FileRenderer r))
generateReporter = forall {r} {a}.
ChartRendering r =>
Experiment
-> FileRenderer r
-> String
-> ExperimentWriter (ExperimentReporter (FileRenderer a))
reporter }
data XYChartViewState r =
XYChartViewState { forall r. XYChartViewState r -> XYChartView
xyChartView :: XYChartView,
forall r. XYChartViewState r -> Experiment
xyChartExperiment :: Experiment,
forall r. XYChartViewState r -> r
xyChartRenderer :: r,
forall r. XYChartViewState r -> String
xyChartDir :: FilePath,
forall r. XYChartViewState r -> Map Int String
xyChartMap :: M.Map Int FilePath }
newXYChart :: ChartRendering r => XYChartView -> Experiment -> r -> FilePath -> ExperimentWriter (XYChartViewState r)
newXYChart :: forall r.
ChartRendering r =>
XYChartView
-> Experiment
-> r
-> String
-> ExperimentWriter (XYChartViewState r)
newXYChart XYChartView
view Experiment
exp r
renderer String
dir =
do let n :: Int
n = Experiment -> Int
experimentRunCount Experiment
exp
[String]
fs <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Int
0..(Int
n forall a. Num a => a -> a -> a
- Int
1)] forall a b. (a -> b) -> a -> b
$ \Int
i ->
String -> ExperimentFilePath -> ExperimentWriter String
resolveFilePath String
dir forall a b. (a -> b) -> a -> b
$
(String -> String) -> ExperimentFilePath -> ExperimentFilePath
mapFilePath (forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> String -> String
replaceExtension forall a b. (a -> b) -> a -> b
$ forall r. ChartRendering r => r -> String
renderableChartExtension r
renderer) forall a b. (a -> b) -> a -> b
$
ExperimentFilePath -> Map String String -> ExperimentFilePath
expandFilePath (XYChartView -> ExperimentFilePath
xyChartFileName XYChartView
view) forall a b. (a -> b) -> a -> b
$
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(String
"$TITLE", XYChartView -> String
xyChartTitle XYChartView
view),
(String
"$RUN_INDEX", forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ Int
i forall a. Num a => a -> a -> a
+ Int
1),
(String
"$RUN_COUNT", forall a. Show a => a -> String
show Int
n)]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [String]
fs forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> String -> IO ()
writeFile []
let m :: Map Int String
m = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0..(Int
n forall a. Num a => a -> a -> a
- Int
1)] [String]
fs
forall (m :: * -> *) a. Monad m => a -> m a
return XYChartViewState { xyChartView :: XYChartView
xyChartView = XYChartView
view,
xyChartExperiment :: Experiment
xyChartExperiment = Experiment
exp,
xyChartRenderer :: r
xyChartRenderer = r
renderer,
xyChartDir :: String
xyChartDir = String
dir,
xyChartMap :: Map Int String
xyChartMap = Map Int String
m }
simulateXYChart :: ChartRendering r => XYChartViewState r -> ExperimentData -> Composite ()
simulateXYChart :: forall r.
ChartRendering r =>
XYChartViewState r -> ExperimentData -> Composite ()
simulateXYChart XYChartViewState r
st ExperimentData
expdata =
do let view :: XYChartView
view = forall r. XYChartViewState r -> XYChartView
xyChartView XYChartViewState r
st
loc :: [ResultId] -> String
loc = ResultLocalisation -> [ResultId] -> String
localisePathResultTitle forall a b. (a -> b) -> a -> b
$
Experiment -> ResultLocalisation
experimentLocalisation forall a b. (a -> b) -> a -> b
$
forall r. XYChartViewState r -> Experiment
xyChartExperiment XYChartViewState r
st
rs0 :: Results
rs0 = XYChartView -> ResultTransform
xyChartXSeries XYChartView
view forall a b. (a -> b) -> a -> b
$
XYChartView -> ResultTransform
xyChartTransform XYChartView
view forall a b. (a -> b) -> a -> b
$
ExperimentData -> Results
experimentResults ExperimentData
expdata
rs1 :: Results
rs1 = XYChartView -> ResultTransform
xyChartLeftYSeries XYChartView
view forall a b. (a -> b) -> a -> b
$
XYChartView -> ResultTransform
xyChartTransform XYChartView
view forall a b. (a -> b) -> a -> b
$
ExperimentData -> Results
experimentResults ExperimentData
expdata
rs2 :: Results
rs2 = XYChartView -> ResultTransform
xyChartRightYSeries XYChartView
view forall a b. (a -> b) -> a -> b
$
XYChartView -> ResultTransform
xyChartTransform XYChartView
view forall a b. (a -> b) -> a -> b
$
ExperimentData -> Results
experimentResults ExperimentData
expdata
ext0 :: ResultValue Double
ext0 =
case Results -> [ResultValue Double]
resultsToDoubleValues Results
rs0 of
[ResultValue Double
x] -> ResultValue Double
x
[ResultValue Double]
_ -> forall a. HasCallStack => String -> a
error String
"Expected to see a single X series: simulateXYChart"
exts1 :: [ResultValue Double]
exts1 = Results -> [ResultValue Double]
resultsToDoubleValues Results
rs1
exts2 :: [ResultValue Double]
exts2 = Results -> [ResultValue Double]
resultsToDoubleValues Results
rs2
signals :: ResultPredefinedSignals
signals = ExperimentData -> ResultPredefinedSignals
experimentPredefinedSignals ExperimentData
expdata
n :: Int
n = Experiment -> Int
experimentRunCount forall a b. (a -> b) -> a -> b
$ forall r. XYChartViewState r -> Experiment
xyChartExperiment XYChartViewState r
st
width :: Int
width = XYChartView -> Int
xyChartWidth XYChartView
view
height :: Int
height = XYChartView -> Int
xyChartHeight XYChartView
view
predicate :: Event Bool
predicate = XYChartView -> Event Bool
xyChartPredicate XYChartView
view
title :: String
title = XYChartView -> String
xyChartTitle XYChartView
view
plotTitle :: String
plotTitle = XYChartView -> String
xyChartPlotTitle XYChartView
view
runPlotTitle :: String
runPlotTitle = XYChartView -> String
xyChartRunPlotTitle XYChartView
view
plotLines :: [PlotLines Double Double -> PlotLines Double Double]
plotLines = XYChartView -> [PlotLines Double Double -> PlotLines Double Double]
xyChartPlotLines XYChartView
view
plotBottomAxis :: LayoutAxis Double -> LayoutAxis Double
plotBottomAxis = XYChartView -> LayoutAxis Double -> LayoutAxis Double
xyChartBottomAxis XYChartView
view
plotLayout :: LayoutLR Double Double Double -> LayoutLR Double Double Double
plotLayout = XYChartView
-> LayoutLR Double Double Double -> LayoutLR Double Double Double
xyChartLayout XYChartView
view
renderer :: r
renderer = forall r. XYChartViewState r -> r
xyChartRenderer XYChartViewState r
st
Int
i <- forall (m :: * -> *) a. ParameterLift m => Parameter a -> m a
liftParameter Parameter Int
simulationIndex
let file :: String
file = forall a. HasCallStack => Maybe a -> a
fromJust forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Int
i forall a. Num a => a -> a -> a
- Int
1) (forall r. XYChartViewState r -> Map Int String
xyChartMap XYChartViewState r
st)
plotTitle' :: String
plotTitle' =
String -> String -> String -> String
replace String
"$TITLE" String
title
String
plotTitle
runPlotTitle' :: String
runPlotTitle' =
if Int
n forall a. Eq a => a -> a -> Bool
== Int
1
then String
plotTitle'
else String -> String -> String -> String
replace String
"$RUN_INDEX" (forall a. Show a => a -> String
show Int
i) forall a b. (a -> b) -> a -> b
$
String -> String -> String -> String
replace String
"$RUN_COUNT" (forall a. Show a => a -> String
show Int
n) forall a b. (a -> b) -> a -> b
$
String -> String -> String -> String
replace String
"$PLOT_TITLE" String
plotTitle'
String
runPlotTitle
inputSignal :: ResultValue e -> m (Signal ())
inputSignal ResultValue e
ext =
case XYChartView -> Maybe Int
xyChartGridSize XYChartView
view of
Just Int
m ->
forall (m :: * -> *) a. EventLift m => Event a -> m a
liftEvent forall a b. (a -> b) -> a -> b
$
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. (a -> b) -> Signal a -> Signal b
mapSignal forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const ()) forall a b. (a -> b) -> a -> b
$
Int -> Event (Signal Int)
newSignalInTimeGrid Int
m
Maybe Int
Nothing ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
ResultPredefinedSignals -> ResultSignal -> Signal ()
pureResultSignal ResultPredefinedSignals
signals forall a b. (a -> b) -> a -> b
$
forall e. ResultValue e -> ResultSignal
resultValueSignal ResultValue e
ext
inputHistory :: t (ResultValue e) -> Composite (t (SignalHistory (Double, e)))
inputHistory t (ResultValue e)
exts =
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM t (ResultValue e)
exts forall a b. (a -> b) -> a -> b
$ \ResultValue e
ext ->
do let x :: ResultData Double
x = forall e. ResultValue e -> ResultData e
resultValueData ResultValue Double
ext0
y :: ResultData e
y = forall e. ResultValue e -> ResultData e
resultValueData ResultValue e
ext
transform :: () -> Event (Double, e)
transform () =
do Bool
p <- Event Bool
predicate
if Bool
p
then forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (,) ResultData Double
x ResultData e
y
else forall (m :: * -> *) a. Monad m => a -> m a
return (Double
1forall a. Fractional a => a -> a -> a
/Double
0, e
1forall a. Fractional a => a -> a -> a
/e
0)
signalx :: ResultSignal
signalx = forall e. ResultValue e -> ResultSignal
resultValueSignal ResultValue Double
ext0
signaly :: ResultSignal
signaly = forall e. ResultValue e -> ResultSignal
resultValueSignal ResultValue e
ext
Signal ()
s <- forall {m :: * -> *} {e}.
(EventLift m, Monad m) =>
ResultValue e -> m (Signal ())
inputSignal ResultValue e
ext
forall a. Signal a -> Composite (SignalHistory a)
newSignalHistory forall a b. (a -> b) -> a -> b
$
forall a b. (a -> Event b) -> Signal a -> Signal b
mapSignalM () -> Event (Double, e)
transform Signal ()
s
[SignalHistory (Double, Double)]
hs1 <- forall {t :: * -> *} {e}.
(Traversable t, Fractional e) =>
t (ResultValue e) -> Composite (t (SignalHistory (Double, e)))
inputHistory [ResultValue Double]
exts1
[SignalHistory (Double, Double)]
hs2 <- forall {t :: * -> *} {e}.
(Traversable t, Fractional e) =>
t (ResultValue e) -> Composite (t (SignalHistory (Double, e)))
inputHistory [ResultValue Double]
exts2
DisposableEvent -> Composite ()
disposableComposite forall a b. (a -> b) -> a -> b
$
Event () -> DisposableEvent
DisposableEvent forall a b. (a -> b) -> a -> b
$
do let plots :: [SignalHistory (Double, Double)]
-> [ResultValue e]
-> [[PlotLines Double Double -> a x y]]
-> Event ([Plot x y], [[PlotLines Double Double -> a x y]])
plots [SignalHistory (Double, Double)]
hs [ResultValue e]
exts [[PlotLines Double Double -> a x y]]
plotLineTails =
do [Plot x y]
ps <-
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [SignalHistory (Double, Double)]
hs [ResultValue e]
exts (forall a. [a] -> a
head [[PlotLines Double Double -> a x y]]
plotLineTails)) forall a b. (a -> b) -> a -> b
$
\(SignalHistory (Double, Double)
h, ResultValue e
ext, PlotLines Double Double -> a x y
plotLines) ->
do (Array Int Double
ts, Array Int (Double, Double)
zs) <- forall a. SignalHistory a -> Event (Array Int Double, Array Int a)
readSignalHistory SignalHistory (Double, Double)
h
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
forall (a :: * -> * -> *) x y. ToPlot a => a x y -> Plot x y
toPlot forall a b. (a -> b) -> a -> b
$
PlotLines Double Double -> a x y
plotLines forall a b. (a -> b) -> a -> b
$
forall x y. Lens' (PlotLines x y) [[(x, y)]]
plot_lines_values forall s t a b. ASetter s t a b -> b -> s -> t
.~ [(Double, Double)] -> [[(Double, Double)]]
filterPlotLinesValues (forall i e. Array i e -> [e]
elems Array Int (Double, Double)
zs) forall a b. (a -> b) -> a -> b
$
forall x y. Lens' (PlotLines x y) String
plot_lines_title forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([ResultId] -> String
loc forall a b. (a -> b) -> a -> b
$ forall e. ResultValue e -> [ResultId]
resultValueIdPath ResultValue e
ext) forall a b. (a -> b) -> a -> b
$
forall a. Default a => a
def
forall (m :: * -> *) a. Monad m => a -> m a
return ([Plot x y]
ps, forall a. Int -> [a] -> [a]
drop (forall (t :: * -> *) a. Foldable t => t a -> Int
length [SignalHistory (Double, Double)]
hs) [[PlotLines Double Double -> a x y]]
plotLineTails)
([Plot Double Double]
ps1, [[PlotLines Double Double -> PlotLines Double Double]]
plotLineTails) <- forall {a :: * -> * -> *} {e} {x} {y}.
ToPlot a =>
[SignalHistory (Double, Double)]
-> [ResultValue e]
-> [[PlotLines Double Double -> a x y]]
-> Event ([Plot x y], [[PlotLines Double Double -> a x y]])
plots [SignalHistory (Double, Double)]
hs1 [ResultValue Double]
exts1 (forall a. [a] -> [[a]]
tails [PlotLines Double Double -> PlotLines Double Double]
plotLines)
([Plot Double Double]
ps2, [[PlotLines Double Double -> PlotLines Double Double]]
plotLineTails) <- forall {a :: * -> * -> *} {e} {x} {y}.
ToPlot a =>
[SignalHistory (Double, Double)]
-> [ResultValue e]
-> [[PlotLines Double Double -> a x y]]
-> Event ([Plot x y], [[PlotLines Double Double -> a x y]])
plots [SignalHistory (Double, Double)]
hs2 [ResultValue Double]
exts2 [[PlotLines Double Double -> PlotLines Double Double]]
plotLineTails
let ps1' :: [Either (Plot Double Double) b]
ps1' = forall a b. (a -> b) -> [a] -> [b]
map forall a b. a -> Either a b
Left [Plot Double Double]
ps1
ps2' :: [Either a (Plot Double Double)]
ps2' = forall a b. (a -> b) -> [a] -> [b]
map forall a b. b -> Either a b
Right [Plot Double Double]
ps2
ps' :: [Either (Plot Double Double) (Plot Double Double)]
ps' = forall {b}. [Either (Plot Double Double) b]
ps1' forall a. [a] -> [a] -> [a]
++ forall {a}. [Either a (Plot Double Double)]
ps2'
axis :: LayoutAxis Double
axis = LayoutAxis Double -> LayoutAxis Double
plotBottomAxis forall a b. (a -> b) -> a -> b
$
forall x. Lens' (LayoutAxis x) String
laxis_title forall s t a b. ASetter s t a b -> b -> s -> t
.~ ([ResultId] -> String
loc forall a b. (a -> b) -> a -> b
$ forall e. ResultValue e -> [ResultId]
resultValueIdPath ResultValue Double
ext0) forall a b. (a -> b) -> a -> b
$
forall a. Default a => a
def
updateLeftAxis :: LayoutLR x y1 y2 -> LayoutLR x y1 y2
updateLeftAxis =
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Plot Double Double]
ps1
then forall x y1 y2. Lens' (LayoutLR x y1 y2) AxisVisibility
layoutlr_left_axis_visibility forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool -> Bool -> Bool -> AxisVisibility
AxisVisibility Bool
False Bool
False Bool
False
else forall a. a -> a
id
updateRightAxis :: LayoutLR x y1 y2 -> LayoutLR x y1 y2
updateRightAxis =
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Plot Double Double]
ps2
then forall x y1 y2. Lens' (LayoutLR x y1 y2) AxisVisibility
layoutlr_right_axis_visibility forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool -> Bool -> Bool -> AxisVisibility
AxisVisibility Bool
False Bool
False Bool
False
else forall a. a -> a
id
chart :: LayoutLR Double Double Double
chart = LayoutLR Double Double Double -> LayoutLR Double Double Double
plotLayout forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall r.
ChartRendering r =>
r -> LayoutLR Double Double Double -> LayoutLR Double Double Double
renderingLayoutLR r
renderer forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall {x} {y1} {y2}. LayoutLR x y1 y2 -> LayoutLR x y1 y2
updateLeftAxis forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {x} {y1} {y2}. LayoutLR x y1 y2 -> LayoutLR x y1 y2
updateRightAxis forall a b. (a -> b) -> a -> b
$
forall x y1 y2. Lens' (LayoutLR x y1 y2) (LayoutAxis x)
layoutlr_x_axis forall s t a b. ASetter s t a b -> b -> s -> t
.~ LayoutAxis Double
axis forall a b. (a -> b) -> a -> b
$
forall x y1 y2. Lens' (LayoutLR x y1 y2) String
layoutlr_title forall s t a b. ASetter s t a b -> b -> s -> t
.~ String
runPlotTitle' forall a b. (a -> b) -> a -> b
$
forall x y1 y2.
Lens' (LayoutLR x y1 y2) [Either (Plot x y1) (Plot x y2)]
layoutlr_plots forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Either (Plot Double Double) (Plot Double Double)]
ps' forall a b. (a -> b) -> a -> b
$
forall a. Default a => a
def
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
do forall r c.
ChartRendering r =>
r -> (Int, Int) -> String -> Renderable c -> IO (PickFn c)
renderChart r
renderer (Int
width, Int
height) String
file (forall a. ToRenderable a => a -> Renderable ()
toRenderable LayoutLR Double Double Double
chart)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Experiment -> Bool
experimentVerbose forall a b. (a -> b) -> a -> b
$ forall r. XYChartViewState r -> Experiment
xyChartExperiment XYChartViewState r
st) forall a b. (a -> b) -> a -> b
$
String -> IO ()
putStr String
"Generated file " forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO ()
putStrLn String
file
filterPlotLinesValues :: [(Double, Double)] -> [[(Double, Double)]]
filterPlotLinesValues :: [(Double, Double)] -> [[(Double, Double)]]
filterPlotLinesValues =
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a. (a -> Bool) -> [a] -> [[a]]
divideBy (\(Double
x, Double
y) -> forall a. RealFloat a => a -> Bool
isNaN Double
x Bool -> Bool -> Bool
|| forall a. RealFloat a => a -> Bool
isInfinite Double
x Bool -> Bool -> Bool
|| forall a. RealFloat a => a -> Bool
isNaN Double
y Bool -> Bool -> Bool
|| forall a. RealFloat a => a -> Bool
isInfinite Double
y)
xyChartHtml :: XYChartViewState r -> Int -> HtmlWriter ()
xyChartHtml :: forall r. XYChartViewState r -> Int -> HtmlWriter ()
xyChartHtml XYChartViewState r
st Int
index =
let n :: Int
n = Experiment -> Int
experimentRunCount forall a b. (a -> b) -> a -> b
$ forall r. XYChartViewState r -> Experiment
xyChartExperiment XYChartViewState r
st
in if Int
n forall a. Eq a => a -> a -> Bool
== Int
1
then forall r. XYChartViewState r -> Int -> HtmlWriter ()
xyChartHtmlSingle XYChartViewState r
st Int
index
else forall r. XYChartViewState r -> Int -> HtmlWriter ()
xyChartHtmlMultiple XYChartViewState r
st Int
index
xyChartHtmlSingle :: XYChartViewState r -> Int -> HtmlWriter ()
xyChartHtmlSingle :: forall r. XYChartViewState r -> Int -> HtmlWriter ()
xyChartHtmlSingle XYChartViewState r
st Int
index =
do forall r. XYChartViewState r -> Int -> HtmlWriter ()
header XYChartViewState r
st Int
index
let f :: String
f = forall a. HasCallStack => Maybe a -> a
fromJust forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
0 (forall r. XYChartViewState r -> Map Int String
xyChartMap XYChartViewState r
st)
HtmlWriter () -> HtmlWriter ()
writeHtmlParagraph forall a b. (a -> b) -> a -> b
$
String -> HtmlWriter ()
writeHtmlImage (String -> String -> String
makeRelative (forall r. XYChartViewState r -> String
xyChartDir XYChartViewState r
st) String
f)
xyChartHtmlMultiple :: XYChartViewState r -> Int -> HtmlWriter ()
xyChartHtmlMultiple :: forall r. XYChartViewState r -> Int -> HtmlWriter ()
xyChartHtmlMultiple XYChartViewState r
st Int
index =
do forall r. XYChartViewState r -> Int -> HtmlWriter ()
header XYChartViewState r
st Int
index
let n :: Int
n = Experiment -> Int
experimentRunCount forall a b. (a -> b) -> a -> b
$ forall r. XYChartViewState r -> Experiment
xyChartExperiment XYChartViewState r
st
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
0..(Int
n forall a. Num a => a -> a -> a
- Int
1)] forall a b. (a -> b) -> a -> b
$ \Int
i ->
let f :: String
f = forall a. HasCallStack => Maybe a -> a
fromJust forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Int
i (forall r. XYChartViewState r -> Map Int String
xyChartMap XYChartViewState r
st)
in HtmlWriter () -> HtmlWriter ()
writeHtmlParagraph forall a b. (a -> b) -> a -> b
$
String -> HtmlWriter ()
writeHtmlImage (String -> String -> String
makeRelative (forall r. XYChartViewState r -> String
xyChartDir XYChartViewState r
st) String
f)
header :: XYChartViewState r -> Int -> HtmlWriter ()
XYChartViewState r
st Int
index =
do String -> HtmlWriter () -> HtmlWriter ()
writeHtmlHeader3WithId (String
"id" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
index) forall a b. (a -> b) -> a -> b
$
String -> HtmlWriter ()
writeHtmlText (XYChartView -> String
xyChartTitle forall a b. (a -> b) -> a -> b
$ forall r. XYChartViewState r -> XYChartView
xyChartView XYChartViewState r
st)
let description :: String
description = XYChartView -> String
xyChartDescription forall a b. (a -> b) -> a -> b
$ forall r. XYChartViewState r -> XYChartView
xyChartView XYChartViewState r
st
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
description) forall a b. (a -> b) -> a -> b
$
HtmlWriter () -> HtmlWriter ()
writeHtmlParagraph forall a b. (a -> b) -> a -> b
$
String -> HtmlWriter ()
writeHtmlText String
description
xyChartTOCHtml :: XYChartViewState r -> Int -> HtmlWriter ()
xyChartTOCHtml :: forall r. XYChartViewState r -> Int -> HtmlWriter ()
xyChartTOCHtml XYChartViewState r
st Int
index =
HtmlWriter () -> HtmlWriter ()
writeHtmlListItem forall a b. (a -> b) -> a -> b
$
String -> HtmlWriter () -> HtmlWriter ()
writeHtmlLink (String
"#id" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
index) forall a b. (a -> b) -> a -> b
$
String -> HtmlWriter ()
writeHtmlText (XYChartView -> String
xyChartTitle forall a b. (a -> b) -> a -> b
$ forall r. XYChartViewState r -> XYChartView
xyChartView XYChartViewState r
st)