| 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 |
Plots.Types
Contents
Description
This module defines the various types for holding plots:
PlotOptionsv- Generic options all plots have.
PlotModsv- Includes
PlotOptionsalong with modifications to thePlotStyle. Plotp- A
rawPlotpgrouped with aPlotMods. DynamicPlotv- A wrapped up
Plotso it can be stored in anAxis. StyledPlotv- A
DynamicPlotwith a concretePlotStyle, ready to be rendered.
As well as other things like the Plotable class, LegendEntries,
HasOrientation and HasVisibility.
Synopsis
- data PlotOptions v
- class HasPlotOptions f a where
- plotOptions :: LensLike' f a (PlotOptions (V a))
- plotName :: Functor f => LensLike' f a Name
- clipPlot :: Functor f => LensLike' f a Bool
- legendEntries :: Functor f => LensLike' f a [LegendEntry (V a)]
- plotTransform :: Functor f => LensLike' f a (Transformation (V a) Double)
- plotVisible :: Functor f => LensLike' f a Bool
- key :: (HasPlotOptions Identity a, MonadState a m) => String -> m ()
- addLegendEntry :: (HasPlotOptions Identity a, MonadState a m) => LegendEntry (V a) -> m ()
- data PlotMods v
- plotMods :: Lens' (Plot p) (PlotMods (V p))
- class (Typeable p, Enveloped p, N p ~ Double) => Plotable p where
- renderPlotable :: InSpace v Double p => AxisSpec v -> PlotStyle v -> p -> Diagram v
- defLegendPic :: InSpace v Double p => PlotStyle v -> p -> Diagram v
- data Plot p
- mkPlot :: (InSpace v Double p, HasBasis v, Foldable v) => p -> Plot p
- rawPlot :: SameSpace p p' => Lens (Plot p) (Plot p') p p'
- data DynamicPlot v where
- DynamicPlot :: (InSpace v Double p, Plotable p) => Plot p -> DynamicPlot v
- _DynamicPlot :: Plotable p => Prism' (DynamicPlot (V p)) (Plot p)
- dynamicPlot :: forall p. Typeable p => Traversal' (DynamicPlot (V p)) (Plot p)
- dynamicPlotMods :: Lens' (DynamicPlot v) (PlotMods v)
- data StyledPlot v
- styledPlot :: forall p. Typeable p => Traversal' (StyledPlot (V p)) p
- styleDynamic :: PlotStyle v -> DynamicPlot v -> StyledPlot v
- renderStyledPlot :: HasLinearMap v => AxisSpec v -> StyledPlot v -> Diagram v
- singleStyledPlotLegend :: StyledPlot v -> [(Double, Diagram v, String)]
- styledPlotLegends :: [StyledPlot v] -> [(Diagram v, String)]
- class HasVisibility a where
- hide :: (MonadState s m, HasVisibility a) => ASetter' s a -> m ()
- display :: (MonadState s m, HasVisibility a) => ASetter' s a -> m ()
- data Orientation
- class HasOrientation a where
- orientation :: Lens' a Orientation
- orient :: HasOrientation o => o -> a -> a -> a
- horizontal :: HasOrientation a => Lens' a Bool
- vertical :: HasOrientation a => Lens' a Bool
- data LegendEntry v
- data LegendPic v
- = DefaultLegendPic
- | CustomLegendPic (PlotStyle v -> Diagram v)
- mkLegendEntry :: String -> LegendEntry v
- legendPicture :: Lens' (LegendEntry v) (LegendPic v)
- legendText :: Lens' (LegendEntry v) String
- legendPrecedence :: Lens' (LegendEntry v) Double
- data AxisSpec v = AxisSpec {
- _specBounds :: v (Double, Double)
- _specTrans :: Transformation v Double
- _specScale :: v LogScale
- _specColourMap :: ColourMap
- specTrans :: forall v. Lens' (AxisSpec v) (Transformation v Double)
- specBounds :: forall v. Lens' (AxisSpec v) (v (Double, Double))
- specScale :: forall v. Lens' (AxisSpec v) (v LogScale)
- scaleNum :: Floating n => (n, n) -> LogScale -> n -> n
- specPoint :: (Applicative v, Additive v, Foldable v) => AxisSpec v -> Point v Double -> Point v Double
- specColourMap :: forall v. Lens' (AxisSpec v) ColourMap
- data Placement = Placement {}
- class HasPlacement a where
- placement :: Lens' a Placement
- placementAt :: Lens' a (V2 Rational)
- placementAnchor :: Lens' a (V2 Rational)
- gapDirection :: Lens' a (Direction V2 Double)
- class HasGap a where
- placeAgainst :: (InSpace V2 n a, SameSpace a b, Enveloped a, Enveloped b, HasOrigin b) => a -> Placement -> n -> b -> b
- topLeft :: Placement
- top :: Placement
- topRight :: Placement
- left :: Placement
- right :: Placement
- bottomLeft :: Placement
- bottom :: Placement
- bottomRight :: Placement
- leftAbove :: Placement
- leftTop :: Placement
- leftMid :: Placement
- leftBottom :: Placement
- leftBelow :: Placement
- midAbove :: Placement
- midBelow :: Placement
- rightAbove :: Placement
- rightTop :: Placement
- rightMid :: Placement
- rightBottom :: Placement
- rightBelow :: Placement
Plot options
data PlotOptions v Source #
Data type for holding information all plots must contain.
Instances
class HasPlotOptions f a where Source #
Class of things that have PlotOptions.
Minimal complete definition
Methods
plotOptions :: LensLike' f a (PlotOptions (V a)) Source #
Lens onto the PlotOptions.
plotName :: Functor f => LensLike' f a Name Source #
The Name applied to the plot. This gives a way to reference a
specific plot in a rendered axis.
clipPlot :: Functor f => LensLike' f a Bool Source #
legendEntries :: Functor f => LensLike' f a [LegendEntry (V a)] Source #
plotTransform :: Functor f => LensLike' f a (Transformation (V a) Double) Source #
Instances
key :: (HasPlotOptions Identity a, MonadState a m) => String -> m () Source #
Add a LegendEntry to something with PlotOptions using the
String as the legendText and a DefaultLegendPic. Here are
some typical examples:
key::String->State(Plot(ScatterPlotv)) ()key::String->State(DynamicPlotv) ()key::String->State(PlotModsv) ()
If you only care about the name of the legend, use key.
addLegendEntry :: (HasPlotOptions Identity a, MonadState a m) => LegendEntry (V a) -> m () Source #
Add a LegendEntry to something with PlotOptions. Here are some
typical examples:
addLegendEntry::LegendEntryv ->State(Plot(ScatterPlotv)) ()addLegendEntry::LegendEntryv ->State(DynamicPlotv) ()
If you only care about the name of the legend, use key.
Plot modifications
A PlotOptions with modifications to a PlotStyle.
Instances
plotMods :: Lens' (Plot p) (PlotMods (V p)) Source #
The modifications to the PlotOptions and PlotStyle in a Plot.
Plotable class
class (Typeable p, Enveloped p, N p ~ Double) => Plotable p where Source #
Class defining how plots should be rendered.
Minimal complete definition
Methods
renderPlotable :: InSpace v Double p => AxisSpec v -> PlotStyle v -> p -> Diagram v Source #
defLegendPic :: InSpace v Double p => PlotStyle v -> p -> Diagram v Source #
The default legend picture when the LegendPic is
DefaultLegendPic.
Instances
Plot types
Parameterised plot
A parameterised plot, together with a PlotMods. This type has an
instance of many classes for modifying specific plots.
Instances
mkPlot :: (InSpace v Double p, HasBasis v, Foldable v) => p -> Plot p Source #
Make a Plot with Default PlotOptions.
Dynamic plot
data DynamicPlot v where Source #
A wrapped up Plot, used to store plots in an Axis.
Constructors
| DynamicPlot :: (InSpace v Double p, Plotable p) => Plot p -> DynamicPlot v |
Instances
_DynamicPlot :: Plotable p => Prism' (DynamicPlot (V p)) (Plot p) Source #
Prism for a DynamicPlot.
dynamicPlot :: forall p. Typeable p => Traversal' (DynamicPlot (V p)) (Plot p) Source #
Traversal over the dynamic plot without the Plotable constraint
_DynamicPlot has.
dynamicPlotMods :: Lens' (DynamicPlot v) (PlotMods v) Source #
The modifications to the PlotOptions and PlotStyle in a DynamicPlot.
Styled plot
data StyledPlot v Source #
A DynamicPlot with a concrete style. This is suitable for being
rendered with renderStyledPlot and get extract the legend entries
with styledPlotLegend.
You can make a StyledPlot with styleDynamic
Instances
styledPlot :: forall p. Typeable p => Traversal' (StyledPlot (V p)) p Source #
Traversal over a raw plot of a styled plot. The type of the plot must match for the traversal to be successful.
styleDynamic :: PlotStyle v -> DynamicPlot v -> StyledPlot v Source #
Give a DynamicPlot a concrete PlotStyle.
renderStyledPlot :: HasLinearMap v => AxisSpec v -> StyledPlot v -> Diagram v Source #
Render a StyledPlot given an and AxisSpec.
singleStyledPlotLegend Source #
Arguments
| :: StyledPlot v | |
| -> [(Double, Diagram v, String)] | (z-order, legend pic, legend text) |
Get the legend rendered entries from a single styled plot. The
resulting entries are in no particular order. See also
styledPlotLegends.
Arguments
| :: [StyledPlot v] | |
| -> [(Diagram v, String)] | [(legend pic, legend text)] |
Render a list of legend entries, in order.
Miscellaneous
Visibility
class HasVisibility a where Source #
Class of objects that can be hidden.
Minimal complete definition
Methods
visible :: Lens' a Bool Source #
Lens onto whether an object should be visible when rendered.
The opposite of visible.
Instances
| HasVisibility Legend Source # | |
| HasVisibility ColourBar Source # | |
| HasVisibility (PlotOptions v) Source # | |
Defined in Plots.Types | |
| HasVisibility (StyledPlot v) Source # | |
Defined in Plots.Types | |
| HasVisibility (DynamicPlot v) Source # | |
Defined in Plots.Types | |
| HasVisibility (Plot p) Source # | |
| HasVisibility (PlotMods v) Source # | |
| HasVisibility (Title v) Source # | |
| HasVisibility (AxisLine v) Source # | |
| HasVisibility (TickLabels v) Source # | |
Defined in Plots.Axis.Labels | |
| HasVisibility (AxisLabel v) Source # | |
| HasVisibility (MinorGridLines v) Source # | Hidden by default. |
Defined in Plots.Axis.Grid | |
| HasVisibility (MajorGridLines v) Source # | |
Defined in Plots.Axis.Grid | |
| HasVisibility (MinorTicks v) Source # | |
Defined in Plots.Axis.Ticks | |
| HasVisibility (MajorTicks v) Source # | |
Defined in Plots.Axis.Ticks | |
| HasVisibility (SingleAxis v) Source # | |
Defined in Plots.Axis | |
hide :: (MonadState s m, HasVisibility a) => ASetter' s a -> m () Source #
display :: (MonadState s m, HasVisibility a) => ASetter' s a -> m () Source #
Orientation
data Orientation Source #
Constructors
| Horizontal | |
| Vertical |
Instances
| Eq Orientation Source # | |
Defined in Plots.Types | |
| Ord Orientation Source # | |
Defined in Plots.Types Methods compare :: Orientation -> Orientation -> Ordering # (<) :: Orientation -> Orientation -> Bool # (<=) :: Orientation -> Orientation -> Bool # (>) :: Orientation -> Orientation -> Bool # (>=) :: Orientation -> Orientation -> Bool # max :: Orientation -> Orientation -> Orientation # min :: Orientation -> Orientation -> Orientation # | |
| Show Orientation Source # | |
Defined in Plots.Types Methods showsPrec :: Int -> Orientation -> ShowS # show :: Orientation -> String # showList :: [Orientation] -> ShowS # | |
| HasOrientation Orientation Source # | |
Defined in Plots.Types Methods | |
class HasOrientation a where Source #
Class of things that have an orientation.
Instances
| HasOrientation Orientation Source # | |
Defined in Plots.Types Methods | |
| HasOrientation Legend Source # | |
Defined in Plots.Legend Methods | |
| HasOrientation ColourBar Source # | |
Defined in Plots.Axis.ColourBar Methods | |
| HasOrientation HistogramOptions Source # | |
Defined in Plots.Types.Histogram Methods | |
| HasOrientation HistogramPlot Source # | |
Defined in Plots.Types.Histogram Methods | |
| HasOrientation BarPlot Source # | |
Defined in Plots.Types.Bar Methods | |
| HasOrientation BarLayout Source # | |
Defined in Plots.Types.Bar Methods | |
| HasOrientation p => HasOrientation (Plot p) Source # | |
Defined in Plots.Types Methods orientation :: Lens' (Plot p) Orientation Source # | |
| HasOrientation (MultiBarState a) Source # | |
Defined in Plots.Types.Bar Methods orientation :: Lens' (MultiBarState a) Orientation Source # | |
orient :: HasOrientation o => o -> a -> a -> a Source #
Pick the first a if the object has Horizontal orientation and
the second a if the object has a Vertical orientation.
horizontal :: HasOrientation a => Lens' a Bool Source #
Lens onto whether an object's orientation is horizontal.
vertical :: HasOrientation a => Lens' a Bool Source #
Lens onto whether an object's orientation is vertical.
Legend entries
data LegendEntry v Source #
Data type for holding a legend entry.
Instances
| type N (LegendEntry v) Source # | |
Defined in Plots.Types | |
| type V (LegendEntry v) Source # | |
Defined in Plots.Types type V (LegendEntry v) = v | |
Type allowing use of the default legend picture (depending on the
plot) or a custom legend picture with access to the PlotStyle.
Constructors
| DefaultLegendPic | |
| CustomLegendPic (PlotStyle v -> Diagram v) |
mkLegendEntry :: String -> LegendEntry v Source #
Make a legend entry with a default legendPicture and
legendPrecedence 0 using the string as the legendText.
legendPicture :: Lens' (LegendEntry v) (LegendPic v) Source #
The picture used in the legend entry.
legendText :: Lens' (LegendEntry v) String Source #
The text used in the legend entry.
legendPrecedence :: Lens' (LegendEntry v) Double Source #
The order in which the legend entries are rendered. If precedences are equal, the entries are put in the order they are added to the axis.
Default is 0.
Axis spec
Constructors
| AxisSpec | |
Fields
| |
scaleNum :: Floating n => (n, n) -> LogScale -> n -> n Source #
Scale a number by log10-ing it and linearly scaling it so it's within the same range.
specPoint :: (Applicative v, Additive v, Foldable v) => AxisSpec v -> Point v Double -> Point v Double Source #
Apply log scaling and the transform to a point.
Positioning
A Position is a point on an axis together with an anchor and a
direction for the gap.
Constructors
| Placement | |
class HasPlacement a where Source #
Minimal complete definition
Methods
placement :: Lens' a Placement Source #
placementAt :: Lens' a (V2 Rational) Source #
The position relative to the axis. V2 0 0 corresponds to the
bottom left corner, V2 1 1 is the top right corner.
placementAnchor :: Lens' a (V2 Rational) Source #
The anchor used for the object being positioned. V2 0 0
corresponds to the bottom left corner, V2 1 1 is the top right
corner.
gapDirection :: Lens' a (Direction V2 Double) Source #
The direction to extend the gap when positioning.
Instances
| HasPlacement Placement Source # | |
| HasPlacement Legend Source # | |
| HasPlacement ColourBar Source # | |
| HasPlacement (Title v) Source # | |
placeAgainst :: (InSpace V2 n a, SameSpace a b, Enveloped a, Enveloped b, HasOrigin b) => a -> Placement -> n -> b -> b Source #
A tool for aligned one object to another. Positions b around the
bounding box of a by translating b.