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

Chart.Primitive

Description

Base Chart and ChartTree types and support

Synopsis

Charts

data Chart where Source #

There are 6 Chart primitives, unified as the Chart type.

  • RectChart: a rectangle in the XY-domain. For example, a Rect 0 1 0 1 is the set of points on the XY Plane bounded by (0,0), (0,1), (1,0) & (1,1). Much of the library is built on Rect Double's but the base types are polymorphic.
  • LineChart: a list of points which represent connected straight lines. [Point 0 0, Point 1 1, Point 2 2, Point 3 3] is an example; three lines connected up to form a line from (0,0) to (3,3).
  • GlyphChart: a GlyphShape which is a predefined shaped centered at a Point in XY space.
  • TextChart: text centered at a Point in XY space.
  • PathChart: specification of curvilinear paths using the SVG standards.
  • BlankChart: a rectangular space that has no visual representation.

What is a Chart is usually a combination of these primitives into a tree or list of charts.

Each Chart primitive is a product of a style (the syntactic representation of the data) and a list of data.

A simple example is:

>>> let r = RectChart defaultRectStyle [one]
>>> r
RectChart (RectStyle {borderSize = 1.0e-2, borderColor = Colour 0.02 0.29 0.48 1.00, color = Colour 0.02 0.73 0.80 0.10}) [Rect -0.5 0.5 -0.5 0.5]

Using the defaults, this chart is rendered as:

writeChartSvg "other/unit.hs" $ mempty & #hudOptions .~ defaultHudOptions & #charts .~ unnamed [r]

Instances

Instances details
Eq Chart Source # 
Instance details

Defined in Chart.Primitive

Methods

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

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

Show Chart Source # 
Instance details

Defined in Chart.Primitive

Methods

showsPrec :: Int -> Chart -> ShowS #

show :: Chart -> String #

showList :: [Chart] -> ShowS #

newtype ChartTree Source #

A group of charts represented by a Tree of chart lists with labelled branches. The labelling is particularly useful downstream, when groupings become grouped SVG elements with classes or ids.

Constructors

ChartTree 

Fields

Instances

Instances details
Eq ChartTree Source # 
Instance details

Defined in Chart.Primitive

Show ChartTree Source # 
Instance details

Defined in Chart.Primitive

Generic ChartTree Source # 
Instance details

Defined in Chart.Primitive

Associated Types

type Rep ChartTree :: Type -> Type #

Semigroup ChartTree Source # 
Instance details

Defined in Chart.Primitive

Monoid ChartTree Source # 
Instance details

Defined in Chart.Primitive

type Rep ChartTree Source # 
Instance details

Defined in Chart.Primitive

