{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
module DeltaQ.Plot
( plotCDF
, plotCDFs
, plotCDFWithQuantiles
, plotInverseCDF
, plotInverseCDFs
, plotInverseCDFWithQuantiles
) where
import DeltaQ.Class
( Outcome (Duration)
, DeltaQ (..)
, Eventually (..)
, eventually
, maybeFromEventually
)
import Graphics.Rendering.Chart.Easy
( (.=)
)
import qualified Graphics.Rendering.Chart.Easy as G
plotCDF
:: ( DeltaQ o
, Enum (Duration o)
, Fractional (Duration o)
, Real (Duration o)
, Real (Probability o)
)
=> String
-> o
-> G.Layout Double Double
plotCDF :: forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o),
Real (Duration o), Real (Probability o)) =>
String -> o -> Layout Double Double
plotCDF String
title o
o =
String -> [(String, o)] -> Layout Double Double
forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o),
Real (Duration o), Real (Probability o)) =>
String -> [(String, o)] -> Layout Double Double
plotCDFs String
title [(String
"", o
o)]
plotCDFs
:: ( DeltaQ o
, Enum (Duration o)
, Fractional (Duration o)
, Real (Duration o)
, Real (Probability o)
)
=> String
-> [(String, o)]
-> G.Layout Double Double
plotCDFs :: forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o),
Real (Duration o), Real (Probability o)) =>
String -> [(String, o)] -> Layout Double Double
plotCDFs String
title [(String, o)]
namedOutcomes = EC (Layout Double Double) () -> Layout Double Double
forall l a. Default l => EC l a -> l
G.execEC (EC (Layout Double Double) () -> Layout Double Double)
-> EC (Layout Double Double) () -> Layout Double Double
forall a b. (a -> b) -> a -> b
$ do
(String -> Identity String)
-> Layout Double Double -> Identity (Layout Double Double)
forall x y (f :: * -> *).
Functor f =>
(String -> f String) -> Layout x y -> f (Layout x y)
G.layout_title ((String -> Identity String)
-> Layout Double Double -> Identity (Layout Double Double))
-> String -> EC (Layout Double Double) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
title
[o] -> EC (Layout Double Double) ()
forall o y.
(DeltaQ o, Real (Duration o), Fractional (Duration o),
PlotValue y) =>
[o] -> EC (Layout Double y) ()
add_x_axis (((String, o) -> o) -> [(String, o)] -> [o]
forall a b. (a -> b) -> [a] -> [b]
map (String, o) -> o
forall a b. (a, b) -> b
snd [(String, o)]
namedOutcomes)
(LayoutAxis Double -> Identity (LayoutAxis Double))
-> Layout Double Double -> Identity (Layout Double Double)
forall x y (f :: * -> *).
Functor f =>
(LayoutAxis y -> f (LayoutAxis y)) -> Layout x y -> f (Layout x y)
G.layout_y_axis ((LayoutAxis Double -> Identity (LayoutAxis Double))
-> Layout Double Double -> Identity (Layout Double Double))
-> ((String -> Identity String)
-> LayoutAxis Double -> Identity (LayoutAxis Double))
-> (String -> Identity String)
-> Layout Double Double
-> Identity (Layout Double Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Identity String)
-> LayoutAxis Double -> Identity (LayoutAxis Double)
forall x (f :: * -> *).
Functor f =>
(String -> f String) -> LayoutAxis x -> f (LayoutAxis x)
G.laxis_title ((String -> Identity String)
-> Layout Double Double -> Identity (Layout Double Double))
-> String -> EC (Layout Double Double) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
"Cumulative Probabilty"
((String, o) -> EC (Layout Double Double) ())
-> [(String, o)] -> EC (Layout Double Double) ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (String, o) -> EC (Layout Double Double) ()
plotOne [(String, o)]
namedOutcomes
where
cv1 :: Duration o -> Double
cv1 = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double)
-> (Duration o -> Rational) -> Duration o -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Duration o -> Rational
forall a. Real a => a -> Rational
toRational
cv2 :: Probability o -> Double
cv2 = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double)
-> (Probability o -> Rational) -> Probability o -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Probability o -> Rational
forall a. Real a => a -> Rational
toRational
plotOne :: (String, o) -> EC (Layout Double Double) ()
plotOne (String
t, o
o) = EC (Layout Double Double) (PlotLines Double Double)
-> EC (Layout Double Double) ()
forall (p :: * -> * -> *) x y.
ToPlot p =>
EC (Layout x y) (p x y) -> EC (Layout x y) ()
G.plot (EC (Layout Double Double) (PlotLines Double Double)
-> EC (Layout Double Double) ())
-> EC (Layout Double Double) (PlotLines Double Double)
-> EC (Layout Double Double) ()
forall a b. (a -> b) -> a -> b
$ String
-> [[(Double, Double)]]
-> EC (Layout Double Double) (PlotLines Double Double)
forall x y l. String -> [[(x, y)]] -> EC l (PlotLines x y)
G.line String
t [[(Duration o -> Double
cv1 Duration o
a, Probability o -> Double
cv2 Probability o
b) | (Duration o
a, Probability o
b) <- o -> [(Duration o, Probability o)]
forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o)) =>
o -> [(Duration o, Probability o)]
toXY o
o]]
plotCDFWithQuantiles
:: ( DeltaQ o
, Enum (Duration o)
, Fractional (Duration o)
, Real (Duration o)
, Real (Probability o)
)
=> String
-> [Probability o]
-> o
-> G.Layout Double Double
plotCDFWithQuantiles :: forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o),
Real (Duration o), Real (Probability o)) =>
String -> [Probability o] -> o -> Layout Double Double
plotCDFWithQuantiles String
title [Probability o]
quantiles o
o = EC (Layout Double Double) () -> Layout Double Double
forall l a. Default l => EC l a -> l
G.execEC (EC (Layout Double Double) () -> Layout Double Double)
-> EC (Layout Double Double) () -> Layout Double Double
forall a b. (a -> b) -> a -> b
$ do
(String -> Identity String)
-> Layout Double Double -> Identity (Layout Double Double)
forall x y (f :: * -> *).
Functor f =>
(String -> f String) -> Layout x y -> f (Layout x y)
G.layout_title ((String -> Identity String)
-> Layout Double Double -> Identity (Layout Double Double))
-> String -> EC (Layout Double Double) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
title
[o] -> EC (Layout Double Double) ()
forall o y.
(DeltaQ o, Real (Duration o), Fractional (Duration o),
PlotValue y) =>
[o] -> EC (Layout Double y) ()
add_x_axis [o
o]
(LayoutAxis Double -> Identity (LayoutAxis Double))
-> Layout Double Double -> Identity (Layout Double Double)
forall x y (f :: * -> *).
Functor f =>
(LayoutAxis y -> f (LayoutAxis y)) -> Layout x y -> f (Layout x y)
G.layout_y_axis ((LayoutAxis Double -> Identity (LayoutAxis Double))
-> Layout Double Double -> Identity (Layout Double Double))
-> ((String -> Identity String)
-> LayoutAxis Double -> Identity (LayoutAxis Double))
-> (String -> Identity String)
-> Layout Double Double
-> Identity (Layout Double Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Identity String)
-> LayoutAxis Double -> Identity (LayoutAxis Double)
forall x (f :: * -> *).
Functor f =>
(String -> f String) -> LayoutAxis x -> f (LayoutAxis x)
G.laxis_title ((String -> Identity String)
-> Layout Double Double -> Identity (Layout Double Double))
-> String -> EC (Layout Double Double) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
"Cumulative Probabilty"
EC (Layout Double Double) (PlotLines Double Double)
-> EC (Layout Double Double) ()
forall (p :: * -> * -> *) x y.
ToPlot p =>
EC (Layout x y) (p x y) -> EC (Layout x y) ()
G.plot (EC (Layout Double Double) (PlotLines Double Double)
-> EC (Layout Double Double) ())
-> EC (Layout Double Double) (PlotLines Double Double)
-> EC (Layout Double Double) ()
forall a b. (a -> b) -> a -> b
$ String
-> [[(Double, Double)]]
-> EC (Layout Double Double) (PlotLines Double Double)
forall x y l. String -> [[(x, y)]] -> EC l (PlotLines x y)
G.line String
"" [[(Duration o -> Double
cv1 Duration o
a, Probability o -> Double
cv2 Probability o
b) | (Duration o
a, Probability o
b) <- o -> [(Duration o, Probability o)]
forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o)) =>
o -> [(Duration o, Probability o)]
toXY o
o]]
(Probability o -> EC (Layout Double Double) ())
-> [Probability o] -> EC (Layout Double Double) ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Probability o -> EC (Layout Double Double) ()
plotQuantile [Probability o]
quantiles
where
cv1 :: Duration o -> Double
cv1 = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double)
-> (Duration o -> Rational) -> Duration o -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Duration o -> Rational
forall a. Real a => a -> Rational
toRational
cv2 :: Probability o -> Double
cv2 = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double)
-> (Probability o -> Rational) -> Probability o -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Probability o -> Rational
forall a. Real a => a -> Rational
toRational
plotQuantile :: Probability o -> EC (Layout Double Double) ()
plotQuantile Probability o
y = case o -> Probability o -> Eventually (Duration o)
forall o. DeltaQ o => o -> Probability o -> Eventually (Duration o)
quantile o
o Probability o
y of
Eventually (Duration o)
Abandoned -> () -> EC (Layout Double Double) ()
forall a. a -> StateT (Layout Double Double) (State CState) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Occurs Duration o
x -> EC (Layout Double Double) (PlotLines Double Double)
-> EC (Layout Double Double) ()
forall (p :: * -> * -> *) x y.
ToPlot p =>
EC (Layout x y) (p x y) -> EC (Layout x y) ()
G.plot (EC (Layout Double Double) (PlotLines Double Double)
-> EC (Layout Double Double) ())
-> EC (Layout Double Double) (PlotLines Double Double)
-> EC (Layout Double Double) ()
forall a b. (a -> b) -> a -> b
$ PlotLines Double Double
-> EC (Layout Double Double) (PlotLines Double Double)
forall a. a -> StateT (Layout Double Double) (State CState) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PlotLines Double Double
-> EC (Layout Double Double) (PlotLines Double Double))
-> PlotLines Double Double
-> EC (Layout Double Double) (PlotLines Double Double)
forall a b. (a -> b) -> a -> b
$ (Double, Double) -> PlotLines Double Double
forall x y. (PlotValue x, PlotValue y) => (x, y) -> PlotLines x y
focusOnPoint (Duration o -> Double
cv1 Duration o
x, Probability o -> Double
cv2 Probability o
y)
plotInverseCDF
:: ( DeltaQ o
, Enum (Duration o)
, Fractional (Duration o)
, Real (Duration o)
, Real (Probability o)
)
=> String
-> o
-> G.Layout Double G.LogValue
plotInverseCDF :: forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o),
Real (Duration o), Real (Probability o)) =>
String -> o -> Layout Double LogValue
plotInverseCDF String
title o
o =
String -> [(String, o)] -> Layout Double LogValue
forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o),
Real (Duration o), Real (Probability o)) =>
String -> [(String, o)] -> Layout Double LogValue
plotInverseCDFs String
title [(String
"", o
o)]
plotInverseCDFs
:: ( DeltaQ o
, Enum (Duration o)
, Fractional (Duration o)
, Real (Duration o)
, Real (Probability o)
)
=> String
-> [(String, o)]
-> G.Layout Double G.LogValue
plotInverseCDFs :: forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o),
Real (Duration o), Real (Probability o)) =>
String -> [(String, o)] -> Layout Double LogValue
plotInverseCDFs String
title [(String, o)]
namedOutcomes = EC (Layout Double LogValue) () -> Layout Double LogValue
forall l a. Default l => EC l a -> l
G.execEC (EC (Layout Double LogValue) () -> Layout Double LogValue)
-> EC (Layout Double LogValue) () -> Layout Double LogValue
forall a b. (a -> b) -> a -> b
$ do
(String -> Identity String)
-> Layout Double LogValue -> Identity (Layout Double LogValue)
forall x y (f :: * -> *).
Functor f =>
(String -> f String) -> Layout x y -> f (Layout x y)
G.layout_title ((String -> Identity String)
-> Layout Double LogValue -> Identity (Layout Double LogValue))
-> String -> EC (Layout Double LogValue) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
title
[o] -> EC (Layout Double LogValue) ()
forall o y.
(DeltaQ o, Real (Duration o), Fractional (Duration o),
PlotValue y) =>
[o] -> EC (Layout Double y) ()
add_x_axis (((String, o) -> o) -> [(String, o)] -> [o]
forall a b. (a -> b) -> [a] -> [b]
map (String, o) -> o
forall a b. (a, b) -> b
snd [(String, o)]
namedOutcomes)
(LayoutAxis LogValue -> Identity (LayoutAxis LogValue))
-> Layout Double LogValue -> Identity (Layout Double LogValue)
forall x y (f :: * -> *).
Functor f =>
(LayoutAxis y -> f (LayoutAxis y)) -> Layout x y -> f (Layout x y)
G.layout_y_axis ((LayoutAxis LogValue -> Identity (LayoutAxis LogValue))
-> Layout Double LogValue -> Identity (Layout Double LogValue))
-> ((String -> Identity String)
-> LayoutAxis LogValue -> Identity (LayoutAxis LogValue))
-> (String -> Identity String)
-> Layout Double LogValue
-> Identity (Layout Double LogValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Identity String)
-> LayoutAxis LogValue -> Identity (LayoutAxis LogValue)
forall x (f :: * -> *).
Functor f =>
(String -> f String) -> LayoutAxis x -> f (LayoutAxis x)
G.laxis_title ((String -> Identity String)
-> Layout Double LogValue -> Identity (Layout Double LogValue))
-> String -> EC (Layout Double LogValue) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
"Log Inverse Cumulative Probabilty"
((String, o) -> EC (Layout Double LogValue) ())
-> [(String, o)] -> EC (Layout Double LogValue) ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (String, o) -> EC (Layout Double LogValue) ()
plotOne [(String, o)]
namedOutcomes
where
cv1 :: Duration o -> Double
cv1 = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double)
-> (Duration o -> Rational) -> Duration o -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Duration o -> Rational
forall a. Real a => a -> Rational
toRational
cv2 :: Probability o -> LogValue
cv2 = Rational -> LogValue
forall a. Fractional a => Rational -> a
fromRational (Rational -> LogValue)
-> (Probability o -> Rational) -> Probability o -> LogValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Probability o -> Rational
forall a. Real a => a -> Rational
toRational
plotOne :: (String, o) -> EC (Layout Double LogValue) ()
plotOne (String
t, o
o) = EC (Layout Double LogValue) (PlotLines Double LogValue)
-> EC (Layout Double LogValue) ()
forall (p :: * -> * -> *) x y.
ToPlot p =>
EC (Layout x y) (p x y) -> EC (Layout x y) ()
G.plot (EC (Layout Double LogValue) (PlotLines Double LogValue)
-> EC (Layout Double LogValue) ())
-> EC (Layout Double LogValue) (PlotLines Double LogValue)
-> EC (Layout Double LogValue) ()
forall a b. (a -> b) -> a -> b
$ String
-> [[(Double, LogValue)]]
-> EC (Layout Double LogValue) (PlotLines Double LogValue)
forall x y l. String -> [[(x, y)]] -> EC l (PlotLines x y)
G.line String
t [[(Duration o -> Double
cv1 Duration o
a, LogValue
1 LogValue -> LogValue -> LogValue
forall a. Num a => a -> a -> a
- Probability o -> LogValue
cv2 Probability o
b) | (Duration o
a, Probability o
b) <- o -> [(Duration o, Probability o)]
forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o)) =>
o -> [(Duration o, Probability o)]
toXY o
o]]
plotInverseCDFWithQuantiles
:: ( DeltaQ o
, Enum (Duration o)
, Fractional (Duration o)
, Real (Duration o)
, Real (Probability o)
)
=> String
-> [Probability o]
-> o
-> G.Layout Double G.LogValue
plotInverseCDFWithQuantiles :: forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o),
Real (Duration o), Real (Probability o)) =>
String -> [Probability o] -> o -> Layout Double LogValue
plotInverseCDFWithQuantiles String
title [Probability o]
quantiles o
o = EC (Layout Double LogValue) () -> Layout Double LogValue
forall l a. Default l => EC l a -> l
G.execEC (EC (Layout Double LogValue) () -> Layout Double LogValue)
-> EC (Layout Double LogValue) () -> Layout Double LogValue
forall a b. (a -> b) -> a -> b
$ do
(String -> Identity String)
-> Layout Double LogValue -> Identity (Layout Double LogValue)
forall x y (f :: * -> *).
Functor f =>
(String -> f String) -> Layout x y -> f (Layout x y)
G.layout_title ((String -> Identity String)
-> Layout Double LogValue -> Identity (Layout Double LogValue))
-> String -> EC (Layout Double LogValue) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
title
[o] -> EC (Layout Double LogValue) ()
forall o y.
(DeltaQ o, Real (Duration o), Fractional (Duration o),
PlotValue y) =>
[o] -> EC (Layout Double y) ()
add_x_axis [o
o]
(LayoutAxis LogValue -> Identity (LayoutAxis LogValue))
-> Layout Double LogValue -> Identity (Layout Double LogValue)
forall x y (f :: * -> *).
Functor f =>
(LayoutAxis y -> f (LayoutAxis y)) -> Layout x y -> f (Layout x y)
G.layout_y_axis ((LayoutAxis LogValue -> Identity (LayoutAxis LogValue))
-> Layout Double LogValue -> Identity (Layout Double LogValue))
-> ((String -> Identity String)
-> LayoutAxis LogValue -> Identity (LayoutAxis LogValue))
-> (String -> Identity String)
-> Layout Double LogValue
-> Identity (Layout Double LogValue)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Identity String)
-> LayoutAxis LogValue -> Identity (LayoutAxis LogValue)
forall x (f :: * -> *).
Functor f =>
(String -> f String) -> LayoutAxis x -> f (LayoutAxis x)
G.laxis_title ((String -> Identity String)
-> Layout Double LogValue -> Identity (Layout Double LogValue))
-> String -> EC (Layout Double LogValue) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
"Log Inverse Cumulative Probabilty"
EC (Layout Double LogValue) (PlotLines Double LogValue)
-> EC (Layout Double LogValue) ()
forall (p :: * -> * -> *) x y.
ToPlot p =>
EC (Layout x y) (p x y) -> EC (Layout x y) ()
G.plot (EC (Layout Double LogValue) (PlotLines Double LogValue)
-> EC (Layout Double LogValue) ())
-> EC (Layout Double LogValue) (PlotLines Double LogValue)
-> EC (Layout Double LogValue) ()
forall a b. (a -> b) -> a -> b
$ String
-> [[(Double, LogValue)]]
-> EC (Layout Double LogValue) (PlotLines Double LogValue)
forall x y l. String -> [[(x, y)]] -> EC l (PlotLines x y)
G.line String
"" [[(Duration o -> Double
cv1 Duration o
a, LogValue
1 LogValue -> LogValue -> LogValue
forall a. Num a => a -> a -> a
- Probability o -> LogValue
cv2 Probability o
b) | (Duration o
a, Probability o
b) <- o -> [(Duration o, Probability o)]
forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o)) =>
o -> [(Duration o, Probability o)]
toXY o
o]]
(Probability o -> EC (Layout Double LogValue) ())
-> [Probability o] -> EC (Layout Double LogValue) ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Probability o -> EC (Layout Double LogValue) ()
plotQuantile [Probability o]
quantiles
where
cv1 :: Duration o -> Double
cv1 = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double)
-> (Duration o -> Rational) -> Duration o -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Duration o -> Rational
forall a. Real a => a -> Rational
toRational
cv2 :: Probability o -> LogValue
cv2 = Rational -> LogValue
forall a. Fractional a => Rational -> a
fromRational (Rational -> LogValue)
-> (Probability o -> Rational) -> Probability o -> LogValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Probability o -> Rational
forall a. Real a => a -> Rational
toRational
plotQuantile :: Probability o -> EC (Layout Double LogValue) ()
plotQuantile Probability o
y = case o -> Probability o -> Eventually (Duration o)
forall o. DeltaQ o => o -> Probability o -> Eventually (Duration o)
quantile o
o Probability o
y of
Eventually (Duration o)
Abandoned -> () -> EC (Layout Double LogValue) ()
forall a. a -> StateT (Layout Double LogValue) (State CState) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Occurs Duration o
x -> EC (Layout Double LogValue) (PlotLines Double LogValue)
-> EC (Layout Double LogValue) ()
forall (p :: * -> * -> *) x y.
ToPlot p =>
EC (Layout x y) (p x y) -> EC (Layout x y) ()
G.plot (EC (Layout Double LogValue) (PlotLines Double LogValue)
-> EC (Layout Double LogValue) ())
-> EC (Layout Double LogValue) (PlotLines Double LogValue)
-> EC (Layout Double LogValue) ()
forall a b. (a -> b) -> a -> b
$ PlotLines Double LogValue
-> EC (Layout Double LogValue) (PlotLines Double LogValue)
forall a. a -> StateT (Layout Double LogValue) (State CState) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PlotLines Double LogValue
-> EC (Layout Double LogValue) (PlotLines Double LogValue))
-> PlotLines Double LogValue
-> EC (Layout Double LogValue) (PlotLines Double LogValue)
forall a b. (a -> b) -> a -> b
$ (Double, LogValue) -> PlotLines Double LogValue
forall x y. (PlotValue x, PlotValue y) => (x, y) -> PlotLines x y
focusOnPoint (Duration o -> Double
cv1 Duration o
x, Probability o -> LogValue
cv2 (Probability o
1 Probability o -> Probability o -> Probability o
forall a. Num a => a -> a -> a
- Probability o
y))
add_x_axis
:: (DeltaQ o, Real (Duration o), Fractional (Duration o), G.PlotValue y)
=> [o]
-> G.EC (G.Layout Double y) ()
add_x_axis :: forall o y.
(DeltaQ o, Real (Duration o), Fractional (Duration o),
PlotValue y) =>
[o] -> EC (Layout Double y) ()
add_x_axis [o]
outcomes = do
(LayoutAxis Double -> Identity (LayoutAxis Double))
-> Layout Double y -> Identity (Layout Double y)
forall x y (f :: * -> *).
Functor f =>
(LayoutAxis x -> f (LayoutAxis x)) -> Layout x y -> f (Layout x y)
G.layout_x_axis ((LayoutAxis Double -> Identity (LayoutAxis Double))
-> Layout Double y -> Identity (Layout Double y))
-> ((String -> Identity String)
-> LayoutAxis Double -> Identity (LayoutAxis Double))
-> (String -> Identity String)
-> Layout Double y
-> Identity (Layout Double y)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Identity String)
-> LayoutAxis Double -> Identity (LayoutAxis Double)
forall x (f :: * -> *).
Functor f =>
(String -> f String) -> LayoutAxis x -> f (LayoutAxis x)
G.laxis_title ((String -> Identity String)
-> Layout Double y -> Identity (Layout Double y))
-> String -> EC (Layout Double y) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
"Time (s)"
(LayoutAxis Double -> Identity (LayoutAxis Double))
-> Layout Double y -> Identity (Layout Double y)
forall x y (f :: * -> *).
Functor f =>
(LayoutAxis x -> f (LayoutAxis x)) -> Layout x y -> f (Layout x y)
G.layout_x_axis
((LayoutAxis Double -> Identity (LayoutAxis Double))
-> Layout Double y -> Identity (Layout Double y))
-> ((AxisFn Double -> Identity (AxisFn Double))
-> LayoutAxis Double -> Identity (LayoutAxis Double))
-> (AxisFn Double -> Identity (AxisFn Double))
-> Layout Double y
-> Identity (Layout Double y)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AxisFn Double -> Identity (AxisFn Double))
-> LayoutAxis Double -> Identity (LayoutAxis Double)
forall x (f :: * -> *).
Functor f =>
(AxisFn x -> f (AxisFn x)) -> LayoutAxis x -> f (LayoutAxis x)
G.laxis_generate
((AxisFn Double -> Identity (AxisFn Double))
-> Layout Double y -> Identity (Layout Double y))
-> AxisFn Double -> EC (Layout Double y) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= AxisFn Double
-> (Double -> AxisFn Double) -> Maybe Double -> AxisFn Double
forall b a. b -> (a -> b) -> Maybe a -> b
maybe AxisFn Double
forall a. PlotValue a => AxisFn a
G.autoAxis (\Double
u' -> LinearAxisParams Double -> (Double, Double) -> AxisFn Double
forall a. RealFloat a => LinearAxisParams a -> (a, a) -> AxisFn a
G.scaledAxis LinearAxisParams Double
forall a. Default a => a
G.def (Double
0, Double
1.05 Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
u')) Maybe Double
maxX
where
fromDuration :: Duration o -> Double
fromDuration = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational (Rational -> Double)
-> (Duration o -> Rational) -> Duration o -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Duration o -> Rational
forall a. Real a => a -> Rational
toRational
maxX :: Maybe Double
maxX = case [o]
outcomes of
[] -> Maybe Double
forall a. Maybe a
Nothing
[o]
_ ->
(Duration o -> Double) -> Maybe (Duration o) -> Maybe Double
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Duration o -> Double
fromDuration
(Maybe (Duration o) -> Maybe Double)
-> Maybe (Duration o) -> Maybe Double
forall a b. (a -> b) -> a -> b
$ [Maybe (Duration o)] -> Maybe (Duration o)
forall a. Ord a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum
([Maybe (Duration o)] -> Maybe (Duration o))
-> [Maybe (Duration o)] -> Maybe (Duration o)
forall a b. (a -> b) -> a -> b
$ (o -> Maybe (Duration o)) -> [o] -> [Maybe (Duration o)]
forall a b. (a -> b) -> [a] -> [b]
map (Eventually (Duration o) -> Maybe (Duration o)
forall a. Eventually a -> Maybe a
maybeFromEventually (Eventually (Duration o) -> Maybe (Duration o))
-> (o -> Eventually (Duration o)) -> o -> Maybe (Duration o)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. o -> Eventually (Duration o)
forall o. DeltaQ o => o -> Eventually (Duration o)
deadline) [o]
outcomes
focusOnPoint
:: (G.PlotValue x, G.PlotValue y)
=> (x,y) -> G.PlotLines x y
focusOnPoint :: forall x y. (PlotValue x, PlotValue y) => (x, y) -> PlotLines x y
focusOnPoint (x
x,y
y) = EC (PlotLines x y) () -> PlotLines x y
forall l a. Default l => EC l a -> l
G.execEC (EC (PlotLines x y) () -> PlotLines x y)
-> EC (PlotLines x y) () -> PlotLines x y
forall a b. (a -> b) -> a -> b
$ do
(LineStyle -> Identity LineStyle)
-> PlotLines x y -> Identity (PlotLines x y)
forall x y (f :: * -> *).
Functor f =>
(LineStyle -> f LineStyle) -> PlotLines x y -> f (PlotLines x y)
G.plot_lines_style ((LineStyle -> Identity LineStyle)
-> PlotLines x y -> Identity (PlotLines x y))
-> ((AlphaColour Double -> Identity (AlphaColour Double))
-> LineStyle -> Identity LineStyle)
-> (AlphaColour Double -> Identity (AlphaColour Double))
-> PlotLines x y
-> Identity (PlotLines x y)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AlphaColour Double -> Identity (AlphaColour Double))
-> LineStyle -> Identity LineStyle
Lens' LineStyle (AlphaColour Double)
G.line_color ((AlphaColour Double -> Identity (AlphaColour Double))
-> PlotLines x y -> Identity (PlotLines x y))
-> AlphaColour Double -> EC (PlotLines x y) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Colour Double -> AlphaColour Double
forall a. Num a => Colour a -> AlphaColour a
G.opaque Colour Double
forall a. Num a => Colour a
G.black
(LineStyle -> Identity LineStyle)
-> PlotLines x y -> Identity (PlotLines x y)
forall x y (f :: * -> *).
Functor f =>
(LineStyle -> f LineStyle) -> PlotLines x y -> f (PlotLines x y)
G.plot_lines_style ((LineStyle -> Identity LineStyle)
-> PlotLines x y -> Identity (PlotLines x y))
-> (([Double] -> Identity [Double])
-> LineStyle -> Identity LineStyle)
-> ([Double] -> Identity [Double])
-> PlotLines x y
-> Identity (PlotLines x y)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Double] -> Identity [Double]) -> LineStyle -> Identity LineStyle
Lens' LineStyle [Double]
G.line_dashes (([Double] -> Identity [Double])
-> PlotLines x y -> Identity (PlotLines x y))
-> [Double] -> EC (PlotLines x y) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= [Double
5, Double
5]
([[(Limit x, Limit y)]] -> Identity [[(Limit x, Limit y)]])
-> PlotLines x y -> Identity (PlotLines x y)
forall x y (f :: * -> *).
Functor f =>
([[(Limit x, Limit y)]] -> f [[(Limit x, Limit y)]])
-> PlotLines x y -> f (PlotLines x y)
G.plot_lines_limit_values (([[(Limit x, Limit y)]] -> Identity [[(Limit x, Limit y)]])
-> PlotLines x y -> Identity (PlotLines x y))
-> [[(Limit x, Limit y)]] -> EC (PlotLines x y) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.=
[ [(Limit x
forall a. Limit a
G.LMin, y -> Limit y
forall a. a -> Limit a
G.LValue y
y), (x -> Limit x
forall a. a -> Limit a
G.LValue x
x, y -> Limit y
forall a. a -> Limit a
G.LValue y
y)]
, [(x -> Limit x
forall a. a -> Limit a
G.LValue x
x, y -> Limit y
forall a. a -> Limit a
G.LValue y
y), (x -> Limit x
forall a. a -> Limit a
G.LValue x
x, Limit y
forall a. Limit a
G.LMin)]
]
toXY
:: (DeltaQ o, Enum (Duration o), Fractional (Duration o))
=> o
-> [(Duration o, Probability o)]
toXY :: forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o)) =>
o -> [(Duration o, Probability o)]
toXY = Int -> Double -> o -> [(Duration o, Probability o)]
forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o)) =>
Int -> Double -> o -> [(Duration o, Probability o)]
toXY' Int
2048 Double
0.05
toXY'
:: (DeltaQ o, Enum (Duration o), Fractional (Duration o))
=> Int
-> Double
-> o
-> [(Duration o, Probability o)]
toXY' :: forall o.
(DeltaQ o, Enum (Duration o), Fractional (Duration o)) =>
Int -> Double -> o -> [(Duration o, Probability o)]
toXY' Int
numPoints Double
overshoot o
o =
[(Duration o, Probability o)] -> [(Duration o, Probability o)]
forall a. Eq a => [a] -> [a]
deduplicate ([(Duration o, Probability o)] -> [(Duration o, Probability o)])
-> [(Duration o, Probability o)] -> [(Duration o, Probability o)]
forall a b. (a -> b) -> a -> b
$ [(Duration o, Probability o)]
leftEdge [(Duration o, Probability o)]
-> [(Duration o, Probability o)] -> [(Duration o, Probability o)]
forall a. Semigroup a => a -> a -> a
<> [(Duration o, Probability o)]
middle [(Duration o, Probability o)]
-> [(Duration o, Probability o)] -> [(Duration o, Probability o)]
forall a. Semigroup a => a -> a -> a
<> [(Duration o, Probability o)]
rightEdge
where
range :: Duration o
range = Duration o
upperX Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
- Duration o
lowerX
eps :: Duration o
eps = Duration o
range Duration o -> Duration o -> Duration o
forall a. Fractional a => a -> a -> a
/ Int -> Duration o
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
numPoints
lowerX :: Duration o
lowerX = Duration o
-> (Duration o -> Duration o)
-> Eventually (Duration o)
-> Duration o
forall b a. b -> (a -> b) -> Eventually a -> b
eventually Duration o
0 Duration o -> Duration o
forall a. a -> a
id (Eventually (Duration o) -> Duration o)
-> Eventually (Duration o) -> Duration o
forall a b. (a -> b) -> a -> b
$ o -> Eventually (Duration o)
forall o. DeltaQ o => o -> Eventually (Duration o)
earliest o
o
upperX :: Duration o
upperX = Duration o
-> (Duration o -> Duration o)
-> Eventually (Duration o)
-> Duration o
forall b a. b -> (a -> b) -> Eventually a -> b
eventually Duration o
halfLifeCarbon14 Duration o -> Duration o
forall a. a -> a
id (Eventually (Duration o) -> Duration o)
-> Eventually (Duration o) -> Duration o
forall a b. (a -> b) -> a -> b
$ o -> Eventually (Duration o)
forall o. DeltaQ o => o -> Eventually (Duration o)
deadline o
o
halfLifeCarbon14 :: Duration o
halfLifeCarbon14 = Duration o
5730 Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
* Duration o
365 Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
* Duration o
24 Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
* Duration o
60 Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
* Duration o
60
success :: Probability o
success = Probability o
1 Probability o -> Probability o -> Probability o
forall a. Num a => a -> a -> a
- o -> Probability o
forall o. DeltaQ o => o -> Probability o
failure o
o
sw :: Duration o -> Probability o
sw = o -> Duration o -> Probability o
forall o. DeltaQ o => o -> Duration o -> Probability o
successWithin o
o
leftEdge :: [(Duration o, Probability o)]
leftEdge =
[(Duration o
0, Probability o
0), (Duration o
lowerX Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
- Duration o
eps, Probability o
0), (Duration o
lowerX, Duration o -> Probability o
sw Duration o
lowerX)]
rightEdge :: [(Duration o, Probability o)]
rightEdge =
[ (Duration o
upperX, Probability o
success)
, (Duration o
upperX Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
+ (Rational -> Duration o
forall a. Fractional a => Rational -> a
fromRational (Rational -> Duration o)
-> (Double -> Rational) -> Double -> Duration o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Rational
forall a. Real a => a -> Rational
toRational (Double -> Duration o) -> Double -> Duration o
forall a b. (a -> b) -> a -> b
$ Double
overshoot) Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
* Duration o
range, Probability o
success)
]
middle :: [(Duration o, Probability o)]
middle
| Duration o
eps Duration o -> Duration o -> Bool
forall a. Ord a => a -> a -> Bool
<= Duration o
0 = []
| Bool
otherwise =
[ (Duration o
x, Duration o -> Probability o
sw Duration o
x)
| Duration o
x <- [Duration o
lowerX Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
+ Duration o
eps, Duration o
lowerX Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
+ Duration o
2Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
*Duration o
eps .. Duration o
upperX Duration o -> Duration o -> Duration o
forall a. Num a => a -> a -> a
- Duration o
eps]
]
deduplicate :: Eq a => [a] -> [a]
deduplicate :: forall a. Eq a => [a] -> [a]
deduplicate [] = []
deduplicate (a
x : [a]
xs) = a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a -> [a] -> [a]
forall {a}. Eq a => a -> [a] -> [a]
dedup' a
x [a]
xs
where
dedup' :: a -> [a] -> [a]
dedup' a
_ [] = []
dedup' a
y (a
y' : [a]
ys)
| a
y a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
y' = a -> [a] -> [a]
dedup' a
y [a]
ys
| Bool
otherwise = a
y' a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a -> [a] -> [a]
dedup' a
y' [a]
ys