chart-svg-0.2.2: Charting library targetting SVGs.
Safe HaskellNone
LanguageHaskell2010

Chart

Description

A haskell Charting library targetting SVGs

Synopsis

Usage

>>> import Chart

chart-svg works well with NumHask.Prelude and Control.Lens but neither are necessary.

>>> :set -XOverloadedLabels
>>> :set -XNoImplicitPrelude
>>> import Control.Lens
>>> import NumHask.Prelude

Overview

Charting consists of three highly-coupled conceptual layers:

  1. the data to be represented.
  2. how the data will be represented on a screen, and.
  3. the creation of visual aids that help interpret the data; such as axes, gridlines and titles.

What is a Chart?

A Chart in this library consists of a specification of the first two items in the above list; data and data annotation.

  • XY: a list of values, specified as either 2D points or rectangles.
  • Annotation: a description of how the data should be represented on the screen.
>>> :t Chart
Chart :: Annotation -> [XY a] -> Chart a

What exactly is annotation and what is data is highly variant within charting practice. This construction treats position on the XY plane differently from other quantitative manifests such as color and size. The chief advantage of priveliging XY position is that scaling and integrating data with other chart elements becomes much easier. The disadvantage is that, to use quantitative tools such as size, data needs to be consciously separated into that which is position-orientated, and that which is defined as Annotation.

Here's some data; three lists of points that will form a line:

>>> let xs = fmap (fmap (uncurry Point)) [[(0.0, 1.0), (1.0, 1.0), (2.0, 5.0)], [(0.0, 0.0), (3.2, 3.0)], [(0.5, 4.0), (0.5, 0)]] :: [[Point Double]]

and an Annotation to describe representation of this data; three line styles with different colors and widths:

>>> let anns = zipWith (\w c -> LineA (LineStyle w c Nothing Nothing Nothing Nothing)) [0.015, 0.03, 0.01] palette1_

and this is enough to create a Chart.