type Rep ChartTree = D1 ('MetaData "ChartTree" "Chart.Primitive" "chart-svg-0.3.1-ASe9AvMwv5fK1wYh9h4HnJ" 'True) (C1 ('MetaCons "ChartTree" 'PrefixI 'True) (S1 ('MetaSel ('Just "tree") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Tree (Maybe Text, [Chart])))))

tree' :: Iso' ChartTree (Tree (Maybe Text, [Chart])) Source #

Lens between ChartTree and the underlying Tree representation

chart' :: Traversal' ChartTree Chart Source #

A traversal of each chart in a tree.

charts' :: Traversal' ChartTree [Chart] Source #

A traversal of each chart list in a tree.

named :: Text -> [Chart] -> ChartTree Source #

Convert a chart list to a tree, adding a specific text label.

unnamed :: [Chart] -> ChartTree Source #

Convert a chart list to a tree, with no text label.

rename :: Maybe Text -> ChartTree -> ChartTree Source #

Rename a top-level label in a tree.

blank :: Rect Double -> ChartTree Source #

A tree with no charts and no label.

group :: Maybe Text -> [ChartTree] -> ChartTree Source #

Group a list of trees into a new tree.

filterChartTree :: (Chart -> Bool) -> ChartTree -> ChartTree Source #

Apply a filter to ChartTree

data Orientation Source #

Verticle or Horizontal

Constructors

Vert 
Hori 

Instances

Instances details
Eq Orientation Source # 
Instance details

Defined in Chart.Primitive

Show Orientation Source # 
Instance details

Defined in Chart.Primitive

Generic Orientation Source # 
Instance details

Defined in Chart.Primitive

Associated Types

type Rep Orientation :: Type -> Type #

type Rep Orientation Source # 
Instance details

Defined in Chart.Primitive

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

data Stacked Source #

Whether to stack chart data

Constructors

Stacked 
NonStacked 

Instances

Instances details
Eq Stacked Source # 
Instance details

Defined in Chart.Primitive

Methods

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

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

Show Stacked Source # 
Instance details

Defined in Chart.Primitive

Generic Stacked Source # 
Instance details

Defined in Chart.Primitive

Associated Types

type Rep Stacked :: Type -> Type #

Methods

from :: Stacked -> Rep Stacked x #

to :: Rep Stacked x -> Stacked #

type Rep Stacked Source # 
Instance details

Defined in Chart.Primitive

type Rep Stacked = D1 ('MetaData "Stacked" "Chart.Primitive" "chart-svg-0.3.1-ASe9AvMwv5fK1wYh9h4HnJ" 'False) (C1 ('MetaCons "Stacked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NonStacked" 'PrefixI 'False) (U1 :: Type -> Type))

data ChartAspect Source #

The basis for the x-y ratio of a 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.

Instances

Instances details
Eq ChartAspect Source # 
Instance details

Defined in Chart.Primitive

Show ChartAspect Source # 
Instance details

Defined in Chart.Primitive

Generic ChartAspect Source # 
Instance details

Defined in Chart.Primitive

Associated Types

type Rep ChartAspect :: Type -> Type #

type Rep ChartAspect Source # 
Instance details

Defined in Chart.Primitive

type Rep ChartAspect = D1 ('MetaData "ChartAspect" "Chart.Primitive" "chart-svg-0.3.1-ASe9AvMwv5fK1wYh9h4HnJ" '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)))

Boxes

Library functionality (rescaling, combining charts, working out axes and generally putting charts together) is driven by a box model. A box is a rectangular space that bounds chart elements.

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

The Rect which encloses the data elements of the chart. Bounding box is a synonym.

>>> box r
Just Rect -0.5 0.5 -0.5 0.5

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

The bounding box for a chart including both data and style elements.

>>> sbox r
Just Rect -0.505 0.505 -0.505 0.505

In the above example, the border of the rectangle adds an extra 0.1 to the height and width of the bounding box enclosing the chart.

projectWith :: Rect Double -> Rect Double -> Chart -> Chart Source #

projects a Chart to a new space from an old rectangular space, preserving linear metric structure.

>>> projectWith (fmap (2*) one) one r
RectChart (RectStyle {borderSize = 1.0e-2, borderColor = Colour 0.02 0.29 0.48 1.00, color = Colour 0.02 0.73 0.80 0.10}) [Rect -1.0 1.0 -1.0 1.0]

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

Maybe project a Chart to a new rectangular space from an old rectangular space, if both Rects exist.

moveChart :: Point Double -> Chart -> Chart Source #

Move a chart.

scaleChart :: Double -> Chart -> Chart Source #

Scale a chart (effecting both the chart data and the style).

scaleStyle :: Double -> Chart -> Chart Source #

Scale just the chart style.

colourChart :: (Colour -> Colour) -> Chart -> Chart Source #

Modify chart colors, applying to both border and main colors.

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

Project a chart tree to a new bounding box, guarding against singleton bounds.

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

Compute the bounding box of a list of charts.

box' :: Lens' ChartTree (Maybe (Rect Double)) Source #

Lens between a ChartTree and its bounding box.

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

Compute the bounding box of the data and style elements contained in a list of charts.

styleBox' :: Lens' ChartTree (Maybe (Rect Double)) Source #

Lens between a style bounding box and a ChartTree tree.

Note that a round trip may be only approximately isomorphic ie

forall c r. \c -> view styleBox' . set styleBox r c ~= r
  • SVG is, in general, an additive model eg a border adds a constant amount no matter the scale or aspect. Text charts, in particular, can have small data boxes but large style additions to the box.
  • rescaling of style here is, in juxtaposition, a multiplicative model.

In practice, this can lead to weird corner cases and unrequited distortion.

The example below starts with the unit chart, and a simple axis bar, with a dynamic overhang, so that the axis bar represents the x-axis extremity.

>>> t1 = unnamed [RectChart defaultRectStyle [one]]
>>> x1 h = toChartTree $ mempty & set #charts t1 & set (#hudOptions % #chartAspect) (ChartAspect) & set (#hudOptions % #axes) [(1,defaultAxisOptions & over #bar (fmap (set #overhang h)) & set (#ticks % #ttick) Nothing & set (#ticks % #gtick) Nothing & set (#ticks % #ltick) Nothing)]

With a significant overhang, the axis bar dominates the extrema:

>>> view styleBox' $ set styleBox' (Just one) (x1 0.1)
Just Rect -0.5 0.5 -0.5 0.5

With no overhang, the style additions caused by the chart dominates:

>>> view styleBox' $ set styleBox' (Just one) (x1 0)
Just Rect -0.5 0.5 -0.5 0.5

In between:

>>> view styleBox' $ set styleBox' (Just one) (x1 0.002)
Just Rect -0.5000199203187251 0.5000199203187251 -0.5 0.5

If having an exact box is important, try running set styleBox' multiple times eg

>>> view styleBox' $ foldr ($) (x1 0.002) (replicate 10 (set styleBox' (Just one)))
Just Rect -0.5 0.5000000000000001 -0.5 0.4999999999999999

Combinators

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

Vertically stack a list of trees (proceeding upwards), aligning them to the left

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

Horizontally stack a list of trees (proceeding to the right) with a gap between

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

Stack a list of tree charts horizontally, then vertically

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

Create a frame over some charts with (additive) padding.

>>> frameChart defaultRectStyle 0.1 [BlankChart []]
RectChart (RectStyle {borderSize = 1.0e-2, borderColor = Colour 0.02 0.29 0.48 1.00, color = Colour 0.02 0.73 0.80 0.10}) []

isEmptyChart :: Chart -> Bool Source #

Whether a chart is empty of data to be represented.

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

Additive padding, framing or buffering for a chart list.

rectangularize :: RectStyle -> ChartTree -> ChartTree Source #

Make a new chart tree out of the bounding boxes of a chart tree.

glyphize :: GlyphStyle -> ChartTree -> ChartTree Source #

Make a new chart tree out of the data points of a chart tree, using the supplied glyphs.

overText :: (TextStyle -> TextStyle) -> Chart -> Chart Source #

Modify the text in a text chart.

renamed :: Text -> ChartTree -> ChartTree Source #

Rename a ChartTree, removing descendent names