plots-0.1.1.1: Diagrams based plotting library.

Copyright(C) 2015 Christopher Chalmers
LicenseBSD-style (see the file LICENSE)
MaintainerChristopher Chalmers
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Plots.Types.Scatter

Contents

Description

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

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
HasConnectingLine f (ScatterPlot v) Source # 
Instance details

Defined in Plots.Types.Scatter

(Applicative f, Typeable v, Typeable d) => HasScatterOptions f (ScatterPlot v) d Source # 
Instance details

Defined in Plots.Types.Scatter

Metric v => Enveloped (ScatterPlot v) Source # 
Instance details

Defined in Plots.Types.Scatter

Methods

getEnvelope :: ScatterPlot v -> Envelope (V (ScatterPlot v)) (N (ScatterPlot v))

boundingBox :: ScatterPlot v -> BoundingBox (V (ScatterPlot v)) (N (ScatterPlot v))

Plotable (ScatterPlot V3) Source # 
Instance details

Defined in Plots.Types.Scatter

Methods

renderPlotable :: InSpace v Double (ScatterPlot V3) => AxisSpec v -> PlotStyle v -> ScatterPlot V3 -> Diagram v Source #

defLegendPic :: InSpace v Double (ScatterPlot V3) => PlotStyle v -> ScatterPlot V3 -> Diagram v Source #

Plotable (ScatterPlot V2) Source # 
Instance details

Defined in Plots.Types.Scatter

Methods

renderPlotable :: InSpace v Double (ScatterPlot V2) => AxisSpec v -> PlotStyle v -> ScatterPlot V2 -> Diagram v Source #

defLegendPic :: InSpace v Double (ScatterPlot V2) => PlotStyle v -> ScatterPlot V2 -> Diagram v Source #

type N (ScatterPlot v) Source # 
Instance details

Defined in Plots.Types.Scatter

type N (ScatterPlot v) = Double
type V (ScatterPlot v) Source # 
Instance details

Defined in Plots.Types.Scatter

type V (ScatterPlot v) = v

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 # 
Instance details

Defined in Plots.Types.Scatter

d ~ d' => HasScatterOptions f (ScatterOptions v d) d' Source # 
Instance details

Defined in Plots.Types.Scatter

type N (ScatterOptions v a) Source # 
Instance details

Defined in Plots.Types.Scatter

type N (ScatterOptions v a) = Double
type V (ScatterOptions v a) Source # 
Instance details

Defined in Plots.Types.Scatter

type V (ScatterOptions v a) = v

class HasScatterOptions f a d where Source #

Minimal complete definition

gscatterOptions

Methods

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
(Applicative f, Typeable (BaseSpace c), Typeable a) => HasScatterOptions f (Axis c) a Source # 
Instance details

Defined in Plots.Types.Scatter

Methods

gscatterOptions :: LensLike' f (Axis c) (ScatterOptions (V (Axis c)) a) Source #

scatterTransform :: LensLike' f (Axis c) (a -> Transformation (V (Axis c)) Double) Source #

scatterStyle :: LensLike' f (Axis c) (a -> Style (V (Axis c)) Double) Source #

scatterPosition :: LensLike' f (Axis c) (a -> Point (V (Axis c)) Double) Source #

(Applicative f, Typeable v, Typeable a) => HasScatterOptions f (DynamicPlot v) a Source # 
Instance details

Defined in Plots.Types.Scatter

(Functor f, HasScatterOptions f p a) => HasScatterOptions f (Plot p) a Source # 
Instance details

Defined in Plots.Types.Scatter

Methods

gscatterOptions :: LensLike' f (Plot p) (ScatterOptions (V (Plot p)) a) Source #

scatterTransform :: LensLike' f (Plot p) (a -> Transformation (V (Plot p)) Double) Source #

scatterStyle :: LensLike' f (Plot p) (a -> Style (V (Plot p)) Double) Source #

scatterPosition :: LensLike' f (Plot p) (a -> Point (V (Plot p)) Double) Source #

(Applicative f, Typeable v, Typeable d) => HasScatterOptions f (ScatterPlot v) d Source # 
Instance details

Defined in Plots.Types.Scatter

d ~ d' => HasScatterOptions f (ScatterOptions v d) d' Source # 
Instance details

Defined in Plots.Types.Scatter

class HasConnectingLine f a where Source #

Class of things that have a LensLike for a ScatterPlot 's connecting line.

Methods

connectingLine :: Functor f => LensLike' f a Bool Source #

LensLike onto whether the scatter plot should have a connecting line between points. If the line is present, it uses the lineStyle from the PlotStyle.

Basic scatter plot

Add plots to the axis

scatterPlot Source #

Arguments

:: (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 Axis

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

Expand

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

scatterPlot' Source #

Arguments

:: (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 Axis

Version of scatterPlot without any changes to the ScatterOptions.

scatterPlot' :: [(Double, Double)] -> State (Axis b V2 Double) ()
scatterPlot' :: [V2 Double]        -> State (Axis b V2 Double) ()
scatterPlot' :: [P2 Double]        -> State (Axis b V2 Double) ()

Example

Expand

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'

scatterPlotOf Source #

Arguments

:: (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 Axis

Version of scatterPlot that accepts a Fold over the data.

scatterPlotOf' Source #

Arguments

:: (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

bubblePlot Source #

Arguments

:: (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 Axis

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 b V2 Double) ()
bubblePlot :: [(Double, V2 Double)]        -> State (Plot (BubbleOptions v) b) () -> State (Axis b V2 Double) ()
bubblePlot :: [(Double, P2 Double)]        -> State (Plot (BubbleOptions v) b) () -> State (Axis b V2 Double) ()

Example

Expand

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

bubblePlot' Source #

Arguments

:: (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 Axis

Simple version of bubblePlot without any changes to the Plot.

bubblePlot' :: [(Double, (Double, Double))] -> State (Axis b V2 Double) ()
bubblePlot' :: [(Double, V2 Double)]        -> State (Axis b V2 Double) ()

bubblePlotOf Source #

Arguments

:: (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 Axis

Version of bubblePlot using a Fold over the data.

bubblePlotOf' Source #

Arguments

:: (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 Axis

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 bubblePlot . scatterTransform, which would give a 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 bubblePlot . scatterTransform, which would give a LensLike onto (n, Point v) -> Style v.

General scatter plot

gscatterPlot Source #

Arguments

:: (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 Axis

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.