>>> let lineExample = mempty & (#chartList .~ zipWith Chart anns (fmap (fmap PointXY) xs)) & #hudOptions .~ defaultHudOptions & #svgOptions .~ defaultSvgOptions :: ChartSvg
>>> :t lineExample
lineExample :: ChartSvg
writeChartSvg "other/line.svg" lineExample

Chart

data Chart a Source #

A Chart is annotated xy-data.

Constructors

Chart 

Fields

Instances

Instances details
Eq a => Eq (Chart a) Source # 
Instance details

Defined in Chart.Types

Methods

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

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

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

Defined in Chart.Types

Methods

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

show :: Chart a -> String #

showList :: [Chart a] -> ShowS #

Generic (Chart a) Source # 
Instance details

Defined in Chart.Types

Associated Types

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

Methods

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

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

type Rep (Chart a) Source # 
Instance details

Defined in Chart.Types

type Rep (Chart a) = D1 ('MetaData "Chart" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "Chart" 'PrefixI 'True) (S1 ('MetaSel ('Just "annotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Annotation) :*: S1 ('MetaSel ('Just "xys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [XY a])))

moveChart :: Additive a => XY a -> [Chart a] -> [Chart a] Source #

Translate the data in a chart.

projectXYs :: Rect Double -> [Chart Double] -> [Chart Double] Source #

Project the xys of a chart to a new XY Space.

projectXYs (dataBox cs) cs == cs if cs is non-empty

projectXYsWith :: Rect Double -> Rect Double -> [Chart Double] -> [Chart Double] Source #

Project chart xys to a new XY Space from an old XY Space

The projections needed are:

  • project the $sel:xys:Chart
  • project the control points of bezier curves
  • project aspect changes only to radii of ellipticals.
projectXYsWith x x == id

projectArcPosition :: Rect Double -> Rect Double -> ArcPosition Double -> ArcInfo Double Source #

project an ArcPosition given new and old Rects

The radii of the ellipse can be represented as:

Point rx 0 & Point 0 ry

These two points are firstly rotated by p and then undergo scaling...

Annotation

data Annotation Source #

How data will be represented onscreen.

The definition of what might be an Annotation type is opinionated.

More complex combinations across Annotations can be constructed from combining charts. See glinesExample, lglyphExample and Chart.Bar for examples.

There may be exceptions, but the approximate magnitude of annotation values are in reference to the size of the screen. For example, a size of 0.01 (say), will means about 1% of the height and/or width of the screen height or width.

Instances

Instances details
Eq Annotation Source # 
Instance details

Defined in Chart.Types

Show Annotation Source # 
Instance details

Defined in Chart.Types

Generic Annotation Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Annotation :: Type -> Type #

type Rep Annotation Source # 
Instance details

Defined in Chart.Types

scaleAnn :: Double -> Annotation -> Annotation Source #

Generically scale an Annotation.

scaleOpacAnn :: Double -> Annotation -> Annotation Source #

dim (or brighten) the opacity of an Annotation by a scale

colourAnn :: Colour -> Annotation -> Annotation Source #

select a main colour

padRect :: Num a => a -> Rect a -> Rect a Source #

additive padding

Styles

data RectStyle Source #

Rectangle styling

>>> defaultRectStyle
RectStyle {borderSize = 1.0e-2, borderColor = Colour 0.65 0.81 0.89 1.00, color = Colour 0.12 0.47 0.71 1.00}

Constructors

RectStyle 

Instances

Instances details
Eq RectStyle Source # 
Instance details

Defined in Chart.Types

Show RectStyle Source # 
Instance details

Defined in Chart.Types

Generic RectStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep RectStyle :: Type -> Type #

type Rep RectStyle Source # 
Instance details

Defined in Chart.Types

type Rep RectStyle = D1 ('MetaData "RectStyle" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "RectStyle" 'PrefixI 'True) (S1 ('MetaSel ('Just "borderSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: (S1 ('MetaSel ('Just "borderColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Colour) :*: S1 ('MetaSel ('Just "color") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Colour))))

blob :: Colour -> RectStyle Source #

solid rectangle, no border

>>> blob black
RectStyle {borderSize = 0.0, borderColor = Colour 0.00 0.00 0.00 0.00, color = Colour 0.00 0.00 0.00 1.00}

clear :: RectStyle Source #

transparent rect

>>> clear
RectStyle {borderSize = 0.0, borderColor = Colour 0.00 0.00 0.00 0.00, color = Colour 0.00 0.00 0.00 0.00}

border :: Double -> Colour -> RectStyle Source #

transparent rectangle, with border

>>> border 0.01 transparent
RectStyle {borderSize = 1.0e-2, borderColor = Colour 0.00 0.00 0.00 0.00, color = Colour 0.00 0.00 0.00 0.00}

data TextStyle Source #

Text styling

>>> defaultTextStyle
TextStyle {size = 8.0e-2, color = Colour 0.05 0.05 0.05 1.00, anchor = AnchorMiddle, hsize = 0.5, vsize = 1.45, nudge1 = -0.2, rotation = Nothing}
>>> let t = zipWith (\x y -> Chart (TextA (defaultTextStyle & (#size .~ (0.05 :: Double))) [x]) [PointXY y]) (fmap Text.singleton ['a' .. 'y']) [Point (sin (x * 0.1)) x | x <- [0 .. 25]]

Instances

Instances details
Eq TextStyle Source # 
Instance details

Defined in Chart.Types

Show TextStyle Source # 
Instance details

Defined in Chart.Types

Generic TextStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep TextStyle :: Type -> Type #

type Rep TextStyle Source # 
Instance details

Defined in Chart.Types

defaultTextStyle :: TextStyle Source #

the offical text style

data GlyphStyle Source #

Glyph styling

>>> defaultGlyphStyle
GlyphStyle {size = 3.0e-2, color = Colour 0.65 0.81 0.89 1.00, borderColor = Colour 0.12 0.47 0.71 1.00, borderSize = 3.0e-3, shape = SquareGlyph, rotation = Nothing, translate = Nothing}

Constructors

GlyphStyle 

Fields

Instances

Instances details
Eq GlyphStyle Source # 
Instance details

Defined in Chart.Types

Show GlyphStyle Source # 
Instance details

Defined in Chart.Types

Generic GlyphStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep GlyphStyle :: Type -> Type #

type Rep GlyphStyle Source # 
Instance details

Defined in Chart.Types

defaultGlyphStyle :: GlyphStyle Source #

the offical glyph style

data GlyphShape Source #

glyph shapes

Instances

Instances details
Eq GlyphShape Source # 
Instance details

Defined in Chart.Types

Show GlyphShape Source # 
Instance details

Defined in Chart.Types

Generic GlyphShape Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep GlyphShape :: Type -> Type #

type Rep GlyphShape Source # 
Instance details

Defined in Chart.Types

type Rep GlyphShape = D1 ('MetaData "GlyphShape" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (((C1 ('MetaCons "CircleGlyph" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SquareGlyph" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EllipseGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "RectSharpGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)))) :+: ((C1 ('MetaCons "RectRoundedGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double))) :+: C1 ('MetaCons "TriangleGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point Double)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point Double)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Point Double))))) :+: (C1 ('MetaCons "VLineGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)) :+: (C1 ('MetaCons "HLineGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "PathGlyph" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))))

data LineStyle Source #

line style

>>> defaultLineStyle
LineStyle {width = 1.2e-2, color = Colour 0.05 0.05 0.05 1.00, linecap = Nothing, linejoin = Nothing, dasharray = Nothing, dashoffset = Nothing}

See also https://developer.mozilla.org/en-US/docs/Web/SVG/Attribute

Instances

Instances details
Eq LineStyle Source # 
Instance details

Defined in Chart.Types

Show LineStyle Source # 
Instance details

Defined in Chart.Types

Generic LineStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep LineStyle :: Type -> Type #

type Rep LineStyle Source # 
Instance details

Defined in Chart.Types

defaultLineStyle :: LineStyle Source #

the official default line style

data LineCap Source #

line cap style

Instances

Instances details
Eq LineCap Source # 
Instance details

Defined in Chart.Types

Methods

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

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

Show LineCap Source # 
Instance details

Defined in Chart.Types

Generic LineCap Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep LineCap :: Type -> Type #

Methods

from :: LineCap -> Rep LineCap x #

to :: Rep LineCap x -> LineCap #

type Rep LineCap Source # 
Instance details

Defined in Chart.Types

type Rep LineCap = D1 ('MetaData "LineCap" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "LineCapButt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LineCapRound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineCapSquare" 'PrefixI 'False) (U1 :: Type -> Type)))

fromLineCap :: IsString s => LineCap -> s Source #

textifier

toLineCap :: (Eq s, IsString s) => s -> LineCap Source #

readifier

data LineJoin Source #

line cap style

Instances

Instances details
Eq LineJoin Source # 
Instance details

Defined in Chart.Types

Show LineJoin Source # 
Instance details

Defined in Chart.Types

Generic LineJoin Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep LineJoin :: Type -> Type #

Methods

from :: LineJoin -> Rep LineJoin x #

to :: Rep LineJoin x -> LineJoin #

type Rep LineJoin Source # 
Instance details

Defined in Chart.Types

type Rep LineJoin = D1 ('MetaData "LineJoin" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "LineJoinMiter" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LineJoinBevel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineJoinRound" 'PrefixI 'False) (U1 :: Type -> Type)))

fromLineJoin :: IsString s => LineJoin -> s Source #

textifier

toLineJoin :: (Eq s, IsString s) => s -> LineJoin Source #

readifier

fromDashArray :: [Double] -> Text Source #

Convert a dash representation from a list to text

data Anchor Source #

position anchor

Instances

Instances details
Eq Anchor Source # 
Instance details

Defined in Chart.Types

Methods

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

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

Show Anchor Source # 
Instance details

Defined in Chart.Types

Generic Anchor Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Anchor :: Type -> Type #

Methods

from :: Anchor -> Rep Anchor x #

to :: Rep Anchor x -> Anchor #

type Rep Anchor Source # 
Instance details

Defined in Chart.Types

type Rep Anchor = D1 ('MetaData "Anchor" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "AnchorMiddle" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AnchorStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AnchorEnd" 'PrefixI 'False) (U1 :: Type -> Type)))

fromAnchor :: IsString s => Anchor -> s Source #

text

toAnchor :: (Eq s, IsString s) => s -> Anchor Source #

from text

data PathStyle Source #

Path styling

>>> defaultPathStyle
PathStyle {borderSize = 1.0e-2, borderColor = Colour 0.65 0.81 0.89 1.00, color = Colour 0.12 0.47 0.71 1.00}

Constructors

PathStyle 

Instances

Instances details
Eq PathStyle Source # 
Instance details

Defined in Chart.Types

Show PathStyle Source # 
Instance details

Defined in Chart.Types

Generic PathStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep PathStyle :: Type -> Type #

type Rep PathStyle Source # 
Instance details

Defined in Chart.Types

type Rep PathStyle = D1 ('MetaData "PathStyle" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "PathStyle" 'PrefixI 'True) (S1 ('MetaSel ('Just "borderSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: (S1 ('MetaSel ('Just "borderColor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Colour) :*: S1 ('MetaSel ('Just "color") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Colour))))

toPathChart :: PathStyle -> [(PathInfo Double, Point Double)] -> Chart Double Source #

Convert from a path command list to a PathA chart

Hud types

data ChartDims a Source #

Dimensions that are tracked in the HudT:

  • chartDim: the rectangular dimension of the physical representation of a chart on the screen so that new hud elements can be appended. Adding a hud piece tends to expand the chart dimension.
  • canvasDim: the rectangular dimension of the canvas on which data will be represented. At times appending a hud element will cause the canvas dimension to shift.
  • dataDim: the rectangular dimension of the data being represented. Adding hud elements can cause this to change.

Constructors

ChartDims 

Fields

Instances

Instances details
Eq a => Eq (ChartDims a) Source # 
Instance details

Defined in Chart.Types

Methods

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

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

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

Defined in Chart.Types

Generic (ChartDims a) Source # 
Instance details

Defined in Chart.Types

Associated Types

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

Methods

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

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

type Rep (ChartDims a) Source # 
Instance details

Defined in Chart.Types

type Rep (ChartDims a) = D1 ('MetaData "ChartDims" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "ChartDims" 'PrefixI 'True) (S1 ('MetaSel ('Just "chartDim") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Rect a)) :*: (S1 ('MetaSel ('Just "canvasDim") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Rect a)) :*: S1 ('MetaSel ('Just "dataDim") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Rect a)))))

newtype HudT m a Source #

Hud monad transformer

Constructors

Hud 

Fields

Instances

Instances details
Monad m => Semigroup (HudT m a) Source # 
Instance details

Defined in Chart.Types

Methods

(<>) :: HudT m a -> HudT m a -> HudT m a #

sconcat :: NonEmpty (HudT m a) -> HudT m a #

stimes :: Integral b => b -> HudT m a -> HudT m a #

Monad m => Monoid (HudT m a) Source # 
Instance details

Defined in Chart.Types

Methods

mempty :: HudT m a #

mappend :: HudT m a -> HudT m a -> HudT m a #

mconcat :: [HudT m a] -> HudT m a #

type Hud = HudT Identity Source #

Heads-Up-Display for a Chart

simulHud :: (Ord a, Monad m) => HudT m a -> HudT m a -> HudT m a Source #

run two hud's simultaneously (using the same original ChartDims state) rather than sequentially (which is the <> operation).

data HudOptions Source #

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

Instances

Instances details
Eq HudOptions Source # 
Instance details

Defined in Chart.Types

Show HudOptions Source # 
Instance details

Defined in Chart.Types

Generic HudOptions Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep HudOptions :: Type -> Type #

Semigroup HudOptions Source # 
Instance details

Defined in Chart.Types

Monoid HudOptions Source # 
Instance details

Defined in Chart.Types

type Rep HudOptions Source # 
Instance details

Defined in Chart.Types

defaultHudOptions :: HudOptions Source #

The official hud options.

scaleOpacHudOptions :: HudOptions -> Double -> HudOptions Source #

adjust the opacity of HudOptions up or down geometrically (scaling by (*o))

defaultCanvas :: RectStyle Source #

The official hud canvas

runHudWith Source #

Arguments

:: Rect Double

initial canvas dimension

-> Rect Double

initial data dimension

-> [Hud Double]

huds to add

-> [Chart Double]

underlying chart

-> [Chart Double]

integrated chart list

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 (and the use of a linear type is an open question).

runHud Source #

Arguments

:: Rect Double

initial canvas dimension

-> [Hud Double]

huds

-> [Chart Double]

underlying charts

-> [Chart Double]

integrated chart list

Combine huds and charts to form a new [Chart] using the supplied canvas and the actual data dimension.

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

makeHud :: Rect Double -> HudOptions -> ([Hud Double], [Chart Double]) Source #

Make huds from a HudOptions.

Some huds, such as the creation of tick values, can extend the data dimension of a chart, so we return a blank chart with the new data dimension. The complexity internally to this function is due to the creation of ticks and, specifically, gridSensible, which is not idempotent. As a result, a tick calculation that does extends the data area, can then lead to new tick values when applying TickRound etc.

data ChartAspect Source #

The basis for the x-y ratio of the final chart

Default style features tend towards assuming that the usual height of the overall svg image is around 1, and ChartAspect is based on this assumption, so that a ChartAspect of "FixedAspect 1.5", say, means a height of 1 and a width of 1.5.

Constructors

FixedAspect Double

Rescale charts to a fixed x-y ratio, inclusive of hud and style features

CanvasAspect Double

Rescale charts to an overall height of 1, preserving the x-y ratio of the data canvas.

ChartAspect

Rescale charts to a height of 1, preserving the existing x-y ratio of the underlying charts, inclusive of hud and style.

UnadjustedAspect

Do not rescale.

Instances

Instances details
Eq ChartAspect Source # 
Instance details

Defined in Chart.Types

Show ChartAspect Source # 
Instance details

Defined in Chart.Types

Generic ChartAspect Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep ChartAspect :: Type -> Type #

type Rep ChartAspect Source # 
Instance details

Defined in Chart.Types

type Rep ChartAspect = D1 ('MetaData "ChartAspect" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) ((C1 ('MetaCons "FixedAspect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "CanvasAspect" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double))) :+: (C1 ('MetaCons "ChartAspect" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnadjustedAspect" 'PrefixI 'False) (U1 :: Type -> Type)))

toChartAspect :: (Eq s, IsString s) => s -> Double -> ChartAspect Source #

readifier

initialCanvas :: ChartAspect -> [Chart Double] -> Rect Double Source #

calculation of the canvas given the ChartAspect

chartAspectHud :: Monad m => ChartAspect -> HudT m Double Source #

Project the chart data given the ChartAspect

canvas :: Monad m => RectStyle -> HudT m Double Source #

Make a canvas hud element.

title :: Monad m => Title -> HudT m Double Source #

Add a title to a chart. The logic used to work out placement is flawed due to being able to freely specify text rotation. It works for specific rotations (Top, Bottom at 0, Left at 90, Right @ 270)

tick :: Monad m => Place -> Tick -> HudT m Double Source #

Create tick glyphs (marks), lines (grid) and text (labels)

Hud primitives

data AxisOptions Source #

axis options

Instances

Instances details
Eq AxisOptions Source # 
Instance details

Defined in Chart.Types

Show AxisOptions Source # 
Instance details

Defined in Chart.Types

Generic AxisOptions Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep AxisOptions :: Type -> Type #

type Rep AxisOptions Source # 
Instance details

Defined in Chart.Types

flipAxis :: AxisOptions -> AxisOptions Source #

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

data Place Source #

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

Instances

Instances details
Eq Place Source # 
Instance details

Defined in Chart.Types

Methods

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

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

Show Place Source # 
Instance details

Defined in Chart.Types

Methods

showsPrec :: Int -> Place -> ShowS #

show :: Place -> String #

showList :: [Place] -> ShowS #

Generic Place Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Place :: Type -> Type #

Methods

from :: Place -> Rep Place x #

to :: Rep Place x -> Place #

type Rep Place Source # 
Instance details

Defined in Chart.Types

type Rep Place = D1 ('MetaData "Place" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" '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 {rstyle = RectStyle {borderSize = 0.0, borderColor = Colour 0.00 0.00 0.00 0.00, color = Colour 0.05 0.05 0.05 0.40}, wid = 4.0e-3, buff = 1.0e-2}

Constructors

AxisBar 

Fields

Instances

Instances details
Eq AxisBar Source # 
Instance details

Defined in Chart.Types

Methods

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

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

Show AxisBar Source # 
Instance details

Defined in Chart.Types

Generic AxisBar Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep AxisBar :: Type -> Type #

Methods

from :: AxisBar -> Rep AxisBar x #

to :: Rep AxisBar x -> AxisBar #

type Rep AxisBar Source # 
Instance details

Defined in Chart.Types

type Rep AxisBar = D1 ('MetaData "AxisBar" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "AxisBar" 'PrefixI 'True) (S1 ('MetaSel ('Just "rstyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RectStyle) :*: (S1 ('MetaSel ('Just "wid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "buff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double))))

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.5, vsize = 1.45, nudge1 = -0.2, rotation = Nothing}, place = PlaceTop, anchor = AnchorMiddle, buff = 4.0e-2}

Constructors

Title 

Fields

Instances

Instances details
Eq Title Source # 
Instance details

Defined in Chart.Types

Methods

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

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

Show Title Source # 
Instance details

Defined in Chart.Types

Methods

showsPrec :: Int -> Title -> ShowS #

show :: Title -> String #

showList :: [Title] -> ShowS #

Generic Title Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Title :: Type -> Type #

Methods

from :: Title -> Rep Title x #

to :: Rep Title x -> Title #

type Rep Title Source # 
Instance details

Defined in Chart.Types

defaultTitle :: Text -> Title Source #

The official hud title

data Tick Source #

xy coordinate markings

>>> defaultTick
Tick {tstyle = TickRound (FormatComma (Just 2)) 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 = 2.0e-3, shape = VLineGlyph 5.0e-3, rotation = Nothing, translate = Nothing},1.25e-2), ttick = Just (TextStyle {size = 5.0e-2, color = Colour 0.05 0.05 0.05 1.00, anchor = AnchorMiddle, hsize = 0.5, vsize = 1.45, nudge1 = -0.2, rotation = Nothing},1.5e-2), ltick = Just (LineStyle {width = 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
Eq Tick Source # 
Instance details

Defined in Chart.Types

Methods

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

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

Show Tick Source # 
Instance details

Defined in Chart.Types

Methods

showsPrec :: Int -> Tick -> ShowS #

show :: Tick -> String #

showList :: [Tick] -> ShowS #

Generic Tick Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Tick :: Type -> Type #

Methods

from :: Tick -> Rep Tick x #

to :: Rep Tick x -> Tick #

type Rep Tick Source # 
Instance details

Defined in Chart.Types

defaultGlyphTick :: GlyphStyle Source #

The official glyph tick

defaultTextTick :: TextStyle Source #

The official text tick

defaultLineTick :: LineStyle Source #

The official line tick

defaultTick :: Tick 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
Eq TickStyle Source # 
Instance details

Defined in Chart.Types

Show TickStyle Source # 
Instance details

Defined in Chart.Types

Generic TickStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep TickStyle :: Type -> Type #

type Rep TickStyle Source # 
Instance details

Defined in Chart.Types

defaultTickStyle :: TickStyle Source #

The official tick style

data TickExtend Source #

Whether Ticks are allowed to extend the data range

Constructors

TickExtend 
NoTickExtend 

Instances

Instances details
Eq TickExtend Source # 
Instance details

Defined in Chart.Types

Show TickExtend Source # 
Instance details

Defined in Chart.Types

Generic TickExtend Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep TickExtend :: Type -> Type #

type Rep TickExtend Source # 
Instance details

Defined in Chart.Types

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

adjustTick :: Adjustments -> Rect Double -> Rect Double -> Place -> Tick -> Tick Source #

adjust Tick for sane font sizes etc

makeTickDates :: PosDiscontinuous -> Maybe Text -> Int -> [UTCTime] -> [(Int, Text)] Source #

Convert a UTCTime list into sensible ticks, placed exactly

makeTickDatesContinuous :: PosDiscontinuous -> Maybe Text -> Int -> [UTCTime] -> [(Double, Text)] Source #

Convert a UTCTime list into sensible ticks, placed on the (0,1) space

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
Eq Adjustments Source # 
Instance details

Defined in Chart.Types

Show Adjustments Source # 
Instance details

Defined in Chart.Types

Generic Adjustments Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Adjustments :: Type -> Type #

type Rep Adjustments Source # 
Instance details

Defined in Chart.Types

type Rep Adjustments = D1 ('MetaData "Adjustments" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" '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 {lsize = 0.3, vgap = 0.2, hgap = 0.1, ltext = TextStyle {size = 0.12, color = Colour 0.05 0.05 0.05 1.00, anchor = AnchorMiddle, hsize = 0.5, vsize = 1.45, nudge1 = -0.2, rotation = Nothing}, lmax = 10, innerPad = 0.1, outerPad = 2.0e-2, legendFrame = 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}), lplace = PlaceRight, lscale = 0.25}

Instances

Instances details
Eq LegendOptions Source # 
Instance details

Defined in Chart.Types

Show LegendOptions Source # 
Instance details

Defined in Chart.Types

Generic LegendOptions Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep LegendOptions :: Type -> Type #

type Rep LegendOptions Source # 
Instance details

Defined in Chart.Types

defaultLegendOptions :: LegendOptions Source #

The official legend options

legendHud :: LegendOptions -> [Chart Double] -> Hud Double Source #

Make a legend hud element taking into account the chart.

data Orientation Source #

Verticle or Horizontal

Constructors

Vert 
Hori 

Instances

Instances details
Eq Orientation Source # 
Instance details

Defined in Chart.Types

Show Orientation Source # 
Instance details

Defined in Chart.Types

Generic Orientation Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Orientation :: Type -> Type #

type Rep Orientation Source # 
Instance details

Defined in Chart.Types

type Rep Orientation = D1 ('MetaData "Orientation" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "Vert" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Hori" 'PrefixI 'False) (U1 :: Type -> Type))

toOrientation :: (Eq s, IsString s) => s -> Orientation Source #

readifier

SVG primitives

data CssOptions Source #

 

Instances

Instances details
Eq CssOptions Source # 
Instance details

Defined in Chart.Types

Show CssOptions Source # 
Instance details

Defined in Chart.Types

Generic CssOptions Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep CssOptions :: Type -> Type #

type Rep CssOptions Source # 
Instance details

Defined in Chart.Types

type Rep CssOptions = D1 ('MetaData "CssOptions" "Chart.Types" "chart-svg-0.2.2-AJskDBGhW2w5nFQE5Ah360" 'False) (C1 ('MetaCons "UseGeometricPrecision" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UseCssCrisp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoCssOptions" 'PrefixI 'False) (U1 :: Type -> Type)))

data SvgOptions Source #

SVG tag options.

>>> defaultSvgOptions
SvgOptions {svgHeight = 300.0, outerPad = Just 2.0e-2, innerPad = Nothing, chartFrame = Nothing, cssOptions = NoCssOptions, chartAspect = FixedAspect 1.5, background = Nothing}

Instances

Instances details
Eq SvgOptions Source # 
Instance details

Defined in Chart.Types

Show SvgOptions Source # 
Instance details

Defined in Chart.Types

Generic SvgOptions Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep SvgOptions :: Type -> Type #

type Rep SvgOptions Source # 
Instance details

Defined in Chart.Types

defaultSvgOptions :: SvgOptions Source #

The official svg options

Chart manipulation

padChart :: Double -> [Chart Double] -> [Chart Double] Source #

additively pad a [Chart]

>>> padChart 0.1 [Chart (RectA defaultRectStyle) [RectXY one]]
[Chart {annotation = RectA (RectStyle {borderSize = 1.0e-2, borderColor = Colour 0.65 0.81 0.89 1.00, color = Colour 0.12 0.47 0.71 1.00}), xys = [R -0.5 0.5 -0.5 0.5]},Chart {annotation = BlankA, xys = [R -0.605 0.605 -0.605 0.605]}]

frameChart :: RectStyle -> Double -> [Chart Double] -> [Chart Double] Source #

overlay a frame on some charts with some additive padding between

>>> frameChart defaultRectStyle 0.1 [Chart BlankA []]
[Chart {annotation = RectA (RectStyle {borderSize = 1.0e-2, borderColor = Colour 0.65 0.81 0.89 1.00, color = Colour 0.12 0.47 0.71 1.00}), xys = []},Chart {annotation = BlankA, xys = []}]

hori :: Double -> [[Chart Double]] -> [Chart Double] Source #

horizontally stack a list of list of charts (proceeding to the right) with a gap between

vert :: Double -> [[Chart Double]] -> [Chart Double] Source #

vertically stack a list of charts (proceeding upwards), aligning them to the left

stack :: Int -> Double -> [[Chart Double]] -> [Chart Double] Source #

stack a list of charts horizontally, then vertically

Bounding box calculation

padBox :: Maybe (Rect Double) -> Rect Double Source #

pad a Rect to remove singleton dimensions

dataBox :: Chart Double -> Maybe (Rect Double) Source #

Rect of a Chart, not including style

dataBoxes :: [Chart Double] -> Maybe (Rect Double) Source #

Rect of charts, not including style

dataBoxesS :: [Chart Double] -> Rect Double Source #

Rect of charts, not including style, with defaults for Nothing and singleton dimensions if any.

styleBox :: Chart Double -> Maybe (Rect Double) Source #

the geometric dimensions of a Chart inclusive of style geometry, but excluding PathA effects

styleBoxes :: [Chart Double] -> Maybe (Rect Double) Source #

the extra geometric dimensions of a [Chart]

styleBoxesS :: [Chart Double] -> Rect Double Source #

the extra geometric dimensions of a [Chart], adjusted for Nothing or singleton dimensions.

styleBoxText :: TextStyle -> Text -> Point Double -> Rect Double Source #

the extra area from text styling

styleBoxGlyph :: GlyphStyle -> Rect Double Source #

the extra area from glyph styling

Re-exports

module Chart.Bar

module Data.Path