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

Chart.Markup

Description

An intermediary representation not unlike SVG or XML but only forming a subset of these standards.

Synopsis

Documentation

newtype Attributes Source #

A collection of attributes as a ByteString key-value map.

Constructors

Attributes 

Instances

Instances details
Monoid Attributes Source # 
Instance details

Defined in Chart.Markup

Semigroup Attributes Source # 
Instance details

Defined in Chart.Markup

Generic Attributes Source # 
Instance details

Defined in Chart.Markup

Associated Types

type Rep Attributes :: Type -> Type #

Show Attributes Source # 
Instance details

Defined in Chart.Markup

Eq Attributes Source # 
Instance details

Defined in Chart.Markup

ToExpr Attributes Source # 
Instance details

Defined in Chart.Markup

type Rep Attributes Source # 
Instance details

Defined in Chart.Markup

type Rep Attributes = D1 ('MetaData "Attributes" "Chart.Markup" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'True) (C1 ('MetaCons "Attributes" 'PrefixI 'True) (S1 ('MetaSel ('Just "attMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ByteString ByteString))))

attribute :: (ByteString, ByteString) -> Attributes Source #

Create a singleton Attributes

data Markup Source #

A representation of SVG (and XML) markup with no specific knowledge of SVG or XML syntax rules.

>>> let c0 = ChartOptions (defaultMarkupOptions & #cssOptions % #preferColorScheme .~ PreferNormal) mempty mempty
>>> markupChartOptions c0
Markup {tag = "svg", atts = Attributes {attMap = fromList [("height","300"),("viewBox","-0.75 -0.5 1.5 1.0"),("width","450"),("xmlns","http://www.w3.org/2000/svg"),("xmlns:xlink","http://www.w3.org/1999/xlink")]}, contents = [MarkupLeaf (Markup {tag = "style", atts = Attributes {attMap = fromList []}, contents = [Content ""]}),MarkupLeaf (Markup {tag = "g", atts = Attributes {attMap = fromList [("class","chart")]}, contents = []}),MarkupLeaf (Markup {tag = "g", atts = Attributes {attMap = fromList [("class","hud")]}, contents = []})]}

Constructors

Markup 

Instances

Instances details
Generic Markup Source # 
Instance details

Defined in Chart.Markup

Associated Types

type Rep Markup :: Type -> Type #

Methods

from :: Markup -> Rep Markup x #

to :: Rep Markup x -> Markup #

Show Markup Source # 
Instance details

Defined in Chart.Markup

Eq Markup Source # 
Instance details

Defined in Chart.Markup

Methods

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

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

ToExpr Markup Source # 
Instance details

Defined in Chart.Markup

Methods

toExpr :: Markup -> Expr #

listToExpr :: [Markup] -> Expr #

type Rep Markup Source # 
Instance details

Defined in Chart.Markup

type Rep Markup = D1 ('MetaData "Markup" "Chart.Markup" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) (C1 ('MetaCons "Markup" 'PrefixI 'True) (S1 ('MetaSel ('Just "tag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString) :*: (S1 ('MetaSel ('Just "atts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Attributes) :*: S1 ('MetaSel ('Just "contents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Content]))))

data Content Source #

The things that can be inside (form the Content of) a Markup element, especially in a DOM context. Comments are unused by the library representation of a chart and are here to help with parsing arbitrary svg in the wild.

>>> contents (markupChartOptions c0)
[MarkupLeaf (Markup {tag = "style", atts = Attributes {attMap = fromList []}, contents = [Content ""]}),MarkupLeaf (Markup {tag = "g", atts = Attributes {attMap = fromList [("class","chart")]}, contents = []}),MarkupLeaf (Markup {tag = "g", atts = Attributes {attMap = fromList [("class","hud")]}, contents = []})]

Instances

Instances details
Generic Content Source # 
Instance details

Defined in Chart.Markup

Associated Types

type Rep Content :: Type -> Type #

Methods

from :: Content -> Rep Content x #

to :: Rep Content x -> Content #

Show Content Source # 
Instance details

Defined in Chart.Markup

Eq Content Source # 
Instance details

Defined in Chart.Markup

Methods

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

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

ToExpr Content Source # 
Instance details

Defined in Chart.Markup

Methods

toExpr :: Content -> Expr #

listToExpr :: [Content] -> Expr #

type Rep Content Source # 
Instance details

Defined in Chart.Markup

renderMarkup :: Markup -> Text Source #

render markup to Text compliant with being an SVG object (and XML element)

>>> renderMarkup (markupChartOptions c0)
"<svg height=\"300\" viewBox=\"-0.75 -0.5 1.5 1.0\" width=\"450\" xmlns=\"http://www.w3.org/2000/svg\" xmlns:xlink=\"http://www.w3.org/1999/xlink\"><style></style><g class=\"chart\"/><g class=\"hud\"/></svg>"

encodeMarkup :: Markup -> ByteString Source #

render markup to a ByteString compliant with being an SVG object (and XML element)

>>> encodeMarkup (markupChartOptions c0)
"<svg height=\"300\" viewBox=\"-0.75 -0.5 1.5 1.0\" width=\"450\" xmlns=\"http://www.w3.org/2000/svg\" xmlns:xlink=\"http://www.w3.org/1999/xlink\"><style></style><g class=\"chart\"/><g class=\"hud\"/></svg>"

data ChartOptions Source #

A product type representing charts, hud options and markup options, which can be transformed into Markup.

Instances

Instances details
Monoid ChartOptions Source # 
Instance details

Defined in Chart.Markup

Semigroup ChartOptions Source # 
Instance details

Defined in Chart.Markup

Generic ChartOptions Source # 
Instance details

Defined in Chart.Markup

Associated Types

type Rep ChartOptions :: Type -> Type #

Show ChartOptions Source # 
Instance details

Defined in Chart.Markup

Eq ChartOptions Source # 
Instance details

Defined in Chart.Markup

type Rep ChartOptions Source # 
Instance details

Defined in Chart.Markup

type Rep ChartOptions = D1 ('MetaData "ChartOptions" "Chart.Markup" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) (C1 ('MetaCons "ChartOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "markupOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 MarkupOptions) :*: (S1 ('MetaSel ('Just "hudOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 HudOptions) :*: S1 ('MetaSel ('Just "charts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ChartTree))))

markupChartOptions :: ChartOptions -> Markup Source #

Convert ChartOptions to Markup

>>> markupChartOptions (ChartOptions (defaultMarkupOptions & #cssOptions % #preferColorScheme .~ PreferNormal) mempty mempty)
Markup {tag = "svg", atts = Attributes {attMap = fromList [("height","300"),("viewBox","-0.75 -0.5 1.5 1.0"),("width","450"),("xmlns","http://www.w3.org/2000/svg"),("xmlns:xlink","http://www.w3.org/1999/xlink")]}, contents = [MarkupLeaf (Markup {tag = "style", atts = Attributes {attMap = fromList []}, contents = [Content ""]}),MarkupLeaf (Markup {tag = "g", atts = Attributes {attMap = fromList [("class","chart")]}, contents = []}),MarkupLeaf (Markup {tag = "g", atts = Attributes {attMap = fromList [("class","hud")]}, contents = []})]}

markupChartTree :: ChartTree -> [Markup] Source #

Convert a ChartTree to markup

>>> lineExample & view #charts & markupChartTree
[Markup {tag = "g", atts = Attributes {attMap = fromList [("class","line")]}, contents = [MarkupLeaf (Markup {tag = "g", atts = Attributes {attMap = fromList [("fill","none"),("stroke","rgb(2%, 73%, 80%)"),("stroke-opacity","1.0"),("stroke-width","0.0150")]}, contents = [MarkupLeaf (Markup {tag = "polyline", atts = Attributes {attMap = fromList [("points","0,-1.0 1.0,-1.0 2.0,-5.0")]}, contents = []})]}),MarkupLeaf (Markup {tag = "g", atts = Attributes {attMap = fromList [("fill","none"),("stroke","rgb(2%, 29%, 48%)"),("stroke-opacity","1.0"),("stroke-width","0.0150")]}, contents = [MarkupLeaf (Markup {tag = "polyline", atts = Attributes {attMap = fromList [("points","0,0 2.8,-3.0")]}, contents = []})]}),MarkupLeaf (Markup {tag = "g", atts = Attributes {attMap = fromList [("fill","none"),("stroke","rgb(66%, 7%, 55%)"),("stroke-opacity","1.0"),("stroke-width","0.0150")]}, contents = [MarkupLeaf (Markup {tag = "polyline", atts = Attributes {attMap = fromList [("points","0.5,-4.0 0.5,0")]}, contents = []})]})]}]

markupChart :: Chart -> Maybe Markup Source #

Convert a Chart to Markup

>>> lineExample & view #charts & foldOf charts' & head & markupChart
Just (Markup {tag = "g", atts = Attributes {attMap = fromList [("fill","none"),("stroke","rgb(2%, 73%, 80%)"),("stroke-opacity","1.0"),("stroke-width","0.0150")]}, contents = [MarkupLeaf (Markup {tag = "polyline", atts = Attributes {attMap = fromList [("points","0,-1.0 1.0,-1.0 2.0,-5.0")]}, contents = []})]})

header :: Double -> Rect Double -> [Markup] -> Markup Source #

Create the classic SVG element

>>> header 100 one [Markup "foo" mempty mempty]
Markup {tag = "svg", atts = Attributes {attMap = fromList [("height","100"),("viewBox","-0.5 -0.5 1.0 1.0"),("width","100"),("xmlns","http://www.w3.org/2000/svg"),("xmlns:xlink","http://www.w3.org/1999/xlink")]}, contents = [MarkupLeaf (Markup {tag = "foo", atts = Attributes {attMap = fromList []}, contents = []})]}

renderChartOptions :: ChartOptions -> Text Source #

Render ChartOptions to an SVG Text snippet

>>> renderChartOptions (ChartOptions (defaultMarkupOptions & #cssOptions % #preferColorScheme .~ PreferNormal) mempty mempty)
"<svg height=\"300\" viewBox=\"-0.75 -0.5 1.5 1.0\" width=\"450\" xmlns=\"http://www.w3.org/2000/svg\" xmlns:xlink=\"http://www.w3.org/1999/xlink\"><style></style><g class=\"chart\"/><g class=\"hud\"/></svg>"

encodeChartOptions :: ChartOptions -> ByteString Source #

Render ChartOptions to an SVG ByteString

>>> encodeChartOptions (ChartOptions (defaultMarkupOptions & #cssOptions % #preferColorScheme .~ PreferNormal) mempty mempty)
"<svg height=\"300\" viewBox=\"-0.75 -0.5 1.5 1.0\" width=\"450\" xmlns=\"http://www.w3.org/2000/svg\" xmlns:xlink=\"http://www.w3.org/1999/xlink\"><style></style><g class=\"chart\"/><g class=\"hud\"/></svg>"

writeChartOptions :: FilePath -> ChartOptions -> IO () Source #

Convert ChartOptions to an SVG ByteString and save to a file

data CssOptions Source #

css options

>>> defaultCssOptions
CssOptions {shapeRendering = NoShapeRendering, preferColorScheme = PreferHud, cssExtra = ""}

Instances

Instances details
Generic CssOptions Source # 
Instance details

Defined in Chart.Markup

Associated Types

type Rep CssOptions :: Type -> Type #

Show CssOptions Source # 
Instance details

Defined in Chart.Markup

Eq CssOptions Source # 
Instance details

Defined in Chart.Markup

type Rep CssOptions Source # 
Instance details

Defined in Chart.Markup

type Rep CssOptions = D1 ('MetaData "CssOptions" "Chart.Markup" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) (C1 ('MetaCons "CssOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "shapeRendering") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CssShapeRendering) :*: (S1 ('MetaSel ('Just "preferColorScheme") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CssPreferColorScheme) :*: S1 ('MetaSel ('Just "cssExtra") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))))

defaultCssOptions :: CssOptions Source #

No special shape rendering and default hud responds to user color scheme preferences.

data CssPreferColorScheme Source #

CSS prefer-color-scheme options

Constructors

PreferHud

includes css that switches approriate hud elements between light and dark.

PreferDark 
PreferLight 
PreferNormal 

Instances

Instances details
Generic CssPreferColorScheme Source # 
Instance details

Defined in Chart.Markup

Associated Types

type Rep CssPreferColorScheme :: Type -> Type #

Show CssPreferColorScheme Source # 
Instance details

Defined in Chart.Markup

Eq CssPreferColorScheme Source # 
Instance details

Defined in Chart.Markup

type Rep CssPreferColorScheme Source # 
Instance details

Defined in Chart.Markup

type Rep CssPreferColorScheme = D1 ('MetaData "CssPreferColorScheme" "Chart.Markup" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) ((C1 ('MetaCons "PreferHud" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PreferDark" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PreferLight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PreferNormal" 'PrefixI 'False) (U1 :: Type -> Type)))

cssPreferColorScheme :: (Colour, Colour) -> CssPreferColorScheme -> ByteString Source #

CSS prefer-color-scheme text snippet

>>> cssPreferColorScheme (light, dark) PreferHud
"svg {\n  color-scheme: light dark;\n}\n{\n  .canvas g, .title g, .axisbar g, .ticktext g, .tickglyph g, .ticklines g, .legendContent g text {\n    fill: rgb(5%, 5%, 5%);\n  }\n  .ticklines g, .tickglyph g, .legendBorder g {\n    stroke: rgb(5%, 5%, 5%);\n  }\n  .legendBorder g {\n    fill: rgb(94%, 94%, 94%);\n  }\n}\n@media (prefers-color-scheme:dark) {\n  .canvas g, .title g, .axisbar g, .ticktext g, .tickglyph g, .ticklines g, .legendContent g text {\n    fill: rgb(94%, 94%, 94%);\n  }\n  .ticklines g, .tickglyph g, .legendBorder g {\n    stroke: rgb(94%, 94%, 94%);\n  }\n  .legendBorder g {\n    fill: rgb(5%, 5%, 5%);\n  }\n}"

fillSwitch :: (Colour, Colour) -> ByteString -> ByteString -> ByteString Source #

CSS snippet to switch between dark and light mode

fillSwitch (color1, color2) "dark" "stuff"

... will default to color1 for elements of the "stuff" class, but switch to color2 if "dark" mode is preferred by the user.

data CssShapeRendering Source #

CSS shape rendering options

Instances

Instances details
Generic CssShapeRendering Source # 
Instance details

Defined in Chart.Markup

Associated Types

type Rep CssShapeRendering :: Type -> Type #

Show CssShapeRendering Source # 
Instance details

Defined in Chart.Markup

Eq CssShapeRendering Source # 
Instance details

Defined in Chart.Markup

type Rep CssShapeRendering Source # 
Instance details

Defined in Chart.Markup

type Rep CssShapeRendering = D1 ('MetaData "CssShapeRendering" "Chart.Markup" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) (C1 ('MetaCons "UseGeometricPrecision" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UseCssCrisp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoShapeRendering" 'PrefixI 'False) (U1 :: Type -> Type)))

markupCssOptions :: CssOptions -> Markup Source #

Convert CssOptions to Markup

>>> markupCssOptions defaultCssOptions
Markup {tag = "style", atts = Attributes {attMap = fromList []}, contents = [Content "svg {\n  color-scheme: light dark;\n}\n{\n  .canvas g, .title g, .axisbar g, .ticktext g, .tickglyph g, .ticklines g, .legendContent g text {\n    fill: rgb(5%, 5%, 5%);\n  }\n  .ticklines g, .tickglyph g, .legendBorder g {\n    stroke: rgb(5%, 5%, 5%);\n  }\n  .legendBorder g {\n    fill: rgb(94%, 94%, 94%);\n  }\n}\n@media (prefers-color-scheme:dark) {\n  .canvas g, .title g, .axisbar g, .ticktext g, .tickglyph g, .ticklines g, .legendContent g text {\n    fill: rgb(94%, 94%, 94%);\n  }\n  .ticklines g, .tickglyph g, .legendBorder g {\n    stroke: rgb(94%, 94%, 94%);\n  }\n  .legendBorder g {\n    fill: rgb(5%, 5%, 5%);\n  }\n}"]}

data MarkupOptions Source #

Markup options.

>>> defaultMarkupOptions
MarkupOptions {markupHeight = 300.0, cssOptions = CssOptions {shapeRendering = NoShapeRendering, preferColorScheme = PreferHud, cssExtra = ""}}

Instances

Instances details
Generic MarkupOptions Source # 
Instance details

Defined in Chart.Markup

Associated Types

type Rep MarkupOptions :: Type -> Type #

Show MarkupOptions Source # 
Instance details

Defined in Chart.Markup

Eq MarkupOptions Source # 
Instance details

Defined in Chart.Markup

type Rep MarkupOptions Source # 
Instance details

Defined in Chart.Markup

type Rep MarkupOptions = D1 ('MetaData "MarkupOptions" "Chart.Markup" "chart-svg-0.4.0-IvsDYjPAAoJCAgDXwgibUh" 'False) (C1 ('MetaCons "MarkupOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "markupHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "cssOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CssOptions)))

defaultMarkupOptions :: MarkupOptions Source #

The official markup options

encodeNum :: Double -> ByteString Source #

Show a Double, or rounded to 4 decimal places if this is shorter.

>>> encodeNum 1
"1.0"
>>> encodeNum 1.23456
"1.2346"

encodePx :: Double -> ByteString Source #

SVG width and height, without any unit suffix, are defined as pixels, which are Integers

>>> encodePx 300.0
"300"