Copyright | (C) 2015 Christopher Chalmers |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Christopher Chalmers |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
A scatter plot is a type of mathematical diagram using Cartesian coordinates to display values for typically two variables for a set of data.
(see scatterPlot
example for code to make this plot)
Synopsis
- data ScatterPlot v
- data ScatterOptions v a
- class HasScatterOptions f a d where
- gscatterOptions :: LensLike' f a (ScatterOptions (V a) d)
- scatterTransform :: Functor f => LensLike' f a (d -> Transformation (V a) Double)
- scatterStyle :: Functor f => LensLike' f a (d -> Style (V a) Double)
- scatterPosition :: Functor f => LensLike' f a (d -> Point (V a) Double)
- class HasConnectingLine f a where
- connectingLine :: Functor f => LensLike' f a Bool
- scatterPlot :: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v), Foldable f) => f p -> State (Plot (ScatterOptions v (Point v Double))) () -> m ()
- scatterPlot' :: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v), Foldable f) => f p -> m ()
- scatterPlotOf :: (BaseSpace c ~ v, PointLike v Double p, Plotable (ScatterPlot v), MonadState (Axis c) m) => Fold s p -> s -> State (Plot (ScatterOptions v (Point v Double))) () -> m ()
- scatterPlotOf' :: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v)) => Fold s p -> s -> m ()
- scatterOptions :: (InSpace v Double a, HasScatterOptions f a (Point v Double)) => LensLike' f a (ScatterOptions v (Point v Double))
- bubblePlot :: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v), Foldable f) => f (Double, p) -> State (Plot (BubbleOptions v)) () -> m ()
- bubblePlot' :: (v ~ BaseSpace c, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v), Foldable f) => f (Double, p) -> m ()
- bubblePlotOf :: (BaseSpace c ~ v, PointLike v Double p, Plotable (ScatterPlot v), MonadState (Axis c) m) => Fold s (Double, p) -> s -> State (Plot (BubbleOptions v)) () -> m ()
- bubblePlotOf' :: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v)) => Fold s (Double, p) -> s -> State (Plot (BubbleOptions v)) () -> m ()
- type BubbleOptions v = ScatterOptions v (Double, Point v Double)
- bubbleOptions :: (InSpace v Double a, HasScatterOptions f a (Double, Point v Double)) => LensLike' f a (BubbleOptions v)
- bubbleTransform :: (InSpace v Double a, HasScatterOptions f a (Double, Point v Double), Settable f) => LensLike' f a (Double -> Transformation v Double)
- bubbleStyle :: (InSpace v Double a, Settable f, HasScatterOptions f a (Double, Point v Double)) => LensLike' f a (Double -> Style v Double)
- gscatterPlot :: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Typeable d, Plotable (ScatterPlot v), Foldable f) => f d -> (d -> p) -> State (Plot (ScatterOptions v d)) () -> m ()
- gscatterOptionsFor :: (InSpace v Double a, HasScatterOptions f a d) => proxy d -> LensLike' f a (ScatterOptions v d)
- mkScatterOptions :: (PointLike v Double p, Foldable f) => f a -> (a -> p) -> ScatterOptions v a
Scatter plot
data ScatterPlot v Source #
A general data type for scatter plots. Allows storing different types of data as well as allowing transforms depending on the data.
Instances
Scatter plot lenses
data ScatterOptions v a Source #
A general data type for scatter plots. Allows storing different types of data as well as allowing transforms depending on the data.
Instances
HasConnectingLine f (ScatterOptions v a) Source # | |
Defined in Plots.Types.Scatter connectingLine :: LensLike' f (ScatterOptions v a) Bool Source # | |
d ~ d' => HasScatterOptions f (ScatterOptions v d) d' Source # | |
Defined in Plots.Types.Scatter gscatterOptions :: LensLike' f (ScatterOptions v d) (ScatterOptions (V (ScatterOptions v d)) d') Source # scatterTransform :: LensLike' f (ScatterOptions v d) (d' -> Transformation (V (ScatterOptions v d)) Double) Source # scatterStyle :: LensLike' f (ScatterOptions v d) (d' -> Style (V (ScatterOptions v d)) Double) Source # scatterPosition :: LensLike' f (ScatterOptions v d) (d' -> Point (V (ScatterOptions v d)) Double) Source # | |
type N (ScatterOptions v a) Source # | |
Defined in Plots.Types.Scatter | |
type V (ScatterOptions v a) Source # | |
Defined in Plots.Types.Scatter type V (ScatterOptions v a) = v |
class HasScatterOptions f a d where Source #
gscatterOptions :: LensLike' f a (ScatterOptions (V a) d) Source #
Lens onto the ScatterOptions
for a general scatter plot.
scatterTransform :: Functor f => LensLike' f a (d -> Transformation (V a) Double) Source #
Apply a transform to the markers using the associated data.
scatterStyle :: Functor f => LensLike' f a (d -> Style (V a) Double) Source #
Apply a style to the markers using the associated data.
scatterPosition :: Functor f => LensLike' f a (d -> Point (V a) Double) Source #
Change the position of the markers depending on the data.
Instances
class HasConnectingLine f a where Source #
Class of things that have a LensLike
for a ScatterPlot
's
connecting line.
Instances
(Settable f, Typeable (BaseSpace c)) => HasConnectingLine f (Axis c) Source # | |
Defined in Plots.Types.Scatter | |
(Applicative f, Typeable v) => HasConnectingLine f (StyledPlot v) Source # | |
Defined in Plots.Types.Scatter connectingLine :: LensLike' f (StyledPlot v) Bool Source # | |
(Applicative f, Typeable v) => HasConnectingLine f (DynamicPlot v) Source # | |
Defined in Plots.Types.Scatter connectingLine :: LensLike' f (DynamicPlot v) Bool Source # | |
HasConnectingLine f p => HasConnectingLine f (Plot p) Source # | |
Defined in Plots.Types.Scatter | |
HasConnectingLine f (ScatterPlot v) Source # | |
Defined in Plots.Types.Scatter connectingLine :: LensLike' f (ScatterPlot v) Bool Source # | |
HasConnectingLine f (ScatterOptions v a) Source # | |
Defined in Plots.Types.Scatter connectingLine :: LensLike' f (ScatterOptions v a) Bool Source # |
Basic scatter plot
Add plots to the axis
:: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v), Foldable f) | |
=> f p | points to plot |
-> State (Plot (ScatterOptions v (Point v Double))) () | changes to plot options |
-> m () | add plot to |
Add a ScatterPlot
to the AxisState
from a data set.
scatterPlot
:: [(Double
,Double
)] ->State
(Plot
(ScatterOptions
V2
(P2
Double
)) b) () ->State
(Axis
V2
) ()scatterPlot
:: [V2
Double
] ->State
(Plot
(ScatterOptions
V2
(P2
Double
)) b) () ->State
(Axis
V2
) ()scatterPlot
:: [P2
Double
] ->State
(Plot
(ScatterOptions
V2
(P2
Double
)) b) () ->State
(Axis
V2
) ()
Example
import Plots mydata1 = [(1,3), (2,5.5), (3.2, 6), (3.5, 6.1)] mydata2 = mydata1 & each . _1 *~ 0.5 mydata3 = [V2 1.2 2.7, V2 2 5.1, V2 3.2 2.6, V2 3.5 5]
scatterAxis :: Axis V2 scatterAxis = r2Axis &~ do scatterPlot mydata1 $ key "data 1" scatterPlot mydata2 $ key "data 2" scatterPlot mydata3 $ key "data 3"
scatterExample = renderAxis scatterAxis
:: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v), Foldable f) | |
=> f p | points to plot |
-> m () | add plot to |
Version of scatterPlot
without any changes to the
ScatterOptions
.
scatterPlot'
:: [(Double
,Double
)] ->State
(Axis
bV2
Double
) ()scatterPlot'
:: [V2
Double
] ->State
(Axis
bV2
Double
) ()scatterPlot'
:: [P2
Double
] ->State
(Axis
bV2
Double
) ()
Example
import Plots mydata4 = [(1,3), (2,5.5), (3.2, 6), (3.5, 6.1)] mydata5 = mydata1 & each . _1 *~ 0.5 mydata6 = [V2 1.2 2.7, V2 2 5.1, V2 3.2 2.6, V2 3.5 5]
scatterAxis' :: Axis B V2 Double scatterAxis' = r2Axis &~ do scatterPlot' mydata4 scatterPlot' mydata5 scatterPlot' mydata6
scatterExample' = renderAxis scatterAxis'
:: (BaseSpace c ~ v, PointLike v Double p, Plotable (ScatterPlot v), MonadState (Axis c) m) | |
=> Fold s p | fold over points |
-> s | data to fold |
-> State (Plot (ScatterOptions v (Point v Double))) () | changes to plot options |
-> m () | add plot to |
Version of scatterPlot
that accepts a Fold
over the data.
:: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v)) | |
=> Fold s p | fold over points |
-> s | data to fold |
-> m () | add plot to axis |
Version of scatterPlot
that accepts a Fold
over the data
without any changes to the ScatterOptions
.
Scatter options
scatterOptions :: (InSpace v Double a, HasScatterOptions f a (Point v Double)) => LensLike' f a (ScatterOptions v (Point v Double)) Source #
Lens onto a scatter plot of points.
Bubble plots
:: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v), Foldable f) | |
=> f (Double, p) | fold over points with a size |
-> State (Plot (BubbleOptions v)) () | changes to the options |
-> m () | add plot to |
Scatter plots with extra numeric parameter. By default the extra parameter is the scale of the marker but this can be changed.
bubblePlot
:: [(Double
, (Double
,Double
))] ->State
(Plot
(BubbleOptions
v) b) () ->State
(Axis
bV2
Double
) ()bubblePlot
:: [(Double
,V2
Double
)] ->State
(Plot
(BubbleOptions
v) b) () ->State
(Axis
bV2
Double
) ()bubblePlot
:: [(Double
,P2
Double
)] ->State
(Plot
(BubbleOptions
v) b) () ->State
(Axis
bV2
Double
) ()
Example
import Plots myweights = [2, 1.3, 1.8, 0.7] mydata7 = zip myweights [(1,3), (2,5.5), (3.2, 6), (3.5, 6.1)] mydata8 = mydata7 & each._2._2 *~ 0.5 & each._1 *~ 0.5 mydata9 = [(1, V2 1.2 2.7), (3, V2 2 5.1), (0.9, V2 3.2 2.6), (2, V2 3.5 5)]
bubbleAxis :: Axis B V2 Double bubbleAxis = r2Axis &~ do bubblePlot mydata7 $ key "data 7" bubblePlot mydata8 $ key "data 8" bubblePlot mydata9 $ key "data 9"
bubbleExample = renderAxis bubbleAxis
:: (v ~ BaseSpace c, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v), Foldable f) | |
=> f (Double, p) | fold over points with a size |
-> m () | add plot to |
:: (BaseSpace c ~ v, PointLike v Double p, Plotable (ScatterPlot v), MonadState (Axis c) m) | |
=> Fold s (Double, p) | fold over the data |
-> s | data |
-> State (Plot (BubbleOptions v)) () | changes to the options |
-> m () | add plot to |
Version of bubblePlot
using a Fold
over the data.
:: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Plotable (ScatterPlot v)) | |
=> Fold s (Double, p) | fold over the data |
-> s | data |
-> State (Plot (BubbleOptions v)) () | changes to the options |
-> m () | add plot to |
Version of bubblePlot
using a Fold
over the data without any
changes to the BubbleOptions
.
Bubble options
type BubbleOptions v = ScatterOptions v (Double, Point v Double) Source #
A bubble plot is a scatter plot using point together with a scalar.
bubbleOptions :: (InSpace v Double a, HasScatterOptions f a (Double, Point v Double)) => LensLike' f a (BubbleOptions v) Source #
LensLike onto into a ScatterOptions
made up of a scaler n
, and
a point, Point
v
bubbleOptions
::Lens'
(Plot
(BubbleOptions
v) v) (BubbleOptions
v)
bubbleTransform :: (InSpace v Double a, HasScatterOptions f a (Double, Point v Double), Settable f) => LensLike' f a (Double -> Transformation v Double) Source #
Setter over the transform function for a bubblePlot
. Default is scale
.
bubbleOptions
::Setter'
(Plot
(BubbleOptions
v) v) (n ->Transformation
v)
Note that this is the less general version of
, which would give a bubblePlot
.
scatterTransform
LensLike
onto (n,
.Point
v) -> Transformation
v
bubbleStyle :: (InSpace v Double a, Settable f, HasScatterOptions f a (Double, Point v Double)) => LensLike' f a (Double -> Style v Double) Source #
Setter over the style function for a bubblePlot
. Default is mempty
.
bubbleStyle
::Setter'
(Plot
(BubbleOptions
v) v) (n ->Style
v)
Note that this is the less general version of
, which would give a bubblePlot
.
scatterTransform
LensLike
onto (n,
.Point
v) -> Style
v
General scatter plot
:: (BaseSpace c ~ v, PointLike v Double p, MonadState (Axis c) m, Typeable d, Plotable (ScatterPlot v), Foldable f) | |
=> f d | data |
-> (d -> p) | extract point from data |
-> State (Plot (ScatterOptions v d)) () | options for plot |
-> m () | add plot to |
A general scatter plot allow using any data type d
to determine
the scatterTransform
and scatterStyle
.
gscatterOptionsFor :: (InSpace v Double a, HasScatterOptions f a d) => proxy d -> LensLike' f a (ScatterOptions v d) Source #
Helper to traverse over a general scatter plot where the type of d is not infered.
Low level construction
mkScatterOptions :: (PointLike v Double p, Foldable f) => f a -> (a -> p) -> ScatterOptions v a Source #
Low level construction of ScatterOptions
.