{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Plots.Types.Scatter
(
ScatterPlot
, ScatterOptions
, HasScatterOptions (..)
, HasConnectingLine (..)
, scatterPlot
, scatterPlot'
, scatterPlotOf
, scatterPlotOf'
, scatterOptions
, bubblePlot
, bubblePlot'
, bubblePlotOf
, bubblePlotOf'
, BubbleOptions
, bubbleOptions
, bubbleTransform
, bubbleStyle
, gscatterPlot
, gscatterOptionsFor
, mkScatterOptions
) where
import Control.Lens hiding (lmap, transform, ( # ))
import Control.Monad.State.Lazy
import qualified Data.Foldable as F
import Data.Typeable
import Diagrams.Coordinates.Isomorphic
import Diagrams.Prelude hiding (view)
import Plots.Axis
import Plots.Style
import Plots.Types
data ScatterPlot v n where
ScatterPlot :: Typeable a => ScatterOptions v n a -> ScatterPlot v n
deriving Typeable
type instance V (ScatterPlot v n) = v
type instance N (ScatterPlot v n) = n
data ScatterOptions v n a = ScatterOptions
{ forall (v :: * -> *) n a. ScatterOptions v n a -> [a]
oData :: [a]
, forall (v :: * -> *) n a. ScatterOptions v n a -> a -> Point v n
oPos :: a -> Point v n
, forall (v :: * -> *) n a.
ScatterOptions v n a -> a -> Transformation v n
oTr :: a -> Transformation v n
, forall (v :: * -> *) n a. ScatterOptions v n a -> a -> Style v n
oSty :: a -> Style v n
, forall (v :: * -> *) n a. ScatterOptions v n a -> Bool
oLine :: Bool
} deriving Typeable
type instance V (ScatterOptions v n a) = v
type instance N (ScatterOptions v n a) = n
instance (Metric v, OrderedField n) => Enveloped (ScatterPlot v n) where
getEnvelope :: ScatterPlot v n
-> Envelope (V (ScatterPlot v n)) (N (ScatterPlot v n))
getEnvelope (ScatterPlot (ScatterOptions {Bool
[a]
a -> Style v n
a -> Transformation v n
a -> Point v n
oLine :: Bool
oSty :: a -> Style v n
oTr :: a -> Transformation v n
oPos :: a -> Point v n
oData :: [a]
oLine :: forall (v :: * -> *) n a. ScatterOptions v n a -> Bool
oSty :: forall (v :: * -> *) n a. ScatterOptions v n a -> a -> Style v n
oTr :: forall (v :: * -> *) n a.
ScatterOptions v n a -> a -> Transformation v n
oPos :: forall (v :: * -> *) n a. ScatterOptions v n a -> a -> Point v n
oData :: forall (v :: * -> *) n a. ScatterOptions v n a -> [a]
..})) = [Point v n] -> Envelope (V [Point v n]) (N [Point v n])
forall a. Enveloped a => a -> Envelope (V a) (N a)
getEnvelope ((a -> Point v n) -> [a] -> [Point v n]
forall a b. (a -> b) -> [a] -> [b]
map a -> Point v n
oPos [a]
oData)
instance (TypeableFloat n, Renderable (Path V2 n) b)
=> Plotable (ScatterPlot V2 n) b where
renderPlotable :: forall (v :: * -> *) n.
InSpace v n (ScatterPlot V2 n) =>
AxisSpec v n
-> PlotStyle b v n -> ScatterPlot V2 n -> QDiagram b v n Any
renderPlotable AxisSpec v n
s PlotStyle b v n
sty (ScatterPlot (ScatterOptions {Bool
[a]
a -> Style V2 n
a -> Transformation V2 n
a -> Point V2 n
oLine :: Bool
oSty :: a -> Style V2 n
oTr :: a -> Transformation V2 n
oPos :: a -> Point V2 n
oData :: [a]
oLine :: forall (v :: * -> *) n a. ScatterOptions v n a -> Bool
oSty :: forall (v :: * -> *) n a. ScatterOptions v n a -> a -> Style v n
oTr :: forall (v :: * -> *) n a.
ScatterOptions v n a -> a -> Transformation v n
oPos :: forall (v :: * -> *) n a. ScatterOptions v n a -> a -> Point v n
oData :: forall (v :: * -> *) n a. ScatterOptions v n a -> [a]
..})) =
QDiagram b v n Any
markers QDiagram b v n Any -> QDiagram b v n Any -> QDiagram b v n Any
forall a. Semigroup a => a -> a -> a
<> QDiagram b v n Any
line
where
markers :: QDiagram b v n Any
markers = (a -> QDiagram b v n Any) -> [a] -> QDiagram b v n Any
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap a -> QDiagram b v n Any
mk [a]
oData QDiagram b v n Any
-> (QDiagram b v n Any -> QDiagram b v n Any) -> QDiagram b v n Any
forall a b. a -> (a -> b) -> b
# PlotStyle b v n -> QDiagram b v n Any -> QDiagram b v n Any
forall a t b.
(SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b,
HasStyle t) =>
a -> t -> t
applyMarkerStyle PlotStyle b v n
sty
mk :: a -> QDiagram b v n Any
mk a
a = QDiagram b v n Any
marker QDiagram b v n Any
-> (QDiagram b v n Any -> QDiagram b v n Any) -> QDiagram b v n Any
forall a b. a -> (a -> b) -> b
# Transformation (V (QDiagram b v n Any)) (N (QDiagram b v n Any))
-> QDiagram b v n Any -> QDiagram b v n Any
forall t. Transformable t => Transformation (V t) (N t) -> t -> t
transform (a -> Transformation V2 n
oTr a
a)
# applyStyle (oSty a)
# moveTo (specPoint s $ oPos a)
marker :: QDiagram b v n Any
marker = PlotStyle b v n
sty PlotStyle b v n
-> Getting
(QDiagram b v n Any) (PlotStyle b v n) (QDiagram b v n Any)
-> QDiagram b v n Any
forall s a. s -> Getting a s a -> a
^. Getting (QDiagram b v n Any) (PlotStyle b v n) (QDiagram b v n Any)
forall (f :: * -> *) a b.
(HasPlotStyle f a b, Functor f) =>
LensLike' f a (QDiagram b (V a) (N a) Any)
plotMarker
line :: QDiagram b v n Any
line
| Bool -> Bool
not Bool
oLine = QDiagram b v n Any
forall a. Monoid a => a
mempty
| Bool
otherwise = [Point (V (QDiagram b v n Any)) (N (QDiagram b v n Any))]
-> QDiagram b v n Any
forall t. TrailLike t => [Point (V t) (N t)] -> t
fromVertices [Point v n]
[Point (V (QDiagram b v n Any)) (N (QDiagram b v n Any))]
points QDiagram b v n Any
-> (QDiagram b v n Any -> QDiagram b v n Any) -> QDiagram b v n Any
forall a b. a -> (a -> b) -> b
# PlotStyle b v n -> QDiagram b v n Any -> QDiagram b v n Any
forall a t b.
(SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b,
HasStyle t) =>
a -> t -> t
applyLineStyle PlotStyle b v n
sty
points :: [Point v n]
points = (a -> Point v n) -> [a] -> [Point v n]
forall a b. (a -> b) -> [a] -> [b]
map (AxisSpec v n -> Point v n -> Point v n
forall (v :: * -> *) n.
(Applicative v, Additive v, Floating n) =>
AxisSpec v n -> Point v n -> Point v n
specPoint AxisSpec v n
s (Point v n -> Point v n) -> (a -> Point v n) -> a -> Point v n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Point v n
a -> Point V2 n
oPos) [a]
oData
defLegendPic :: forall (v :: * -> *) n.
InSpace v n (ScatterPlot V2 n) =>
PlotStyle b v n -> ScatterPlot V2 n -> QDiagram b v n Any
defLegendPic PlotStyle b v n
sty (ScatterPlot (ScatterOptions {})) =
PlotStyle b v n
sty PlotStyle b v n
-> Getting
(QDiagram b v n Any) (PlotStyle b v n) (QDiagram b v n Any)
-> QDiagram b v n Any
forall s a. s -> Getting a s a -> a
^. Getting (QDiagram b v n Any) (PlotStyle b v n) (QDiagram b v n Any)
forall (f :: * -> *) a b.
(HasPlotStyle f a b, Functor f) =>
LensLike' f a (QDiagram b (V a) (N a) Any)
plotMarker
QDiagram b v n Any
-> (QDiagram b v n Any -> QDiagram b v n Any) -> QDiagram b v n Any
forall a b. a -> (a -> b) -> b
& PlotStyle b v n -> QDiagram b v n Any -> QDiagram b v n Any
forall a t b.
(SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b,
HasStyle t) =>
a -> t -> t
applyMarkerStyle PlotStyle b v n
sty
mkScatterOptions
:: (PointLike v n p, F.Foldable f, Fractional n)
=> f a
-> (a -> p)
-> ScatterOptions v n a
mkScatterOptions :: forall (v :: * -> *) n p (f :: * -> *) a.
(PointLike v n p, Foldable f, Fractional n) =>
f a -> (a -> p) -> ScatterOptions v n a
mkScatterOptions f a
xs a -> p
pf = ScatterOptions
{ oData :: [a]
oData = f a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList f a
xs
, oPos :: a -> Point v n
oPos = Getting (Point v n) p (Point v n) -> p -> Point v n
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Point v n) p (Point v n)
forall (v :: * -> *) n a. PointLike v n a => Iso' a (Point v n)
unpointLike (p -> Point v n) -> (a -> p) -> a -> Point v n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> p
pf
, oTr :: a -> Transformation v n
oTr = a -> Transformation v n
forall a. Monoid a => a
mempty
, oSty :: a -> Style v n
oSty = Style v n -> a -> Style v n
forall a b. a -> b -> a
const (Tagged
(HashMap TypeRep (Attribute v n))
(Identity (HashMap TypeRep (Attribute v n)))
-> Tagged (Style v n) (Identity (Style v n))
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
_Wrapped (Tagged
(HashMap TypeRep (Attribute v n))
(Identity (HashMap TypeRep (Attribute v n)))
-> Tagged (Style v n) (Identity (Style v n)))
-> HashMap TypeRep (Attribute v n) -> Style v n
forall t b. AReview t b -> b -> t
## HashMap TypeRep (Attribute v n)
forall a. Monoid a => a
mempty)
, oLine :: Bool
oLine = Bool
False
}
class HasConnectingLine f a where
connectingLine :: Functor f => LensLike' f a Bool
instance HasConnectingLine f (ScatterOptions v n a) where
connectingLine :: Functor f => LensLike' f (ScatterOptions v n a) Bool
connectingLine = (ScatterOptions v n a -> Bool)
-> (ScatterOptions v n a -> Bool -> ScatterOptions v n a)
-> Lens (ScatterOptions v n a) (ScatterOptions v n a) Bool Bool
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ScatterOptions v n a -> Bool
forall (v :: * -> *) n a. ScatterOptions v n a -> Bool
oLine (\ScatterOptions v n a
o Bool
b -> ScatterOptions v n a
o {oLine :: Bool
oLine = Bool
b})
instance HasConnectingLine f (ScatterPlot v n) where
connectingLine :: Functor f => LensLike' f (ScatterPlot v n) Bool
connectingLine Bool -> f Bool
f (ScatterPlot o :: ScatterOptions v n a
o@(ScatterOptions {Bool
[a]
a -> Style v n
a -> Transformation v n
a -> Point v n
oLine :: Bool
oSty :: a -> Style v n
oTr :: a -> Transformation v n
oPos :: a -> Point v n
oData :: [a]
oLine :: forall (v :: * -> *) n a. ScatterOptions v n a -> Bool
oSty :: forall (v :: * -> *) n a. ScatterOptions v n a -> a -> Style v n
oTr :: forall (v :: * -> *) n a.
ScatterOptions v n a -> a -> Transformation v n
oPos :: forall (v :: * -> *) n a. ScatterOptions v n a -> a -> Point v n
oData :: forall (v :: * -> *) n a. ScatterOptions v n a -> [a]
..}))
= Bool -> f Bool
f Bool
oLine f Bool -> (Bool -> ScatterPlot v n) -> f (ScatterPlot v n)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Bool
b -> ScatterOptions v n a -> ScatterPlot v n
forall a (v :: * -> *) n.
Typeable a =>
ScatterOptions v n a -> ScatterPlot v n
ScatterPlot ScatterOptions v n a
o {oLine :: Bool
oLine = Bool
b}
instance HasConnectingLine f p => HasConnectingLine f (Plot p b) where
connectingLine :: Functor f => LensLike' f (Plot p b) Bool
connectingLine = (p -> f p) -> Plot p b -> f (Plot p b)
forall p p' b. SameSpace p p' => Lens (Plot p b) (Plot p' b) p p'
rawPlot ((p -> f p) -> Plot p b -> f (Plot p b))
-> ((Bool -> f Bool) -> p -> f p) -> LensLike' f (Plot p b) Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> f Bool) -> p -> f p
forall (f :: * -> *) a.
(HasConnectingLine f a, Functor f) =>
LensLike' f a Bool
connectingLine
instance (Applicative f, Typeable b, Typeable v, Typeable n)
=> HasConnectingLine f (DynamicPlot b v n) where
connectingLine :: Functor f => LensLike' f (DynamicPlot b v n) Bool
connectingLine = (forall p b.
(Typeable p, Typeable b) =>
Traversal' (DynamicPlot b (V p) (N p)) (Plot p b)
forall {f :: * -> *}.
Applicative f =>
(Plot (ScatterPlot v n) b -> f (Plot (ScatterPlot v n) b))
-> DynamicPlot b v n -> f (DynamicPlot b v n)
dynamicPlot :: Traversal' (DynamicPlot b v n) (Plot (ScatterPlot v n) b))
((Plot (ScatterPlot v n) b -> f (Plot (ScatterPlot v n) b))
-> DynamicPlot b v n -> f (DynamicPlot b v n))
-> ((Bool -> f Bool)
-> Plot (ScatterPlot v n) b -> f (Plot (ScatterPlot v n) b))
-> LensLike' f (DynamicPlot b v n) Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> f Bool)
-> Plot (ScatterPlot v n) b -> f (Plot (ScatterPlot v n) b)
forall (f :: * -> *) a.
(HasConnectingLine f a, Functor f) =>
LensLike' f a Bool
connectingLine
instance (Applicative f, Typeable v, Typeable n)
=> HasConnectingLine f (StyledPlot b v n) where
connectingLine :: Functor f => LensLike' f (StyledPlot b v n) Bool
connectingLine = (forall p b. Typeable p => Traversal' (StyledPlot b (V p) (N p)) p
forall {f :: * -> *}.
Applicative f =>
(ScatterPlot v n -> f (ScatterPlot v n))
-> StyledPlot b v n -> f (StyledPlot b v n)
styledPlot :: Traversal' (StyledPlot b v n) (ScatterPlot v n))
((ScatterPlot v n -> f (ScatterPlot v n))
-> StyledPlot b v n -> f (StyledPlot b v n))
-> ((Bool -> f Bool) -> ScatterPlot v n -> f (ScatterPlot v n))
-> LensLike' f (StyledPlot b v n) Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> f Bool) -> ScatterPlot v n -> f (ScatterPlot v n)
forall (f :: * -> *) a.
(HasConnectingLine f a, Functor f) =>
LensLike' f a Bool
connectingLine
instance (Settable f, Typeable (BaseSpace c), Typeable n)
=> HasConnectingLine f (Axis b c n) where
connectingLine :: Functor f => LensLike' f (Axis b c n) Bool
connectingLine = (StyledPlot b (BaseSpace c) n -> f (StyledPlot b (BaseSpace c) n))
-> Axis b c n -> f (Axis b c n)
forall (c :: * -> *) (v :: * -> *) b n.
(BaseSpace c ~ v) =>
Setter' (Axis b c n) (StyledPlot b v n)
finalPlots ((StyledPlot b (BaseSpace c) n -> f (StyledPlot b (BaseSpace c) n))
-> Axis b c n -> f (Axis b c n))
-> ((Bool -> f Bool)
-> StyledPlot b (BaseSpace c) n
-> f (StyledPlot b (BaseSpace c) n))
-> LensLike' f (Axis b c n) Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> f Bool)
-> StyledPlot b (BaseSpace c) n -> f (StyledPlot b (BaseSpace c) n)
forall (f :: * -> *) a.
(HasConnectingLine f a, Functor f) =>
LensLike' f a Bool
connectingLine
class HasScatterOptions f a d where
gscatterOptions :: LensLike' f a (ScatterOptions (V a) (N a) d)
scatterTransform :: Functor f => LensLike' f a (d -> Transformation (V a) (N a))
scatterTransform = LensLike' f a (ScatterOptions (V a) (N a) d)
forall (f :: * -> *) a d.
HasScatterOptions f a d =>
LensLike' f a (ScatterOptions (V a) (N a) d)
gscatterOptions LensLike' f a (ScatterOptions (V a) (N a) d)
-> (((d -> Transformation (V a) (N a))
-> f (d -> Transformation (V a) (N a)))
-> ScatterOptions (V a) (N a) d
-> f (ScatterOptions (V a) (N a) d))
-> LensLike' f a (d -> Transformation (V a) (N a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScatterOptions (V a) (N a) d -> d -> Transformation (V a) (N a))
-> (ScatterOptions (V a) (N a) d
-> (d -> Transformation (V a) (N a))
-> ScatterOptions (V a) (N a) d)
-> Lens
(ScatterOptions (V a) (N a) d)
(ScatterOptions (V a) (N a) d)
(d -> Transformation (V a) (N a))
(d -> Transformation (V a) (N a))
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ScatterOptions (V a) (N a) d -> d -> Transformation (V a) (N a)
forall (v :: * -> *) n a.
ScatterOptions v n a -> a -> Transformation v n
oTr (\ScatterOptions (V a) (N a) d
o d -> Transformation (V a) (N a)
tr -> ScatterOptions (V a) (N a) d
o {oTr :: d -> Transformation (V a) (N a)
oTr = d -> Transformation (V a) (N a)
tr})
scatterStyle :: Functor f => LensLike' f a (d -> Style (V a) (N a))
scatterStyle = LensLike' f a (ScatterOptions (V a) (N a) d)
forall (f :: * -> *) a d.
HasScatterOptions f a d =>
LensLike' f a (ScatterOptions (V a) (N a) d)
gscatterOptions LensLike' f a (ScatterOptions (V a) (N a) d)
-> (((d -> Style (V a) (N a)) -> f (d -> Style (V a) (N a)))
-> ScatterOptions (V a) (N a) d
-> f (ScatterOptions (V a) (N a) d))
-> LensLike' f a (d -> Style (V a) (N a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScatterOptions (V a) (N a) d -> d -> Style (V a) (N a))
-> (ScatterOptions (V a) (N a) d
-> (d -> Style (V a) (N a)) -> ScatterOptions (V a) (N a) d)
-> Lens
(ScatterOptions (V a) (N a) d)
(ScatterOptions (V a) (N a) d)
(d -> Style (V a) (N a))
(d -> Style (V a) (N a))
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ScatterOptions (V a) (N a) d -> d -> Style (V a) (N a)
forall (v :: * -> *) n a. ScatterOptions v n a -> a -> Style v n
oSty (\ScatterOptions (V a) (N a) d
o d -> Style (V a) (N a)
sty -> ScatterOptions (V a) (N a) d
o {oSty :: d -> Style (V a) (N a)
oSty = d -> Style (V a) (N a)
sty})
scatterPosition :: Functor f => LensLike' f a (d -> Point (V a) (N a))
scatterPosition = LensLike' f a (ScatterOptions (V a) (N a) d)
forall (f :: * -> *) a d.
HasScatterOptions f a d =>
LensLike' f a (ScatterOptions (V a) (N a) d)
gscatterOptions LensLike' f a (ScatterOptions (V a) (N a) d)
-> (((d -> Point (V a) (N a)) -> f (d -> Point (V a) (N a)))
-> ScatterOptions (V a) (N a) d
-> f (ScatterOptions (V a) (N a) d))
-> LensLike' f a (d -> Point (V a) (N a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScatterOptions (V a) (N a) d -> d -> Point (V a) (N a))
-> (ScatterOptions (V a) (N a) d
-> (d -> Point (V a) (N a)) -> ScatterOptions (V a) (N a) d)
-> Lens
(ScatterOptions (V a) (N a) d)
(ScatterOptions (V a) (N a) d)
(d -> Point (V a) (N a))
(d -> Point (V a) (N a))
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens ScatterOptions (V a) (N a) d -> d -> Point (V a) (N a)
forall (v :: * -> *) n a. ScatterOptions v n a -> a -> Point v n
oPos (\ScatterOptions (V a) (N a) d
o d -> Point (V a) (N a)
pos -> ScatterOptions (V a) (N a) d
o {oPos :: d -> Point (V a) (N a)
oPos = d -> Point (V a) (N a)
pos})
instance d ~ d' => HasScatterOptions f (ScatterOptions v n d) d' where
gscatterOptions :: LensLike'
f
(ScatterOptions v n d)
(ScatterOptions
(V (ScatterOptions v n d)) (N (ScatterOptions v n d)) d')
gscatterOptions = LensLike'
f
(ScatterOptions v n d)
(ScatterOptions
(V (ScatterOptions v n d)) (N (ScatterOptions v n d)) d')
forall a. a -> a
id
instance (Applicative f, Typeable v, Typeable n, Typeable d)
=> HasScatterOptions f (ScatterPlot v n) d where
gscatterOptions :: LensLike'
f
(ScatterPlot v n)
(ScatterOptions (V (ScatterPlot v n)) (N (ScatterPlot v n)) d)
gscatterOptions ScatterOptions (V (ScatterPlot v n)) (N (ScatterPlot v n)) d
-> f (ScatterOptions (V (ScatterPlot v n)) (N (ScatterPlot v n)) d)
f s :: ScatterPlot v n
s@(ScatterPlot ScatterOptions v n a
p) =
case ScatterOptions v n a
-> Maybe (ScatterOptions v n a :~: ScatterOptions v n d)
forall a. Typeable a => a -> Maybe (a :~: ScatterOptions v n d)
eq ScatterOptions v n a
p of
Just ScatterOptions v n a :~: ScatterOptions v n d
Refl -> ScatterOptions v n d -> ScatterPlot v n
forall a (v :: * -> *) n.
Typeable a =>
ScatterOptions v n a -> ScatterPlot v n
ScatterPlot (ScatterOptions v n d -> ScatterPlot v n)
-> f (ScatterOptions v n d) -> f (ScatterPlot v n)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ScatterOptions (V (ScatterPlot v n)) (N (ScatterPlot v n)) d
-> f (ScatterOptions (V (ScatterPlot v n)) (N (ScatterPlot v n)) d)
f ScatterOptions v n a
ScatterOptions (V (ScatterPlot v n)) (N (ScatterPlot v n)) d
p
Maybe (ScatterOptions v n a :~: ScatterOptions v n d)
Nothing -> ScatterPlot v n -> f (ScatterPlot v n)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ScatterPlot v n
s
where
eq :: Typeable a => a -> Maybe (a :~: ScatterOptions v n d)
eq :: forall a. Typeable a => a -> Maybe (a :~: ScatterOptions v n d)
eq a
_ = Maybe (a :~: ScatterOptions v n d)
forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT
instance (Functor f, HasScatterOptions f p a) => HasScatterOptions f (Plot p b) a where
gscatterOptions :: LensLike'
f (Plot p b) (ScatterOptions (V (Plot p b)) (N (Plot p b)) a)
gscatterOptions = (p -> f p) -> Plot p b -> f (Plot p b)
forall p p' b. SameSpace p p' => Lens (Plot p b) (Plot p' b) p p'
rawPlot ((p -> f p) -> Plot p b -> f (Plot p b))
-> ((ScatterOptions (V p) (N p) a
-> f (ScatterOptions (V p) (N p) a))
-> p -> f p)
-> (ScatterOptions (V p) (N p) a
-> f (ScatterOptions (V p) (N p) a))
-> Plot p b
-> f (Plot p b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScatterOptions (V p) (N p) a -> f (ScatterOptions (V p) (N p) a))
-> p -> f p
forall (f :: * -> *) a d.
HasScatterOptions f a d =>
LensLike' f a (ScatterOptions (V a) (N a) d)
gscatterOptions
instance (Applicative f, Typeable b, Typeable v, Typeable n, Typeable a)
=> HasScatterOptions f (DynamicPlot b v n) a where
gscatterOptions :: LensLike'
f
(DynamicPlot b v n)
(ScatterOptions (V (DynamicPlot b v n)) (N (DynamicPlot b v n)) a)
gscatterOptions = (Plot (ScatterOptions v n a) b
-> f (Plot (ScatterOptions v n a) b))
-> DynamicPlot b v n -> f (DynamicPlot b v n)
forall p b.
(Typeable p, Typeable b) =>
Traversal' (DynamicPlot b (V p) (N p)) (Plot p b)
dynamicPlot ((Plot (ScatterOptions v n a) b
-> f (Plot (ScatterOptions v n a) b))
-> DynamicPlot b v n -> f (DynamicPlot b v n))
-> ((ScatterOptions v n a -> f (ScatterOptions v n a))
-> Plot (ScatterOptions v n a) b
-> f (Plot (ScatterOptions v n a) b))
-> (ScatterOptions v n a -> f (ScatterOptions v n a))
-> DynamicPlot b v n
-> f (DynamicPlot b v n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScatterOptions v n a -> f (ScatterOptions v n a))
-> Plot (ScatterOptions v n a) b
-> f (Plot (ScatterOptions v n a) b)
forall p p' b. SameSpace p p' => Lens (Plot p b) (Plot p' b) p p'
rawPlot
instance (Applicative f, Typeable b, Typeable (BaseSpace c), Typeable n, Typeable a)
=> HasScatterOptions f (Axis b c n) a where
gscatterOptions :: LensLike'
f (Axis b c n) (ScatterOptions (V (Axis b c n)) (N (Axis b c n)) a)
gscatterOptions = ([DynamicPlot b (BaseSpace c) n]
-> f [DynamicPlot b (BaseSpace c) n])
-> Axis b c n -> f (Axis b c n)
forall (c :: * -> *) (v :: * -> *) b n.
(BaseSpace c ~ v) =>
Lens' (Axis b c n) [DynamicPlot b v n]
axisPlots (([DynamicPlot b (BaseSpace c) n]
-> f [DynamicPlot b (BaseSpace c) n])
-> Axis b c n -> f (Axis b c n))
-> ((ScatterOptions (BaseSpace c) n a
-> f (ScatterOptions (BaseSpace c) n a))
-> [DynamicPlot b (BaseSpace c) n]
-> f [DynamicPlot b (BaseSpace c) n])
-> (ScatterOptions (BaseSpace c) n a
-> f (ScatterOptions (BaseSpace c) n a))
-> Axis b c n
-> f (Axis b c n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DynamicPlot b (BaseSpace c) n
-> f (DynamicPlot b (BaseSpace c) n))
-> [DynamicPlot b (BaseSpace c) n]
-> f [DynamicPlot b (BaseSpace c) n]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((DynamicPlot b (BaseSpace c) n
-> f (DynamicPlot b (BaseSpace c) n))
-> [DynamicPlot b (BaseSpace c) n]
-> f [DynamicPlot b (BaseSpace c) n])
-> ((ScatterOptions (BaseSpace c) n a
-> f (ScatterOptions (BaseSpace c) n a))
-> DynamicPlot b (BaseSpace c) n
-> f (DynamicPlot b (BaseSpace c) n))
-> (ScatterOptions (BaseSpace c) n a
-> f (ScatterOptions (BaseSpace c) n a))
-> [DynamicPlot b (BaseSpace c) n]
-> f [DynamicPlot b (BaseSpace c) n]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScatterOptions (BaseSpace c) n a
-> f (ScatterOptions (BaseSpace c) n a))
-> DynamicPlot b (BaseSpace c) n
-> f (DynamicPlot b (BaseSpace c) n)
forall (f :: * -> *) a d.
HasScatterOptions f a d =>
LensLike' f a (ScatterOptions (V a) (N a) d)
gscatterOptions
scatterOptions :: (InSpace v n a, HasScatterOptions f a (Point v n))
=> LensLike' f a (ScatterOptions v n (Point v n))
scatterOptions :: forall (v :: * -> *) n a (f :: * -> *).
(InSpace v n a, HasScatterOptions f a (Point v n)) =>
LensLike' f a (ScatterOptions v n (Point v n))
scatterOptions = (ScatterOptions v n (Point v n)
-> f (ScatterOptions v n (Point v n)))
-> a -> f a
forall (f :: * -> *) a d.
HasScatterOptions f a d =>
LensLike' f a (ScatterOptions (V a) (N a) d)
gscatterOptions
scatterPlot
:: (BaseSpace c ~ v,
PointLike v n p,
Typeable n,
MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b,
F.Foldable f)
=> f p
-> State (Plot (ScatterOptions v n (Point v n)) b) ()
-> m ()
scatterPlot :: forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *)
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, Typeable n,
MonadState (Axis b c n) m, Plotable (ScatterPlot v n) b,
Foldable f) =>
f p -> State (Plot (ScatterOptions v n (Point v n)) b) () -> m ()
scatterPlot f p
xs = [Point v n]
-> (Point v n -> Point v n)
-> State (Plot (ScatterOptions v n (Point v n)) b) ()
-> m ()
forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *) d
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b, Typeable d, Foldable f) =>
f d -> (d -> p) -> State (Plot (ScatterOptions v n d) b) () -> m ()
gscatterPlot (f p
xs f p -> Getting (Endo [Point v n]) (f p) (Point v n) -> [Point v n]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. (p -> Const (Endo [Point v n]) p)
-> f p -> Const (Endo [Point v n]) (f p)
forall (f :: * -> *) a. Foldable f => IndexedFold Int (f a) a
folded ((p -> Const (Endo [Point v n]) p)
-> f p -> Const (Endo [Point v n]) (f p))
-> ((Point v n -> Const (Endo [Point v n]) (Point v n))
-> p -> Const (Endo [Point v n]) p)
-> Getting (Endo [Point v n]) (f p) (Point v n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Point v n -> Const (Endo [Point v n]) (Point v n))
-> p -> Const (Endo [Point v n]) p
forall (v :: * -> *) n a. PointLike v n a => Iso' a (Point v n)
unpointLike) Point v n -> Point v n
forall a. a -> a
id
scatterPlot'
:: (BaseSpace c ~ v,
PointLike v n p,
Typeable n,
MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b,
F.Foldable f)
=> f p
-> m ()
scatterPlot' :: forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *)
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, Typeable n,
MonadState (Axis b c n) m, Plotable (ScatterPlot v n) b,
Foldable f) =>
f p -> m ()
scatterPlot' f p
xs = f p
-> State
(Plot (ScatterOptions (BaseSpace c) n (Point (BaseSpace c) n)) b)
()
-> m ()
forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *)
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, Typeable n,
MonadState (Axis b c n) m, Plotable (ScatterPlot v n) b,
Foldable f) =>
f p -> State (Plot (ScatterOptions v n (Point v n)) b) () -> m ()
scatterPlot f p
xs (()
-> State
(Plot (ScatterOptions (BaseSpace c) n (Point (BaseSpace c) n)) b)
()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
scatterPlotOf
:: (BaseSpace c ~ v,
PointLike v n p,
Typeable n,
MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b)
=> Fold s p
-> s
-> State (Plot (ScatterOptions v n (Point v n)) b) ()
-> m ()
scatterPlotOf :: forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *) s.
(BaseSpace c ~ v, PointLike v n p, Typeable n,
MonadState (Axis b c n) m, Plotable (ScatterPlot v n) b) =>
Fold s p
-> s -> State (Plot (ScatterOptions v n (Point v n)) b) () -> m ()
scatterPlotOf Fold s p
f s
s = [p] -> State (Plot (ScatterOptions v n (Point v n)) b) () -> m ()
forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *)
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, Typeable n,
MonadState (Axis b c n) m, Plotable (ScatterPlot v n) b,
Foldable f) =>
f p -> State (Plot (ScatterOptions v n (Point v n)) b) () -> m ()
scatterPlot (Getting (Endo [p]) s p -> s -> [p]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [p]) s p
Fold s p
f s
s)
scatterPlotOf'
:: (BaseSpace c ~ v,
PointLike v n p,
Typeable n,
MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b)
=> Fold s p
-> s
-> m ()
scatterPlotOf' :: forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *) s.
(BaseSpace c ~ v, PointLike v n p, Typeable n,
MonadState (Axis b c n) m, Plotable (ScatterPlot v n) b) =>
Fold s p -> s -> m ()
scatterPlotOf' Fold s p
f s
s = [p] -> m ()
forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *)
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, Typeable n,
MonadState (Axis b c n) m, Plotable (ScatterPlot v n) b,
Foldable f) =>
f p -> m ()
scatterPlot' (Getting (Endo [p]) s p -> s -> [p]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [p]) s p
Fold s p
f s
s)
type BubbleOptions v n = ScatterOptions v n (n, Point v n)
bubblePlot
:: (BaseSpace c ~ v,
PointLike v n p,
MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b,
Typeable n,
F.Foldable f)
=> f (n, p)
-> State (Plot (BubbleOptions v n) b) ()
-> m ()
bubblePlot :: forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *)
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b, Typeable n, Foldable f) =>
f (n, p) -> State (Plot (BubbleOptions v n) b) () -> m ()
bubblePlot f (n, p)
xs State (Plot (ScatterOptions v n (n, Point v n)) b) ()
s =
[(n, Point v n)]
-> ((n, Point v n) -> Point v n)
-> State (Plot (ScatterOptions v n (n, Point v n)) b) ()
-> m ()
forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *) d
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b, Typeable d, Foldable f) =>
f d -> (d -> p) -> State (Plot (ScatterOptions v n d) b) () -> m ()
gscatterPlot (f (n, p)
xs f (n, p)
-> Getting (Endo [(n, Point v n)]) (f (n, p)) (n, Point v n)
-> [(n, Point v n)]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. ((n, p) -> Const (Endo [(n, Point v n)]) (n, p))
-> f (n, p) -> Const (Endo [(n, Point v n)]) (f (n, p))
forall (f :: * -> *) a. Foldable f => IndexedFold Int (f a) a
folded (((n, p) -> Const (Endo [(n, Point v n)]) (n, p))
-> f (n, p) -> Const (Endo [(n, Point v n)]) (f (n, p)))
-> (((n, Point v n)
-> Const (Endo [(n, Point v n)]) (n, Point v n))
-> (n, p) -> Const (Endo [(n, Point v n)]) (n, p))
-> Getting (Endo [(n, Point v n)]) (f (n, p)) (n, Point v n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnIso p p (Point v n) (Point v n)
-> Iso (n, p) (n, p) (n, Point v n) (n, Point v n)
forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping AnIso p p (Point v n) (Point v n)
forall (v :: * -> *) n a. PointLike v n a => Iso' a (Point v n)
unpointLike) (n, Point v n) -> Point v n
forall a b. (a, b) -> b
snd (State (Plot (ScatterOptions v n (n, Point v n)) b) () -> m ())
-> State (Plot (ScatterOptions v n (n, Point v n)) b) () -> m ()
forall a b. (a -> b) -> a -> b
$ do
LensLike'
Identity
(Plot (ScatterOptions v n (n, Point v n)) b)
(n -> Transformation v n)
forall (v :: * -> *) n a (f :: * -> *).
(InSpace v n a, HasScatterOptions f a (n, Point v n),
Settable f) =>
LensLike' f a (n -> Transformation v n)
bubbleTransform LensLike'
Identity
(Plot (ScatterOptions v n (n, Point v n)) b)
(n -> Transformation v n)
-> (n -> Transformation v n)
-> State (Plot (ScatterOptions v n (n, Point v n)) b) ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= n -> Transformation v n
forall (v :: * -> *) n.
(Additive v, Fractional n) =>
n -> Transformation v n
scaling
State (Plot (ScatterOptions v n (n, Point v n)) b) ()
s
bubblePlot'
:: (v ~ BaseSpace c,
PointLike v n p,
Typeable n,
MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b,
F.Foldable f)
=> f (n, p)
-> m ()
bubblePlot' :: forall (v :: * -> *) (c :: * -> *) n p b (m :: * -> *)
(f :: * -> *).
(v ~ BaseSpace c, PointLike v n p, Typeable n,
MonadState (Axis b c n) m, Plotable (ScatterPlot v n) b,
Foldable f) =>
f (n, p) -> m ()
bubblePlot' f (n, p)
xs = f (n, p)
-> State (Plot (BubbleOptions (BaseSpace c) n) b) () -> m ()
forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *)
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b, Typeable n, Foldable f) =>
f (n, p) -> State (Plot (BubbleOptions v n) b) () -> m ()
bubblePlot f (n, p)
xs (() -> State (Plot (BubbleOptions (BaseSpace c) n) b) ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
bubblePlotOf
:: (BaseSpace c ~ v,
PointLike v n p,
MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b,
Typeable n)
=> Fold s (n,p)
-> s
-> State (Plot (BubbleOptions v n) b) ()
-> m ()
bubblePlotOf :: forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *) s.
(BaseSpace c ~ v, PointLike v n p, MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b, Typeable n) =>
Fold s (n, p) -> s -> State (Plot (BubbleOptions v n) b) () -> m ()
bubblePlotOf Fold s (n, p)
f s
s = [(n, p)] -> State (Plot (BubbleOptions v n) b) () -> m ()
forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *)
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b, Typeable n, Foldable f) =>
f (n, p) -> State (Plot (BubbleOptions v n) b) () -> m ()
bubblePlot (Getting (Endo [(n, p)]) s (n, p) -> s -> [(n, p)]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [(n, p)]) s (n, p)
Fold s (n, p)
f s
s)
bubblePlotOf'
:: (BaseSpace c ~ v,
PointLike v n p,
MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b,
Typeable n)
=> Fold s (n,p)
-> s
-> State (Plot (BubbleOptions v n) b) ()
-> m ()
bubblePlotOf' :: forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *) s.
(BaseSpace c ~ v, PointLike v n p, MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b, Typeable n) =>
Fold s (n, p) -> s -> State (Plot (BubbleOptions v n) b) () -> m ()
bubblePlotOf' Fold s (n, p)
f s
s = [(n, p)] -> State (Plot (BubbleOptions v n) b) () -> m ()
forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *)
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b, Typeable n, Foldable f) =>
f (n, p) -> State (Plot (BubbleOptions v n) b) () -> m ()
bubblePlot (Getting (Endo [(n, p)]) s (n, p) -> s -> [(n, p)]
forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [(n, p)]) s (n, p)
Fold s (n, p)
f s
s)
bubbleOptions :: (InSpace v n a, HasScatterOptions f a (n, Point v n))
=> LensLike' f a (BubbleOptions v n)
bubbleOptions :: forall (v :: * -> *) n a (f :: * -> *).
(InSpace v n a, HasScatterOptions f a (n, Point v n)) =>
LensLike' f a (BubbleOptions v n)
bubbleOptions = (ScatterOptions v n (n, Point v n)
-> f (ScatterOptions v n (n, Point v n)))
-> a -> f a
forall (f :: * -> *) a d.
HasScatterOptions f a d =>
LensLike' f a (ScatterOptions (V a) (N a) d)
gscatterOptions
bubbleTransform
:: (InSpace v n a, HasScatterOptions f a (n, Point v n), Settable f)
=> LensLike' f a (n -> Transformation v n)
bubbleTransform :: forall (v :: * -> *) n a (f :: * -> *).
(InSpace v n a, HasScatterOptions f a (n, Point v n),
Settable f) =>
LensLike' f a (n -> Transformation v n)
bubbleTransform = LensLike' f a (BubbleOptions v n)
forall (v :: * -> *) n a (f :: * -> *).
(InSpace v n a, HasScatterOptions f a (n, Point v n)) =>
LensLike' f a (BubbleOptions v n)
bubbleOptions LensLike' f a (BubbleOptions v n)
-> (((n -> Transformation v n) -> f (n -> Transformation v n))
-> BubbleOptions v n -> f (BubbleOptions v n))
-> ((n -> Transformation v n) -> f (n -> Transformation v n))
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((n, Point v n) -> Transformation v n)
-> f ((n, Point v n) -> Transformation v n))
-> BubbleOptions v n -> f (BubbleOptions v n)
forall (f :: * -> *) a d.
(HasScatterOptions f a d, Functor f) =>
LensLike' f a (d -> Transformation (V a) (N a))
scatterTransform ((((n, Point v n) -> Transformation v n)
-> f ((n, Point v n) -> Transformation v n))
-> BubbleOptions v n -> f (BubbleOptions v n))
-> (((n -> Transformation v n) -> f (n -> Transformation v n))
-> ((n, Point v n) -> Transformation v n)
-> f ((n, Point v n) -> Transformation v n))
-> ((n -> Transformation v n) -> f (n -> Transformation v n))
-> BubbleOptions v n
-> f (BubbleOptions v n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((n -> Transformation v n) -> n -> Transformation v n)
-> ((n, Point v n) -> Transformation v n)
-> (n, Point v n)
-> Transformation v n)
-> ((n -> Transformation v n) -> f (n -> Transformation v n))
-> ((n, Point v n) -> Transformation v n)
-> f ((n, Point v n) -> Transformation v n)
forall (p :: * -> * -> *) (q :: * -> * -> *) (f :: * -> *) a b s t.
(Profunctor p, Profunctor q, Settable f) =>
(p a b -> q s t) -> Optical p q f s t a b
sets ((n -> Transformation v n) -> n -> Transformation v n)
-> ((n, Point v n) -> Transformation v n)
-> (n, Point v n)
-> Transformation v n
forall {a} {t} {t} {t} {b}.
((a -> t) -> t -> t) -> ((a, b) -> t) -> (t, b) -> t
nOnly
where nOnly :: ((a -> t) -> t -> t) -> ((a, b) -> t) -> (t, b) -> t
nOnly (a -> t) -> t -> t
f (a, b) -> t
g (t
n,b
p) = (a -> t) -> t -> t
f (\a
n' -> (a, b) -> t
g (a
n', b
p)) t
n
bubbleStyle :: (InSpace v n a, Settable f, HasScatterOptions f a (n, Point v n))
=> LensLike' f a (n -> Style v n)
bubbleStyle :: forall (v :: * -> *) n a (f :: * -> *).
(InSpace v n a, Settable f,
HasScatterOptions f a (n, Point v n)) =>
LensLike' f a (n -> Style v n)
bubbleStyle = LensLike' f a (BubbleOptions v n)
forall (v :: * -> *) n a (f :: * -> *).
(InSpace v n a, HasScatterOptions f a (n, Point v n)) =>
LensLike' f a (BubbleOptions v n)
bubbleOptions LensLike' f a (BubbleOptions v n)
-> (((n -> Style v n) -> f (n -> Style v n))
-> BubbleOptions v n -> f (BubbleOptions v n))
-> ((n -> Style v n) -> f (n -> Style v n))
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((n, Point v n) -> Style v n) -> f ((n, Point v n) -> Style v n))
-> BubbleOptions v n -> f (BubbleOptions v n)
forall (f :: * -> *) a d.
(HasScatterOptions f a d, Functor f) =>
LensLike' f a (d -> Style (V a) (N a))
scatterStyle ((((n, Point v n) -> Style v n) -> f ((n, Point v n) -> Style v n))
-> BubbleOptions v n -> f (BubbleOptions v n))
-> (((n -> Style v n) -> f (n -> Style v n))
-> ((n, Point v n) -> Style v n)
-> f ((n, Point v n) -> Style v n))
-> ((n -> Style v n) -> f (n -> Style v n))
-> BubbleOptions v n
-> f (BubbleOptions v n)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (((n -> Style v n) -> n -> Style v n)
-> ((n, Point v n) -> Style v n) -> (n, Point v n) -> Style v n)
-> ((n -> Style v n) -> f (n -> Style v n))
-> ((n, Point v n) -> Style v n)
-> f ((n, Point v n) -> Style v n)
forall (p :: * -> * -> *) (q :: * -> * -> *) (f :: * -> *) a b s t.
(Profunctor p, Profunctor q, Settable f) =>
(p a b -> q s t) -> Optical p q f s t a b
sets ((n -> Style v n) -> n -> Style v n)
-> ((n, Point v n) -> Style v n) -> (n, Point v n) -> Style v n
forall {a} {t} {t} {t} {b}.
((a -> t) -> t -> t) -> ((a, b) -> t) -> (t, b) -> t
nOnly
where nOnly :: ((a -> t) -> t -> t) -> ((a, b) -> t) -> (t, b) -> t
nOnly (a -> t) -> t -> t
f (a, b) -> t
g (t
n,b
p) = (a -> t) -> t -> t
f (\a
n' -> (a, b) -> t
g (a
n', b
p)) t
n
gscatterPlot
:: (BaseSpace c ~ v,
PointLike v n p,
MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b,
Typeable d,
F.Foldable f)
=> f d
-> (d -> p)
-> State (Plot (ScatterOptions v n d) b) ()
-> m ()
gscatterPlot :: forall (c :: * -> *) (v :: * -> *) n p b (m :: * -> *) d
(f :: * -> *).
(BaseSpace c ~ v, PointLike v n p, MonadState (Axis b c n) m,
Plotable (ScatterPlot v n) b, Typeable d, Foldable f) =>
f d -> (d -> p) -> State (Plot (ScatterOptions v n d) b) () -> m ()
gscatterPlot f d
xs d -> p
pf State (Plot (ScatterOptions v n d) b) ()
s = Plot (ScatterPlot v n) b -> m ()
forall (c :: * -> *) n p b (m :: * -> *).
(InSpace (BaseSpace c) n p, MonadState (Axis b c n) m,
Plotable p b) =>
Plot p b -> m ()
addPlot (Plot (ScatterPlot v n) b -> m ())
-> Plot (ScatterPlot v n) b -> m ()
forall a b. (a -> b) -> a -> b
$ ASetter
(Plot (ScatterOptions v n d) b)
(Plot (ScatterPlot v n) b)
(ScatterOptions v n d)
(ScatterPlot v n)
-> (ScatterOptions v n d -> ScatterPlot v n)
-> Plot (ScatterOptions v n d) b
-> Plot (ScatterPlot v n) b
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
over ASetter
(Plot (ScatterOptions v n d) b)
(Plot (ScatterPlot v n) b)
(ScatterOptions v n d)
(ScatterPlot v n)
forall p p' b. SameSpace p p' => Lens (Plot p b) (Plot p' b) p p'
rawPlot ScatterOptions v n d -> ScatterPlot v n
forall a (v :: * -> *) n.
Typeable a =>
ScatterOptions v n a -> ScatterPlot v n
ScatterPlot Plot (ScatterOptions v n d) b
p1
where
p1 :: Plot (ScatterOptions v n d) b
p1 = State (Plot (ScatterOptions v n d) b) ()
-> Plot (ScatterOptions v n d) b -> Plot (ScatterOptions v n d) b
forall s a. State s a -> s -> s
execState State (Plot (ScatterOptions v n d) b) ()
s Plot (ScatterOptions v n d) b
p0
p0 :: Plot (ScatterOptions v n d) b
p0 = ScatterOptions v n d -> Plot (ScatterOptions v n d) b
forall p b. (Additive (V p), Num (N p)) => p -> Plot p b
mkPlot (ScatterOptions v n d -> Plot (ScatterOptions v n d) b)
-> ScatterOptions v n d -> Plot (ScatterOptions v n d) b
forall a b. (a -> b) -> a -> b
$ f d -> (d -> Point v n) -> ScatterOptions v n d
forall (v :: * -> *) n p (f :: * -> *) a.
(PointLike v n p, Foldable f, Fractional n) =>
f a -> (a -> p) -> ScatterOptions v n a
mkScatterOptions f d
xs (Getting (Point v n) p (Point v n) -> p -> Point v n
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Point v n) p (Point v n)
forall (v :: * -> *) n a. PointLike v n a => Iso' a (Point v n)
unpointLike (p -> Point v n) -> (d -> p) -> d -> Point v n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> p
pf)
gscatterOptionsFor
:: (InSpace v n a, HasScatterOptions f a d)
=> proxy d -> LensLike' f a (ScatterOptions v n d)
gscatterOptionsFor :: forall (v :: * -> *) n a (f :: * -> *) d (proxy :: * -> *).
(InSpace v n a, HasScatterOptions f a d) =>
proxy d -> LensLike' f a (ScatterOptions v n d)
gscatterOptionsFor proxy d
_ = (ScatterOptions v n d -> f (ScatterOptions v n d)) -> a -> f a
forall (f :: * -> *) a d.
HasScatterOptions f a d =>
LensLike' f a (ScatterOptions (V a) (N a) d)
gscatterOptions