Copyright | (C) 2015 Christopher Chalmers |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Christopher Chalmers |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module defines the various types for holding plots:
PlotOptions
b v n- Generic options all plots have.
PlotMods
b v n- Includes
PlotOptions
along with modifications to thePlotStyle
. Plot
p b- A
rawPlot
p
grouped with aPlotMods
. DynamicPlot
b v n- A wrapped up
Plot
so it can be stored in anAxis
. StyledPlot
b v n- A
DynamicPlot
with a concretePlotStyle
, ready to be rendered.
As well as other things like the Plotable
class, LegendEntries
,
HasOrientation
and HasVisibility
.
Synopsis
- data PlotOptions b v n
- class HasPlotOptions f a b | a -> b where
- plotOptions :: LensLike' f a (PlotOptions b (V a) (N a))
- plotName :: Functor f => LensLike' f a Name
- clipPlot :: Functor f => LensLike' f a Bool
- legendEntries :: Functor f => LensLike' f a [LegendEntry b (V a) (N a)]
- plotTransform :: Functor f => LensLike' f a (Transformation (V a) (N a))
- plotVisible :: Functor f => LensLike' f a Bool
- key :: (HasPlotOptions Identity a b, MonadState a m, Num (N a)) => String -> m ()
- addLegendEntry :: (HasPlotOptions Identity a b, MonadState a m) => LegendEntry b (V a) (N a) -> m ()
- data PlotMods b v n
- plotMods :: Lens' (Plot p b) (PlotMods b (V p) (N p))
- class (Typeable p, Enveloped p) => Plotable p b where
- data Plot p b
- mkPlot :: (Additive (V p), Num (N p)) => p -> Plot p b
- rawPlot :: SameSpace p p' => Lens (Plot p b) (Plot p' b) p p'
- data DynamicPlot b v n where
- DynamicPlot :: (InSpace v n p, Plotable p b) => Plot p b -> DynamicPlot b v n
- _DynamicPlot :: (Plotable p b, Typeable b) => Prism' (DynamicPlot b (V p) (N p)) (Plot p b)
- dynamicPlot :: forall p b. (Typeable p, Typeable b) => Traversal' (DynamicPlot b (V p) (N p)) (Plot p b)
- dynamicPlotMods :: Lens' (DynamicPlot b v n) (PlotMods b v n)
- data StyledPlot b v n
- styledPlot :: forall p b. Typeable p => Traversal' (StyledPlot b (V p) (N p)) p
- styleDynamic :: PlotStyle b v n -> DynamicPlot b v n -> StyledPlot b v n
- renderStyledPlot :: TypeableFloat n => AxisSpec V2 n -> StyledPlot b V2 n -> QDiagram b V2 n Any
- singleStyledPlotLegend :: StyledPlot b v n -> [(n, QDiagram b v n Any, String)]
- styledPlotLegends :: Ord n => [StyledPlot b v n] -> [(QDiagram b v n Any, 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 b v n
- data LegendPic b v n
- = DefaultLegendPic
- | CustomLegendPic (PlotStyle b v n -> QDiagram b v n Any)
- mkLegendEntry :: Num n => String -> LegendEntry b v n
- legendPicture :: Lens' (LegendEntry b v n) (LegendPic b v n)
- legendText :: Lens' (LegendEntry b v n) String
- legendPrecedence :: Lens' (LegendEntry b v n) n
- data AxisSpec v n = AxisSpec {
- _specBounds :: v (n, n)
- _specTrans :: Transformation v n
- _specScale :: v LogScale
- _specColourMap :: ColourMap
- specTrans :: forall v n. Lens' (AxisSpec v n) (Transformation v n)
- specBounds :: forall v n. Lens' (AxisSpec v n) (v (n, n))
- specScale :: forall v n. Lens' (AxisSpec v n) (v LogScale)
- scaleNum :: Floating n => (n, n) -> LogScale -> n -> n
- specPoint :: (Applicative v, Additive v, Floating n) => AxisSpec v n -> Point v n -> Point v n
- specColourMap :: forall v n. Lens' (AxisSpec v n) ColourMap
- data Placement = Placement {}
- class HasPlacement a where
- class HasGap a where
- placeAgainst :: (InSpace V2 n a, SameSpace a b, Enveloped a, HasOrigin b, Alignable 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 b v n Source #
Data type for holding information all plots must contain.
Instances
class HasPlotOptions f a b | a -> b where Source #
Class of things that have PlotOptions
.
plotOptions :: LensLike' f a (PlotOptions b (V a) (N 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 b (V a) (N a)] Source #
plotTransform :: Functor f => LensLike' f a (Transformation (V a) (N a)) Source #
plotVisible :: Functor f => LensLike' f a Bool Source #
Whether or not the plot should be shown. The BoundingBox
of the
plot will still affect the inferred axis bounds.
Instances
key :: (HasPlotOptions Identity a b, MonadState a m, Num (N a)) => 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
(ScatterPlot
v n) b) ()key
::String
->State
(DynamicPlot
b v n) ()key
::String
->State
(PlotMods
b v n) ()
If you only care about the name of the legend, use key
.
addLegendEntry :: (HasPlotOptions Identity a b, MonadState a m) => LegendEntry b (V a) (N a) -> m () Source #
Add a LegendEntry
to something with PlotOptions
. Here are some
typical examples:
addLegendEntry
::LegendEntry
b v n ->State
(Plot
(ScatterPlot
v n) b) ()addLegendEntry
::LegendEntry
b v n ->State
(DynamicPlot
b v n) ()
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 b) (PlotMods b (V p) (N p)) Source #
The modifications to the PlotOptions
and PlotStyle
in a Plot
.
Plotable class
class (Typeable p, Enveloped p) => Plotable p b where Source #
Class defining how plots should be rendered.
renderPlotable :: InSpace v n p => AxisSpec v n -> PlotStyle b v n -> p -> QDiagram b v n Any Source #
defLegendPic :: InSpace v n p => PlotStyle b v n -> p -> QDiagram b v n Any 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 :: (Additive (V p), Num (N p)) => p -> Plot p b Source #
Make a Plot
with Default
PlotOptions
.
Dynamic plot
data DynamicPlot b v n where Source #
A wrapped up Plot
, used to store plots in an Axis
.
DynamicPlot :: (InSpace v n p, Plotable p b) => Plot p b -> DynamicPlot b v n |
Instances
_DynamicPlot :: (Plotable p b, Typeable b) => Prism' (DynamicPlot b (V p) (N p)) (Plot p b) Source #
Prism for a DynamicPlot
.
dynamicPlot :: forall p b. (Typeable p, Typeable b) => Traversal' (DynamicPlot b (V p) (N p)) (Plot p b) Source #
Traversal over the dynamic plot without the Plotable
constraint
_DynamicPlot
has.
dynamicPlotMods :: Lens' (DynamicPlot b v n) (PlotMods b v n) Source #
The modifications to the PlotOptions
and PlotStyle
in a DynamicPlot
.
Styled plot
data StyledPlot b v n 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 b. Typeable p => Traversal' (StyledPlot b (V p) (N 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 b v n -> DynamicPlot b v n -> StyledPlot b v n Source #
Give a DynamicPlot
a concrete PlotStyle
.
renderStyledPlot :: TypeableFloat n => AxisSpec V2 n -> StyledPlot b V2 n -> QDiagram b V2 n Any Source #
Render a StyledPlot
given an and AxisSpec
.
singleStyledPlotLegend Source #
:: StyledPlot b v n | |
-> [(n, QDiagram b v n Any, 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
.
:: Ord n | |
=> [StyledPlot b v n] | |
-> [(QDiagram b v n Any, 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.
visible :: Lens' a Bool Source #
Lens onto whether an object should be visible when rendered.
The opposite of visible
.
Instances
HasVisibility (ColourBar b n) Source # | |
HasVisibility (MajorGridLines v n) Source # | |
Defined in Plots.Axis.Grid | |
HasVisibility (MinorGridLines v n) Source # | Hidden by default. |
Defined in Plots.Axis.Grid | |
HasVisibility (AxisLine v n) Source # | |
HasVisibility (MajorTicks v n) Source # | |
Defined in Plots.Axis.Ticks | |
HasVisibility (MinorTicks v n) Source # | |
Defined in Plots.Axis.Ticks | |
HasVisibility (Legend b n) Source # | |
HasVisibility (Plot p b) Source # | |
HasVisibility (SingleAxis b v n) Source # | |
Defined in Plots.Axis | |
HasVisibility (AxisLabel b v n) Source # | |
HasVisibility (TickLabels b v n) Source # | |
Defined in Plots.Axis.Labels | |
HasVisibility (Title b v n) Source # | |
HasVisibility (DynamicPlot b v n) Source # | |
Defined in Plots.Types | |
HasVisibility (PlotMods b v n) Source # | |
HasVisibility (PlotOptions b v n) Source # | |
Defined in Plots.Types | |
HasVisibility (StyledPlot b v n) Source # | |
Defined in Plots.Types |
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 #
Instances
Show Orientation Source # | |
Defined in Plots.Types showsPrec :: Int -> Orientation -> ShowS # show :: Orientation -> String # showList :: [Orientation] -> ShowS # | |
Eq Orientation Source # | |
Defined in Plots.Types (==) :: Orientation -> Orientation -> Bool # (/=) :: Orientation -> Orientation -> Bool # | |
Ord Orientation Source # | |
Defined in Plots.Types compare :: Orientation -> Orientation -> Ordering # (<) :: Orientation -> Orientation -> Bool # (<=) :: Orientation -> Orientation -> Bool # (>) :: Orientation -> Orientation -> Bool # (>=) :: Orientation -> Orientation -> Bool # max :: Orientation -> Orientation -> Orientation # min :: Orientation -> Orientation -> Orientation # | |
HasOrientation Orientation Source # | |
Defined in Plots.Types |
class HasOrientation a where Source #
Class of things that have an orientation.
orientation :: Lens' a Orientation Source #
Lens onto the orientation of an object.
Instances
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 b v n Source #
Data type for holding a legend entry.
Instances
type N (LegendEntry b v n) Source # | |
Defined in Plots.Types | |
type V (LegendEntry b v n) Source # | |
Defined in Plots.Types |
Type allowing use of the default legend picture (depending on the
plot) or a custom legend picture with access to the PlotStyle
.
DefaultLegendPic | |
CustomLegendPic (PlotStyle b v n -> QDiagram b v n Any) |
mkLegendEntry :: Num n => String -> LegendEntry b v n Source #
Make a legend entry with a default legendPicture
and
legendPrecedence
0 using the string as the legendText
.
legendPicture :: Lens' (LegendEntry b v n) (LegendPic b v n) Source #
The picture used in the legend entry.
legendText :: Lens' (LegendEntry b v n) String Source #
The text used in the legend entry.
legendPrecedence :: Lens' (LegendEntry b v n) n 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
AxisSpec | |
|
specBounds :: forall v n. Lens' (AxisSpec v n) (v (n, n)) Source #
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, Floating n) => AxisSpec v n -> Point v n -> Point v n 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.
class HasPlacement a where Source #
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 Rational) Source #
The direction to extend the HasGap
when positioning.
Instances
HasPlacement Placement Source # | |
HasPlacement (ColourBar b n) Source # | |
HasPlacement (Legend b n) Source # | |
HasPlacement (Title b v n) Source # | |
placeAgainst :: (InSpace V2 n a, SameSpace a b, Enveloped a, HasOrigin b, Alignable 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
.