chart-svg-0.4.0: Charting library targetting SVGs.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Chart.Hud

Description

A hud stands for head-up display, and is a collective noun used to name chart elements that assist in data interpretation or otherwise annotate and decorate data.

This includes axes, titles, borders, frames, background canvaii, tick marks and tick value labels.

Synopsis

Hud

data Hud Source #

Heads-up display additions to charts

A Hud is composed of:

  • A priority for the hud element in the chart folding process.
  • A chart tree with a state dependency on the chart being created.

Constructors

Hud 

Fields

Instances

Instances details
Generic Hud Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep Hud :: Type -> Type #

Methods

from :: Hud -> Rep Hud x #

to :: Rep Hud x -> Hud #

type Rep Hud Source # 
Instance details

Defined in Chart.Hud

type Rep Hud = D1 ('MetaData "Hud" "Chart.Hud" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) (C1 ('MetaCons "Hud" 'PrefixI 'True) (S1 ('MetaSel ('Just "priority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Priority) :*: S1 ('MetaSel ('Just "hud") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (State HudChart ChartTree))))

newtype Priority Source #

The priority of a Hud element or transformation, lower value means higher priority.

Lower priority (higher values) huds will tend to be placed on the outside of a chart.

Hud elements are rendered in order from high to low priority and the positioning of hud elements can depend on the positioning of elements that have already been included. Equal priority values will be placed in the same process step.

The first example below, based in lineExample but with the legend placed on the right and coloured frames to help accentuate effects, includes (in order of priority):

  • an inner frame, representing the core data area of the chart (Priority 1)
  • the axes (defaultPriority (5))
  • the titles (Priority 12)
  • the legend (Priority 50)
  • an outer frame which is transparent and used to pad out the chart (Priority 100).
priorityv1Example = lineExample & (#hudOptions % #frames) .~ [(1, FrameOptions (Just defaultRectStyle) 0), (100, FrameOptions (Just (defaultRectStyle & #color .~ (palette1 4 & opac' .~ 0.05) & #borderColor .~ palette1 4)) 0.1)] & #hudOptions % #legends %~ fmap (first (const (Priority 50))) & #hudOptions % #legends %~ fmap (second (set #place PlaceRight))

The second variation below drops the title priorities to below the legend:

priorityv2Example = priorityv1Example & #hudOptions % #titles %~ fmap (first (const (Priority 51)))

Constructors

Priority 

Fields

Instances

Instances details
Generic Priority Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep Priority :: Type -> Type #

Methods

from :: Priority -> Rep Priority x #

to :: Rep Priority x -> Priority #

Num Priority Source # 
Instance details

Defined in Chart.Hud

Fractional Priority Source # 
Instance details

Defined in Chart.Hud

Show Priority Source # 
Instance details

Defined in Chart.Hud

Eq Priority Source # 
Instance details

Defined in Chart.Hud

Ord Priority Source # 
Instance details

Defined in Chart.Hud

type Rep Priority Source # 
Instance details

Defined in Chart.Hud

type Rep Priority = D1 ('MetaData "Priority" "Chart.Hud" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'True) (C1 ('MetaCons "Priority" 'PrefixI 'True) (S1 ('MetaSel ('Just "priority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))

defaultPriority :: Priority Source #

An arbitrary 5.0

>>> defaultPriority
Priority {priority = 5.0}

type HudBox = Rect Double Source #

A type for Rect to represent the entire bounding box of a chart, including the Hud

type CanvasBox = Rect Double Source #

A type for Rect to represent the bounding box of the canvas portion of a chart, excluding Hud elements

type DataBox = Rect Double Source #

A type for Rect to represent the bounding box of the data elements a chart, which can be a different metric to Canvas and Hud Rects

data HudChart Source #

Type to track the split of Chart elements into Hud and Canvas

  • charts: charts that form the canvas or data elements of the chart; the rectangular dimension which is considered to be the data representation space.
  • hud: charts that form the Hud.
  • dataBox: The bounding box of the underlying data domain.

This is done to support functionality where we can choose whether to normalise the chart aspect based on the entire chart (FixedAspect) or on just the data visualisation space (CanvasAspect).

Constructors

HudChart 

Instances

Instances details
Generic HudChart Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep HudChart :: Type -> Type #

Methods

from :: HudChart -> Rep HudChart x #

to :: Rep HudChart x -> HudChart #

Show HudChart Source # 
Instance details

Defined in Chart.Hud

Eq HudChart Source # 
Instance details

Defined in Chart.Hud

type Rep HudChart Source # 
Instance details

Defined in Chart.Hud

type Rep HudChart = D1 ('MetaData "HudChart" "Chart.Hud" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) (C1 ('MetaCons "HudChart" 'PrefixI 'True) (S1 ('MetaSel ('Just "chart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ChartTree) :*: (S1 ('MetaSel ('Just "hud") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ChartTree) :*: S1 ('MetaSel ('Just "dataBox") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DataBox))))

canvasBox' :: Lens' HudChart (Maybe CanvasBox) Source #

A lens between a HudChart and the bounding box of the canvas

canvasStyleBox' :: Getter HudChart (Maybe CanvasBox) Source #

A lens between a HudChart and the bounding box of the canvas, including style extensions.

hudBox' :: Lens' HudChart (Maybe HudBox) Source #

lens between a HudChart and its hud bounding box, not including style.

hudStyleBox' :: Getter HudChart (Maybe HudBox) Source #

a lens between a HudChart and the bounding box of the hud.

Hud Processing

runHudWith Source #

Arguments

:: CanvasBox

initial canvas

-> DataBox

initial data space

-> [Hud]

huds to add

-> ChartTree

underlying chart

-> ChartTree

integrated chart tree

Combine huds and charts to form a new Chart using the supplied initial canvas and data dimensions. Note that chart data is transformed by this computation (a linear type might be useful here).

runHud Source #

Arguments

:: CanvasBox

initial canvas dimension

-> [Hud]

huds

-> ChartTree

underlying charts

-> ChartTree

integrated chart list

Combine huds and charts to form a new ChartTree with a supplied initial canvas dimension.

Note that the original chart data are transformed and irrevocably forgotten by this computation.

HudOptions

data HudOptions Source #

Typical, configurable hud elements. Anything else can be hand-coded as a Hud.

Instances

Instances details
Monoid HudOptions Source # 
Instance details

Defined in Chart.Hud

Semigroup HudOptions Source # 
Instance details

Defined in Chart.Hud

Generic HudOptions Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep HudOptions :: Type -> Type #

Show HudOptions Source # 
Instance details

Defined in Chart.Hud

Eq HudOptions Source # 
Instance details

Defined in Chart.Hud

type Rep HudOptions Source # 
Instance details

Defined in Chart.Hud

defaultHudOptions :: HudOptions Source #

The official hud options.

  • A fixed chart aspect (width:height) of 1.5
  • An x axis at the bottom and y axis at the left.
  • The default tick style for each axis of an axis bar, tick glyphs (or marks), automated tick labels, and tick (or grid) lines.
  • A high Priority (and thus inner), low-opacity frame, representing the data area of the chart.
  • A low priority (outer), transparent frame, providing some padding around the chart.

addHud :: HudOptions -> ChartTree -> ChartTree Source #

Decorate a ChartTree with HudOptions

initialCanvas :: ChartAspect -> ChartTree -> Rect Double Source #

The initial canvas before applying Huds

>>> initialCanvas (FixedAspect 1.5) (unnamed [RectChart defaultRectStyle [one]])
Rect -0.75 0.75 -0.5 0.5

colourHudOptions :: (Colour -> Colour) -> HudOptions -> HudOptions Source #

alter a colour with a function

toHuds :: HudOptions -> DataBox -> ([Hud], DataBox) Source #

Make Huds and potential data box extension; from a HudOption and an initial data box.

Hud Effects

closes :: Traversable f => f (State HudChart ChartTree) -> State HudChart () Source #

Absorb a series of state-dependent tress into state.

fromEffect :: Priority -> State HudChart () -> Hud Source #

Wrap a state effect into a Hud

applyChartAspect :: ChartAspect -> State HudChart () Source #

Apply a ChartAspect

getHudBox :: ChartAspect -> HudChart -> Maybe HudBox Source #

Supply the bounding box of the HudChart given a ChartAspect.

Hud primitives

data AxisOptions Source #

axis options

Constructors

AxisOptions 

Instances

Instances details
Generic AxisOptions Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep AxisOptions :: Type -> Type #

Show AxisOptions Source # 
Instance details

Defined in Chart.Hud

Eq AxisOptions Source # 
Instance details

Defined in Chart.Hud

type Rep AxisOptions Source # 
Instance details

Defined in Chart.Hud

flipAxis :: AxisOptions -> AxisOptions Source #

flip an axis from being an X dimension to a Y one or vice-versa.

data FrameOptions Source #

Options for hud frames

>>> defaultFrameOptions
FrameOptions {frame = Just (RectStyle {borderSize = 0.0, borderColor = Colour 0.00 0.00 0.00 0.00, color = Colour 1.00 1.00 1.00 0.02}), buffer = 0.0}

Constructors

FrameOptions 

Instances

Instances details
Generic FrameOptions Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep FrameOptions :: Type -> Type #

Show FrameOptions Source # 
Instance details

Defined in Chart.Hud

Eq FrameOptions Source # 
Instance details

Defined in Chart.Hud

type Rep FrameOptions Source # 
Instance details

Defined in Chart.Hud

type Rep FrameOptions = D1 ('MetaData "FrameOptions" "Chart.Hud" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) (C1 ('MetaCons "FrameOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "frame") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe RectStyle)) :*: S1 ('MetaSel ('Just "buffer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)))

defaultFrameOptions :: FrameOptions Source #

The official hud frame

data Place Source #

Placement of elements around (what is implicity but maybe shouldn't just be) a rectangular canvas

Instances

Instances details
Generic Place Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep Place :: Type -> Type #

Methods

from :: Place -> Rep Place x #

to :: Rep Place x -> Place #

Show Place Source # 
Instance details

Defined in Chart.Hud

Methods

showsPrec :: Int -> Place -> ShowS #

show :: Place -> String #

showList :: [Place] -> ShowS #

Eq Place Source # 
Instance details

Defined in Chart.Hud

Methods

(==) :: Place -> Place -> Bool #

(/=) :: Place -> Place -> Bool #

type Rep Place Source # 
Instance details

Defined in Chart.Hud

type Rep Place = D1 ('MetaData "Place" "Chart.Hud" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) ((C1 ('MetaCons "PlaceLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PlaceRight" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PlaceTop" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PlaceBottom" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PlaceAbsolute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point Double))))))

placeText :: Place -> Text Source #

textifier

data AxisBar Source #

The bar on an axis representing the x or y plane.

>>> defaultAxisBar
AxisBar {style = RectStyle {borderSize = 0.0, borderColor = Colour 0.00 0.00 0.00 0.00, color = Colour 0.05 0.05 0.05 0.40}, size = 4.0e-3, buffer = 1.0e-2, overhang = 2.0e-3}

Constructors

AxisBar 

Fields

Instances

Instances details
Generic AxisBar Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep AxisBar :: Type -> Type #

Methods

from :: AxisBar -> Rep AxisBar x #

to :: Rep AxisBar x -> AxisBar #

Show AxisBar Source # 
Instance details

Defined in Chart.Hud

Eq AxisBar Source # 
Instance details

Defined in Chart.Hud

Methods

(==) :: AxisBar -> AxisBar -> Bool #

(/=) :: AxisBar -> AxisBar -> Bool #

type Rep AxisBar Source # 
Instance details

Defined in Chart.Hud

defaultAxisBar :: AxisBar Source #

The official axis bar

data Title Source #

Options for titles. Defaults to center aligned, and placed at Top of the hud

>>> defaultTitle "title"
Title {text = "title", style = TextStyle {size = 0.12, color = Colour 0.05 0.05 0.05 1.00, anchor = AnchorMiddle, hsize = 0.45, vsize = 1.1, vshift = -0.25, rotation = Nothing, scalex = ScaleX, frame = Nothing}, place = PlaceTop, anchor = AnchorMiddle, buffer = 4.0e-2}

Constructors

Title 

Instances

Instances details
Generic Title Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep Title :: Type -> Type #

Methods

from :: Title -> Rep Title x #

to :: Rep Title x -> Title #

Show Title Source # 
Instance details

Defined in Chart.Hud

Methods

showsPrec :: Int -> Title -> ShowS #

show :: Title -> String #

showList :: [Title] -> ShowS #

Eq Title Source # 
Instance details

Defined in Chart.Hud

Methods

(==) :: Title -> Title -> Bool #

(/=) :: Title -> Title -> Bool #

type Rep Title Source # 
Instance details

Defined in Chart.Hud

defaultTitle :: Text -> Title Source #

The official hud title

data Ticks Source #

xy coordinate markings

>>> defaultTicks
Ticks {style = TickRound (FormatN {fstyle = FSCommaPrec, sigFigs = Just 1, maxDistinguishIterations = 4, addLPad = True, cutRightZeros = True}) 8 TickExtend, gtick = Just (GlyphStyle {size = 3.0e-2, color = Colour 0.05 0.05 0.05 0.40, borderColor = Colour 0.05 0.05 0.05 0.40, borderSize = 4.0e-3, shape = VLineGlyph, rotation = Nothing, translate = Nothing},3.0e-2), ttick = Just (TextStyle {size = 5.0e-2, color = Colour 0.05 0.05 0.05 1.00, anchor = AnchorMiddle, hsize = 0.45, vsize = 1.1, vshift = -0.25, rotation = Nothing, scalex = ScaleX, frame = Nothing},3.3e-2), ltick = Just (LineStyle {size = 5.0e-3, color = Colour 0.05 0.05 0.05 0.05, linecap = Nothing, linejoin = Nothing, dasharray = Nothing, dashoffset = Nothing},0.0)}

Instances

Instances details
Generic Ticks Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep Ticks :: Type -> Type #

Methods

from :: Ticks -> Rep Ticks x #

to :: Rep Ticks x -> Ticks #

Show Ticks Source # 
Instance details

Defined in Chart.Hud

Methods

showsPrec :: Int -> Ticks -> ShowS #

show :: Ticks -> String #

showList :: [Ticks] -> ShowS #

Eq Ticks Source # 
Instance details

Defined in Chart.Hud

Methods

(==) :: Ticks -> Ticks -> Bool #

(/=) :: Ticks -> Ticks -> Bool #

type Rep Ticks Source # 
Instance details

Defined in Chart.Hud

defaultGlyphTick :: GlyphStyle Source #

The official glyph tick

defaultTextTick :: TextStyle Source #

The official text tick

defaultLineTick :: LineStyle Source #

The official line tick

defaultTicks :: Ticks Source #

The official tick

data TickStyle Source #

Style of tick marks on an axis.

Constructors

TickNone

no ticks on axis

TickLabels [Text]

specific labels (equidistant placement)

TickRound FormatN Int TickExtend

sensibly rounded ticks, a guide to how many, and whether to extend beyond the data bounding box

TickExact FormatN Int

exactly n equally spaced ticks

TickPlaced [(Double, Text)]

specific labels and placement

Instances

Instances details
Generic TickStyle Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep TickStyle :: Type -> Type #

Show TickStyle Source # 
Instance details

Defined in Chart.Hud

Eq TickStyle Source # 
Instance details

Defined in Chart.Hud

type Rep TickStyle Source # 
Instance details

Defined in Chart.Hud

defaultTickStyle :: TickStyle Source #

The official tick style

>>> defaultTickStyle
TickRound (FormatN {fstyle = FSCommaPrec, sigFigs = Just 1, maxDistinguishIterations = 4, addLPad = True, cutRightZeros = True}) 8 TickExtend

data TickExtend Source #

Whether Ticks are allowed to extend the data range

Constructors

TickExtend 
NoTickExtend 

Instances

Instances details
Generic TickExtend Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep TickExtend :: Type -> Type #

Show TickExtend Source # 
Instance details

Defined in Chart.Hud

Eq TickExtend Source # 
Instance details

Defined in Chart.Hud

type Rep TickExtend Source # 
Instance details

Defined in Chart.Hud

type Rep TickExtend = D1 ('MetaData "TickExtend" "Chart.Hud" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) (C1 ('MetaCons "TickExtend" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoTickExtend" 'PrefixI 'False) (U1 :: Type -> Type))

adjustTicks :: Adjustments -> HudBox -> DataBox -> Place -> Ticks -> Ticks Source #

adjust Tick for sane font sizes etc

data Adjustments Source #

options for prettifying axis decorations

>>> defaultAdjustments
Adjustments {maxXRatio = 8.0e-2, maxYRatio = 6.0e-2, angledRatio = 0.12, allowDiagonal = True}

Instances

Instances details
Generic Adjustments Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep Adjustments :: Type -> Type #

Show Adjustments Source # 
Instance details

Defined in Chart.Hud

Eq Adjustments Source # 
Instance details

Defined in Chart.Hud

type Rep Adjustments Source # 
Instance details

Defined in Chart.Hud

type Rep Adjustments = D1 ('MetaData "Adjustments" "Chart.Hud" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) (C1 ('MetaCons "Adjustments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "maxXRatio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "maxYRatio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "angledRatio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "allowDiagonal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))

defaultAdjustments :: Adjustments Source #

The official hud adjustments.

data LegendOptions Source #

Legend options

>>> defaultLegendOptions
LegendOptions {size = 0.3, buffer = 0.1, vgap = 0.2, hgap = 0.1, textStyle = TextStyle {size = 0.18, color = Colour 0.05 0.05 0.05 1.00, anchor = AnchorMiddle, hsize = 0.45, vsize = 1.1, vshift = -0.25, rotation = Nothing, scalex = ScaleX, frame = Nothing}, innerPad = 0.1, outerPad = 2.0e-2, frame = Just (RectStyle {borderSize = 1.0e-2, borderColor = Colour 0.05 0.05 0.05 1.00, color = Colour 0.05 0.05 0.05 0.00}), place = PlaceRight, overallScale = 0.25, content = []}

Instances

Instances details
Generic LegendOptions Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep LegendOptions :: Type -> Type #

Show LegendOptions Source # 
Instance details

Defined in Chart.Hud

Eq LegendOptions Source # 
Instance details

Defined in Chart.Hud

type Rep LegendOptions Source # 
Instance details

Defined in Chart.Hud

defaultLegendOptions :: LegendOptions Source #

The official legend options

Option to Hud

frameHud :: FrameOptions -> State HudChart ChartTree Source #

Make a frame hud transformation.

legendHud :: LegendOptions -> ChartTree -> State HudChart ChartTree Source #

Make a legend hud element, from a bespoke ChartTree.