chart-svg-0.6.0.0: Charting library targetting SVGs.
Safe HaskellSafe-Inferred
LanguageGHC2021

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

newtype Hud Source #

Heads-up display additions to charts

Constructors

Hud 

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.6.0.0-HjsGv1l8hv76XDZORokPY6" 'True) (C1 ('MetaCons "Hud" 'PrefixI 'True) (S1 ('MetaSel ('Just "phud") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Priority (HudChart -> ChartTree)))))

data Priority a 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 (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)] & over (#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
Functor Priority Source # 
Instance details

Defined in Chart.Hud

Methods

fmap :: (a -> b) -> Priority a -> Priority b #

(<$) :: a -> Priority b -> Priority a #

Generic (Priority a) Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep (Priority a) :: Type -> Type #

Methods

from :: Priority a -> Rep (Priority a) x #

to :: Rep (Priority a) x -> Priority a #

Show a => Show (Priority a) Source # 
Instance details

Defined in Chart.Hud

Methods

showsPrec :: Int -> Priority a -> ShowS #

show :: Priority a -> String #

showList :: [Priority a] -> ShowS #

Eq a => Eq (Priority a) Source # 
Instance details

Defined in Chart.Hud

Methods

(==) :: Priority a -> Priority a -> Bool #

(/=) :: Priority a -> Priority a -> Bool #

Ord a => Ord (Priority a) Source # 
Instance details

Defined in Chart.Hud

Methods

compare :: Priority a -> Priority a -> Ordering #

(<) :: Priority a -> Priority a -> Bool #

(<=) :: Priority a -> Priority a -> Bool #

(>) :: Priority a -> Priority a -> Bool #

(>=) :: Priority a -> Priority a -> Bool #

max :: Priority a -> Priority a -> Priority a #

min :: Priority a -> Priority a -> Priority a #

type Rep (Priority a) Source # 
Instance details

Defined in Chart.Hud

type Rep (Priority a) = D1 ('MetaData "Priority" "Chart.Hud" "chart-svg-0.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) (C1 ('MetaCons "Priority" 'PrefixI 'True) (S1 ('MetaSel ('Just "priority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "item") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

type ChartBox = Rect Double Source #

A type for Rect to represent the bounding box of a chart.

type DataBox = Rect Double Source #

A type for Rect to represent the bounding box of the data.

data HudChart Source #

Named pair 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.

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.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) (C1 ('MetaCons "HudChart" 'PrefixI 'True) (S1 ('MetaSel ('Just "chartSection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChartTree) :*: S1 ('MetaSel ('Just "hudSection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChartTree)))

data HudChartSection Source #

A section of a HudChart

Constructors

CanvasSection

The canvas without any style allowances

CanvasStyleSection

The canvas portion including style boundaries.

HudSection

The hud and canvas sections, not including style.

HudStyleSection

The hud and canvas sections, including style

Instances

Instances details
Generic HudChartSection Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep HudChartSection :: Type -> Type #

Show HudChartSection Source # 
Instance details

Defined in Chart.Hud

Eq HudChartSection Source # 
Instance details

Defined in Chart.Hud

type Rep HudChartSection Source # 
Instance details

Defined in Chart.Hud

type Rep HudChartSection = D1 ('MetaData "HudChartSection" "Chart.Hud" "chart-svg-0.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) ((C1 ('MetaCons "CanvasSection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CanvasStyleSection" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HudSection" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HudStyleSection" 'PrefixI 'False) (U1 :: Type -> Type)))

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.

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

alter a colour with a function

Hud Processing

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

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

appendHud :: ChartTree -> HudChart -> HudChart Source #

Append a ChartTree to the hud section of a HudChart.

makeHuds :: [HudChart -> ChartTree] -> HudChart -> HudChart Source #

Add huds to the hud section of a HudChart, given a list of hud makers.

fromHudChart :: HudChart -> ChartTree Source #

Convert a HudChart to a ChartTree labelling the hud and chart sections.

runHudWith Source #

Arguments

:: ChartBox

initial canvas

-> [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).

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

Decorate a ChartTree with HudOptions

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

Compute a Rect representing the initial chart canvas from a ChartAspect and maybe a ChartTree, before the addition of style and hud elements.

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

finalCanvas :: ChartAspect -> Maybe ChartTree -> Rect Double Source #

Compute a Rect representing the final chart canvas from a ChartAspect and maybe a ChartTree. The difference between initialCanvas and finalCanvas is using the actual chart canvas for CanvasAspect.

>>> finalCanvas (CanvasAspect 1.5) (Just $ unnamed [RectChart defaultRectStyle [one]])
Rect (-0.5) 0.5 (-0.5) 0.5

Hud options

data AxisOptions Source #

axis options

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

defaultXAxisOptions :: AxisOptions Source #

The official X-axis

defaultYAxisOptions :: AxisOptions Source #

The official Y-axis

data FrameOptions Source #

Options for hud frames

>>> defaultFrameOptions
FrameOptions {frame = Just (Style {size = 6.0e-2, borderSize = 0.0, color = Colour 1.00 1.00 1.00 0.02, borderColor = Colour 0.00 0.00 0.00 0.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}), anchorTo = HudStyleSection, buffer = 0.0}

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.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) (C1 ('MetaCons "FrameOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "frame") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Style)) :*: (S1 ('MetaSel ('Just "anchorTo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HudChartSection) :*: S1 ('MetaSel ('Just "buffer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (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.6.0.0-HjsGv1l8hv76XDZORokPY6" '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 'DecidedLazy) (Rec0 (Point Double))))))

flipPlace :: Place -> Place Source #

Flip Place to the opposite side, or unchanged if PlaceAbsolute.

>>> flipPlace PlaceLeft
PlaceRight

data AxisBar Source #

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

>>> defaultAxisBar
AxisBar {style = Style {size = 6.0e-2, borderSize = 0.0, color = Colour 0.05 0.05 0.05 0.40, borderColor = Colour 0.00 0.00 0.00 0.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}, size = 4.0e-3, buffer = 1.0e-2, overhang = 2.0e-3, anchorTo = CanvasSection}

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 TitleOptions Source #

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

>>> defaultTitleOptions "title"
TitleOptions {text = "title", style = Style {size = 0.12, borderSize = 1.0e-2, color = Colour 0.05 0.05 0.05 1.00, borderColor = Colour 0.02 0.29 0.48 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}, place = PlaceTop, anchor = AnchorMiddle, buffer = 4.0e-2}

Constructors

TitleOptions 

Fields

Instances

Instances details
Generic TitleOptions Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep TitleOptions :: Type -> Type #

Show TitleOptions Source # 
Instance details

Defined in Chart.Hud

Eq TitleOptions Source # 
Instance details

Defined in Chart.Hud

type Rep TitleOptions Source # 
Instance details

Defined in Chart.Hud

defaultTitleOptions :: Text -> TitleOptions Source #

The official hud title

data Ticks Source #

axis tick markings

>>> defaultXTicks
Ticks {tick = TickRound (FormatN {fstyle = FSCommaPrec, sigFigs = Just 1, maxDistinguishIterations = 4, addLPad = True, cutRightZeros = True}) 5 TickExtend, glyphTick = Just (TickStyle {style = Style {size = 3.0e-2, borderSize = 4.0e-3, color = Colour 0.05 0.05 0.05 0.40, borderColor = Colour 0.05 0.05 0.05 0.40, scaleP = ScalePY, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = VLineGlyph}, anchorTo = CanvasSection, buffer = 1.0e-2}), textTick = Just (TickStyle {style = Style {size = 4.0e-2, borderSize = 1.0e-2, color = Colour 0.05 0.05 0.05 1.00, borderColor = Colour 0.02 0.29 0.48 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}, anchorTo = HudStyleSection, buffer = 1.0e-2}), lineTick = Just (TickStyle {style = Style {size = 5.0e-3, borderSize = 1.0e-2, color = Colour 0.05 0.05 0.05 0.05, borderColor = Colour 0.02 0.29 0.48 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}, anchorTo = CanvasSection, buffer = 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

data TickStyle Source #

Common elements across all tick types.

Constructors

TickStyle 

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

type Rep TickStyle = D1 ('MetaData "TickStyle" "Chart.Hud" "chart-svg-0.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) (C1 ('MetaCons "TickStyle" 'PrefixI 'True) (S1 ('MetaSel ('Just "style") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Style) :*: (S1 ('MetaSel ('Just "anchorTo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HudChartSection) :*: S1 ('MetaSel ('Just "buffer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))))

defaultGlyphTickStyleX :: TickStyle Source #

The official glyph tick

defaultGlyphTickStyleY :: TickStyle Source #

The official glyph tick

defaultTextTick :: TickStyle Source #

The official text tick

defaultLineTick :: TickStyle Source #

The official line tick

defaultXTicks :: Ticks Source #

The official X-axis tick

defaultYTicks :: Ticks Source #

The official Y-axis tick

data Tick 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 Tick Source # 
Instance details

Defined in Chart.Hud

Associated Types

type Rep Tick :: Type -> Type #

Methods

from :: Tick -> Rep Tick x #

to :: Rep Tick x -> Tick #

Show Tick Source # 
Instance details

Defined in Chart.Hud

Methods

showsPrec :: Int -> Tick -> ShowS #

show :: Tick -> String #

showList :: [Tick] -> ShowS #

Eq Tick Source # 
Instance details

Defined in Chart.Hud

Methods

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

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

type Rep Tick Source # 
Instance details

Defined in Chart.Hud

defaultTick :: Tick Source #

The official tick style

>>> defaultTick
TickRound (FormatN {fstyle = FSCommaPrec, sigFigs = Just 1, maxDistinguishIterations = 4, addLPad = True, cutRightZeros = True}) 5 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.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) (C1 ('MetaCons "TickExtend" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoTickExtend" 'PrefixI 'False) (U1 :: Type -> Type))

formatN' :: Lens' Tick (Maybe FormatN) Source #

Lens between a FormatN and a Tick.

numTicks' :: Lens' Tick (Maybe Int) Source #

Lens between number of ticks and a Tick.

Only for TickRound and TickExact

tickExtend' :: Lens' Tick (Maybe TickExtend) Source #

Lens between a FormatN and a Tick.

adjustTicks :: Adjustments -> ChartBox -> 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.6.0.0-HjsGv1l8hv76XDZORokPY6" 'False) (C1 ('MetaCons "Adjustments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "maxXRatio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "maxYRatio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "angledRatio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "allowDiagonal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

defaultAdjustments :: Adjustments Source #

The official hud adjustments.

data LegendOptions Source #

Legend options

>>> defaultLegendOptions
LegendOptions {legendSize = 0.3, buffer = 0.1, vgap = 0.2, hgap = 0.1, textStyle = Style {size = 0.16, borderSize = 1.0e-2, color = Colour 0.05 0.05 0.05 1.00, borderColor = Colour 0.02 0.29 0.48 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}, innerPad = 0.1, outerPad = 2.0e-2, frame = Just (Style {size = 6.0e-2, borderSize = 5.0e-3, color = Colour 0.05 0.05 0.05 0.00, borderColor = Colour 0.05 0.05 0.05 1.00, scaleP = NoScaleP, anchor = AnchorMiddle, rotation = Nothing, translate = Nothing, escapeText = EscapeText, frame = Nothing, lineCap = Nothing, lineJoin = Nothing, dasharray = Nothing, dashoffset = Nothing, hsize = 0.6, vsize = 1.1, vshift = -0.25, glyphShape = SquareGlyph}), place = PlaceRight, scaleChartsBy = 0.25, scaleP = ScalePX, legendCharts = []}

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

Convert Hud elements to charts

axisHud :: AxisOptions -> DataBox -> HudChart -> ChartTree Source #

Create an axis.

titleHud :: TitleOptions -> HudChart -> ChartTree Source #

title append transformation.

frameHud :: FrameOptions -> HudChart -> ChartTree Source #

Make a frame hud transformation.

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

Make a legend from LegendOptions given an existing HudChart