plots-0.1.1.3: Diagrams based plotting library
Copyright(C) 2016 Christopher Chalmers
LicenseBSD-style (see the file LICENSE)
MaintainerChristopher Chalmers
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Plots.Types.Pie

Description

A pie plot is a circular statistical graphic, which is divided into slices to illustrate numerical proportion.

(see piePlot example for code to make this plot)

Synopsis

Pie plot

data PieState b n a Source #

The state used to draw a part chart made of multiple pie wedges.

Instances

Instances details
Applicative f => HasWedge f (PieState b n a) Source # 
Instance details

Defined in Plots.Types.Pie

type N (PieState b n a) Source # 
Instance details

Defined in Plots.Types.Pie

type N (PieState b n a) = n
type V (PieState b n a) Source # 
Instance details

Defined in Plots.Types.Pie

type V (PieState b n a) = V2

piePlot Source #

Arguments

:: (MonadState (Axis b Polar n) m, Plotable (Wedge n) b, Foldable f) 
=> f a

data for each wedge

-> (a -> n)

extract weight of each wedge

-> State (PieState b n a) () 
-> m () 

Make a pie plot from a list of data by making a series of wedge plots.

Example

Expand

import Plots

pieData = [("red", 3), ("blue", 4), ("green", 2), ("purple", 5)]

piePlotAxis :: Axis B Polar Double
piePlotAxis = polarAxis &~ do
  piePlot pieData snd $ wedgeKeys fst
  hide (axes . traversed)
piePlotExample = renderAxis piePlotAxis

piePlot' Source #

Arguments

:: (MonadState (Axis b Polar n) m, Plotable (Wedge n) b, Foldable f) 
=> f n

weight of each wedge

-> m () 

Make a pie plot from list of values without any changes.

Example

Expand

import Plots

piePlotAxis' :: Axis B Polar Double
piePlotAxis' = polarAxis &~ do
  piePlot' [1,3,5,2]
  wedgeInnerRadius .= 0.5
  hide (axes . traversed)
pieExample' = renderAxis piePlotAxis'

onWedges :: (a -> State (Plot (Wedge n) b) ()) -> State (PieState b n a) () Source #

Modify the state for each wedge given the data entry.

Some common lenses to use on the Wedge:

  • plotColour - change the colour of the bars
  • areaStyle - modify the style of the bars
  • key - add a legend entry for that group of bars
  • wedgeOffset - the offset of the wedge from the center

wedgeKeys :: Num n => (a -> String) -> State (PieState b n a) () Source #

Add a legend entry for each item given a function that extracts the item's name.

Wedges

data Wedge n Source #

Contains information to draw a single wedge of a pie. It is not intended to be drawn directly. Instead use piePlot.

Instances

Instances details
HasWedge f (Wedge n) Source # 
Instance details

Defined in Plots.Types.Pie

RealFloat n => Enveloped (Wedge n) Source # 
Instance details

Defined in Plots.Types.Pie

Methods

getEnvelope :: Wedge n -> Envelope (V (Wedge n)) (N (Wedge n)) #

(TypeableFloat n, Renderable (Path V2 n) b) => Plotable (Wedge n) b Source # 
Instance details

Defined in Plots.Types.Pie

Methods

renderPlotable :: forall (v :: Type -> Type) n0. InSpace v n0 (Wedge n) => AxisSpec v n0 -> PlotStyle b v n0 -> Wedge n -> QDiagram b v n0 Any Source #

defLegendPic :: forall (v :: Type -> Type) n0. InSpace v n0 (Wedge n) => PlotStyle b v n0 -> Wedge n -> QDiagram b v n0 Any Source #

type N (Wedge n) Source # 
Instance details

Defined in Plots.Types.Pie

type N (Wedge n) = n
type V (Wedge n) Source # 
Instance details

Defined in Plots.Types.Pie

type V (Wedge n) = V2

mkWedge Source #

Arguments

:: Num n 
=> Direction V2 n

starting direction

-> Angle n

width of wedge

-> Wedge n

resulting wedge

Create a pie wedge with unit radius, starting at direction d with width theta.

class HasWedge f a where Source #

Minimal complete definition

pieWedge

Methods

pieWedge :: LensLike' f a (Wedge (N a)) Source #

Description on how to draw a wedge.

wedgeOuterRadius :: Functor f => LensLike' f a (N a) Source #

The outside radius of the wedge. Default is 1.

wedgeInnerRadius :: Functor f => LensLike' f a (N a) Source #

The inside radius of the wedge. Default is $0$.

wedgeOffset :: Functor f => LensLike' f a (N a) Source #

The offset of the wedge from the center.

wedgeWidth :: Functor f => LensLike' f a (Angle (N a)) Source #

The width of the wedge, starting from the wedgeDirection.

wedgeDirection :: Functor f => LensLike' f a (Direction V2 (N a)) Source #

The inititial direction of the wedge.

Instances

Instances details
HasWedge f (Wedge n) Source # 
Instance details

Defined in Plots.Types.Pie

(Functor f, HasWedge f a) => HasWedge f (Plot a b) Source # 
Instance details

Defined in Plots.Types.Pie

Methods

pieWedge :: LensLike' f (Plot a b) (Wedge (N (Plot a b))) Source #

wedgeOuterRadius :: LensLike' f (Plot a b) (N (Plot a b)) Source #

wedgeInnerRadius :: LensLike' f (Plot a b) (N (Plot a b)) Source #

wedgeOffset :: LensLike' f (Plot a b) (N (Plot a b)) Source #

wedgeWidth :: LensLike' f (Plot a b) (Angle (N (Plot a b))) Source #

wedgeDirection :: LensLike' f (Plot a b) (Direction V2 (N (Plot a b))) Source #

(BaseSpace c ~ V2, Settable f, Typeable n) => HasWedge f (Axis b c n) Source # 
Instance details

Defined in Plots.Types.Pie

Methods

pieWedge :: LensLike' f (Axis b c n) (Wedge (N (Axis b c n))) Source #

wedgeOuterRadius :: LensLike' f (Axis b c n) (N (Axis b c n)) Source #

wedgeInnerRadius :: LensLike' f (Axis b c n) (N (Axis b c n)) Source #

wedgeOffset :: LensLike' f (Axis b c n) (N (Axis b c n)) Source #

wedgeWidth :: LensLike' f (Axis b c n) (Angle (N (Axis b c n))) Source #

wedgeDirection :: LensLike' f (Axis b c n) (Direction V2 (N (Axis b c n))) Source #

(Applicative f, Typeable b, v ~ V2, Typeable n) => HasWedge f (DynamicPlot b v n) Source # 
Instance details

Defined in Plots.Types.Pie

(v ~ V2, Applicative f, Typeable n) => HasWedge f (StyledPlot b v n) Source # 
Instance details

Defined in Plots.Types.Pie

Applicative f => HasWedge f (PieState b n a) Source # 
Instance details

Defined in Plots.Types.Pie

wedgePlot :: (v ~ BaseSpace c, v ~ V2, PointLike v n (Polar n), MonadState (Axis b c n) m, Plotable (Wedge n) b) => Direction V2 n -> Angle n -> State (Plot (Wedge n) b) () -> m () Source #

Add a single PiePlot to the AxisState from a data set.

Example

Expand

import Plots

wedgePlotAxis :: Axis B Polar Double
wedgePlotAxis = polarAxis &~ do
  wedgePlot xDir (38@@deg) $ key "wedge"
wedgeExample = renderAxis wedgePlotAxis