chart-svg-0.1.1: Charts in SVG

Safe HaskellNone
LanguageHaskell2010

Chart.Types

Contents

Synopsis

Documentation

data Chart a Source #

A Chart consists of - a list of spots on the xy-plane, and - specific style of representation for each spot.

Constructors

Chart 

Fields

Instances
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.1.1-E9vnLYsUbhm7chwZtErhMB" False) (C1 (MetaCons "Chart" PrefixI True) (S1 (MetaSel (Just "annotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Annotation) :*: S1 (MetaSel (Just "spots") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Spot a])))

data Annotation Source #

Manifestation of the data on a screen.

Instances
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

data RectStyle Source #

Rectangle styling

>>> defaultRectStyle
RectStyle {borderSize = 1.0e-2, borderColor = RGBA 0.12 0.47 0.71 0.80, color = RGBA 0.12 0.47 0.71 0.30}
writeCharts "other/unit.svg" [Chart (RectA defaultRectStyle) [SpotRect (unitRect::Rect Double)]]

Constructors

RectStyle 
Instances
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.1.1-E9vnLYsUbhm7chwZtErhMB" False) (C1 (MetaCons "RectStyle" PrefixI True) (S1 (MetaSel (Just "borderSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: (S1 (MetaSel (Just "borderColor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Colour) :*: S1 (MetaSel (Just "color") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Colour))))

blob :: Colour -> RectStyle Source #

solid rectangle, no border

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

clear :: RectStyle Source #

transparent rect

>>> clear
RectStyle {borderSize = 0.0, borderColor = RGBA 0.00 0.00 0.00 0.00, color = RGBA 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 = RGBA 0.00 0.00 0.00 0.00, color = RGBA 0.00 0.00 0.00 0.00}

data TextStyle Source #

Text styling

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

Instances
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 Anchor Source #

position anchor

Instances
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.1.1-E9vnLYsUbhm7chwZtErhMB" 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 GlyphStyle Source #

Glyph styling

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

Constructors

GlyphStyle 

Fields

Instances
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
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.1.1-E9vnLYsUbhm7chwZtErhMB" 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 DecidedLazy) (Rec0 Double)) :+: C1 (MetaCons "RectSharpGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))) :+: ((C1 (MetaCons "RectRoundedGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double))) :+: C1 (MetaCons "TriangleGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Point Double)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Point Double)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Point Double))))) :+: (C1 (MetaCons "VLineGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) :+: (C1 (MetaCons "HLineGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) :+: C1 (MetaCons "PathGlyph" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))))

data LineStyle Source #

line style

>>> defaultLineStyle
LineStyle {width = 1.2e-2, color = RGBA 0.65 0.81 0.89 0.30}

Constructors

LineStyle 

Fields

Instances
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

type Rep LineStyle = D1 (MetaData "LineStyle" "Chart.Types" "chart-svg-0.1.1-E9vnLYsUbhm7chwZtErhMB" False) (C1 (MetaCons "LineStyle" PrefixI True) (S1 (MetaSel (Just "width") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double) :*: S1 (MetaSel (Just "color") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Colour)))

defaultLineStyle :: LineStyle Source #

the official default line style

data PixelStyle Source #

A pixel chart is a specialization of a RectA chart

>>> defaultPixelStyle
PixelStyle {pixelColorMin = RGBA 0.65 0.81 0.89 1.00, pixelColorMax = RGBA 0.12 0.47 0.71 1.00, pixelGradient = 1.5707963267948966, pixelRectStyle = RectStyle {borderSize = 0.0, borderColor = RGBA 0.00 0.00 0.00 0.00, color = RGBA 0.00 0.00 0.00 1.00}, pixelTextureId = "pixel"}

Constructors

PixelStyle 

Fields

Instances
Eq PixelStyle Source # 
Instance details

Defined in Chart.Types

Show PixelStyle Source # 
Instance details

Defined in Chart.Types

Generic PixelStyle Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep PixelStyle :: Type -> Type #

type Rep PixelStyle Source # 
Instance details

Defined in Chart.Types

defaultPixelStyle :: PixelStyle Source #

The official pixel style.

data Direction Source #

Verticle or Horizontal

Constructors

Vert 
Hori 
Instances
Eq Direction Source # 
Instance details

Defined in Chart.Types

Show Direction Source # 
Instance details

Defined in Chart.Types

Generic Direction Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Direction :: Type -> Type #

type Rep Direction Source # 
Instance details

Defined in Chart.Types

type Rep Direction = D1 (MetaData "Direction" "Chart.Types" "chart-svg-0.1.1-E9vnLYsUbhm7chwZtErhMB" False) (C1 (MetaCons "Vert" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Hori" PrefixI False) (U1 :: Type -> Type))

fromDirection :: IsString s => Direction -> s Source #

textifier

toDirection :: (Eq s, IsString s) => s -> Direction Source #

readifier

data Spot a Source #

unification of a point and rect on the plane

Constructors

SpotPoint (Point a) 
SpotRect (Rect a) 
Instances
Functor Spot Source # 
Instance details

Defined in Chart.Types

Methods

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

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

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

Defined in Chart.Types

Methods

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

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

(Ord a, Num a, Fractional a) => Num (Spot a) Source # 
Instance details

Defined in Chart.Types

Methods

(+) :: Spot a -> Spot a -> Spot a #

(-) :: Spot a -> Spot a -> Spot a #

(*) :: Spot a -> Spot a -> Spot a #

negate :: Spot a -> Spot a #

abs :: Spot a -> Spot a #

signum :: Spot a -> Spot a #

fromInteger :: Integer -> Spot a #

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

Defined in Chart.Types

Methods

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

show :: Spot a -> String #

showList :: [Spot a] -> ShowS #

Ord a => Semigroup (Spot a) Source # 
Instance details

Defined in Chart.Types

Methods

(<>) :: Spot a -> Spot a -> Spot a #

sconcat :: NonEmpty (Spot a) -> Spot a #

stimes :: Integral b => b -> Spot a -> Spot a #

toRect :: Spot a -> Rect a Source #

Convert a spot to an Rect

toPoint :: (Ord a, Fractional a) => Spot a -> Point a Source #

Convert a spot to a Point

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

additive padding

data SvgAspect Source #

The x-y ratio of the viewing box

Instances
Eq SvgAspect Source # 
Instance details

Defined in Chart.Types

Show SvgAspect Source # 
Instance details

Defined in Chart.Types

Generic SvgAspect Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep SvgAspect :: Type -> Type #

type Rep SvgAspect Source # 
Instance details

Defined in Chart.Types

type Rep SvgAspect = D1 (MetaData "SvgAspect" "Chart.Types" "chart-svg-0.1.1-E9vnLYsUbhm7chwZtErhMB" False) (C1 (MetaCons "ManualAspect" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) :+: C1 (MetaCons "ChartAspect" PrefixI False) (U1 :: Type -> Type))

toSvgAspect :: (Eq s, IsString s) => s -> Double -> SvgAspect Source #

readifier

fromSvgAspect :: IsString s => SvgAspect -> s Source #

textifier

data EscapeText Source #

or html

Constructors

EscapeText 
NoEscapeText 
Instances
Eq EscapeText Source # 
Instance details

Defined in Chart.Types

Show EscapeText Source # 
Instance details

Defined in Chart.Types

Generic EscapeText Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep EscapeText :: Type -> Type #

type Rep EscapeText Source # 
Instance details

Defined in Chart.Types

type Rep EscapeText = D1 (MetaData "EscapeText" "Chart.Types" "chart-svg-0.1.1-E9vnLYsUbhm7chwZtErhMB" False) (C1 (MetaCons "EscapeText" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoEscapeText" PrefixI False) (U1 :: Type -> Type))

data CssOptions Source #

pixel chart helper

Constructors

UseCssCrisp 
NoCssOptions 
Instances
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.1.1-E9vnLYsUbhm7chwZtErhMB" False) (C1 (MetaCons "UseCssCrisp" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoCssOptions" PrefixI False) (U1 :: Type -> Type))

data ScaleCharts Source #

turns off scaling. Usually not what you want.

Constructors

ScaleCharts 
NoScaleCharts 
Instances
Eq ScaleCharts Source # 
Instance details

Defined in Chart.Types

Show ScaleCharts Source # 
Instance details

Defined in Chart.Types

Generic ScaleCharts Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep ScaleCharts :: Type -> Type #

type Rep ScaleCharts Source # 
Instance details

Defined in Chart.Types

type Rep ScaleCharts = D1 (MetaData "ScaleCharts" "Chart.Types" "chart-svg-0.1.1-E9vnLYsUbhm7chwZtErhMB" False) (C1 (MetaCons "ScaleCharts" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoScaleCharts" PrefixI False) (U1 :: Type -> Type))

data SvgOptions Source #

Top-level SVG options.

>>> defaultSvgOptions
SvgOptions {svgHeight = 300.0, outerPad = Just 2.0e-2, innerPad = Nothing, chartFrame = Nothing, escapeText = NoEscapeText, useCssCrisp = NoCssOptions, scaleCharts' = ScaleCharts, svgAspect = ManualAspect 1.5}
writeChartsWith "other/svgoptions.svg" (defaultSvgOptions & #svgAspect .~ ManualAspect 0.7) lines

Instances
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

data ChartDims a Source #

In order to create huds, there are three main pieces of state that need to be kept track of:

  • 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
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.1.1-E9vnLYsUbhm7chwZtErhMB" False) (C1 (MetaCons "ChartDims" PrefixI True) (S1 (MetaSel (Just "chartDim") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Rect a)) :*: (S1 (MetaSel (Just "canvasDim") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Rect a)) :*: S1 (MetaSel (Just "dataDim") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Rect a)))))

newtype HudT m a Source #

Hud monad transformer

Constructors

Hud 

Fields

Instances
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 #

data HudOptions Source #

Practically, the configuration of a Hud is going to be in decimals, typed into config files and the like, and so we concrete at the configuration level, and settle on doubles for specifying the geomtry of hud elements.

writeHudOptionsChart "other/hud.svg" defaultSvgOptions defaultHudOptions [] []

Instances
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.

defaultCanvas :: RectStyle Source #

The official hud canvas

data AxisOptions Source #

axis options

Constructors

AxisOptions 
Instances
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

data Place Source #

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

Instances
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.1.1-E9vnLYsUbhm7chwZtErhMB" 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))))))

placeText :: Place -> Text Source #

textifier

data Bar Source #

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

>>> defaultBar
Bar {rstyle = RectStyle {borderSize = 0.0, borderColor = RGBA 0.50 0.50 0.50 1.00, color = RGBA 0.50 0.50 0.50 1.00}, wid = 5.0e-3, buff = 1.0e-2}

Constructors

Bar 

Fields

Instances
Eq Bar Source # 
Instance details

Defined in Chart.Types

Methods

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

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

Show Bar Source # 
Instance details

Defined in Chart.Types

Methods

showsPrec :: Int -> Bar -> ShowS #

show :: Bar -> String #

showList :: [Bar] -> ShowS #

Generic Bar Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Bar :: Type -> Type #

Methods

from :: Bar -> Rep Bar x #

to :: Rep Bar x -> Bar #

type Rep Bar Source # 
Instance details

Defined in Chart.Types

defaultBar :: Bar Source #

The official axis bar

data Title Source #

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

Constructors

Title 

Fields

Instances
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 0) 8 TickExtend, gtick = Just (GlyphStyle {size = 3.0e-2, color = RGBA 0.50 0.50 0.50 1.00, borderColor = RGBA 0.50 0.50 0.50 1.00, borderSize = 5.0e-3, shape = VLineGlyph 5.0e-3, rotation = Nothing, translate = Nothing},1.25e-2), ttick = Just (TextStyle {size = 5.0e-2, color = RGBA 0.50 0.50 0.50 1.00, anchor = AnchorMiddle, hsize = 0.5, vsize = 1.45, nudge1 = -0.2, rotation = Nothing, translate = Nothing, hasMathjax = False},1.5e-2), ltick = Just (LineStyle {width = 5.0e-3, color = RGBA 0.50 0.50 0.50 0.05},0.0)}
Instances
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
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
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.1.1-E9vnLYsUbhm7chwZtErhMB" False) (C1 (MetaCons "TickExtend" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoTickExtend" PrefixI False) (U1 :: Type -> Type))

data Adjustments Source #

options for prettifying axis decorations

>>> defaultAdjustments
Adjustments {maxXRatio = 8.0e-2, maxYRatio = 6.0e-2, angledRatio = 0.12, allowDiagonal = True}
Instances
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

defaultAdjustments :: Adjustments Source #

The official hud adjustments.

data LegendOptions Source #

Legend options

>>> defaultLegendOptions
LegendOptions {lsize = 0.1, vgap = 0.2, hgap = 0.1, ltext = TextStyle {size = 8.0e-2, color = RGBA 0.20 0.20 0.20 1.00, anchor = AnchorMiddle, hsize = 0.5, vsize = 1.45, nudge1 = -0.2, rotation = Nothing, translate = Nothing, hasMathjax = False}, lmax = 10, innerPad = 0.1, outerPad = 0.1, legendFrame = Just (RectStyle {borderSize = 2.0e-2, borderColor = RGBA 0.50 0.50 0.50 1.00, color = RGBA 1.00 1.00 1.00 1.00}), lplace = PlaceBottom, lscale = 0.2}

Instances
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

data Colour Source #

snatching Colour as the library color representation.

Instances
Eq Colour Source # 
Instance details

Defined in Chart.Types

Methods

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

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

Show Colour Source # 
Instance details

Defined in Chart.Types

Generic Colour Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep Colour :: Type -> Type #

Methods

from :: Colour -> Rep Colour x #

to :: Rep Colour x -> Colour #

type Rep Colour Source # 
Instance details

Defined in Chart.Types

type Rep Colour = D1 (MetaData "Colour" "Chart.Types" "chart-svg-0.1.1-E9vnLYsUbhm7chwZtErhMB" True) (C1 (MetaCons "Colour'" PrefixI True) (S1 (MetaSel (Just "color'") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Color (Alpha RGB) Double))))

pattern Colour :: Double -> Double -> Double -> Double -> Colour Source #

Constructor.

opac :: Colour -> Double Source #

get opacity

setOpac :: Double -> Colour -> Colour Source #

set opacity

palette :: [Color RGB Double] Source #

some RGB colors to work with

palette1 :: [Colour] Source #

some RGBA colors

blend :: Double -> Colour -> Colour -> Colour Source #

interpolate between 2 colors

toHex :: Colour -> Text Source #

convert from Colour to #xxxxxx

grayscale :: Double -> Color RGB Double Source #

gray with 1 opacity

colorText :: Colour Source #

standard text color

re-exports

data FormatN Source #

Number formatting options.

>>> defaultFormatN
FormatComma 2
Instances
Eq FormatN Source # 
Instance details

Defined in Chart.Types

Methods

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

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

Show FormatN Source # 
Instance details

Defined in Chart.Types

Generic FormatN Source # 
Instance details

Defined in Chart.Types

Associated Types

type Rep FormatN :: Type -> Type #

Methods

from :: FormatN -> Rep FormatN x #

to :: Rep FormatN x -> FormatN #

type Rep FormatN Source # 
Instance details

Defined in Chart.Types

defaultFormatN :: FormatN Source #

The official format

fromFormatN :: IsString s => FormatN -> s Source #

textifier

toFormatN :: (Eq s, IsString s) => s -> Int -> FormatN Source #

readifier

fixed :: Int -> Double -> Text Source #

to x decimal places

comma :: Int -> Double -> Text Source #

comma format

expt :: Int -> Double -> Text Source #

scientific exponential

dollar :: Double -> Text Source #

dollars and cents

formatN :: FormatN -> Double -> Text Source #

make text

precision :: (Int -> Double -> Text) -> Int -> [Double] -> [Text] Source #

Provide formatted text for a list of numbers so that they are just distinguished. 'precision commas 2 ticks' means give the tick labels as much precision as is needed for them to be distinguished, but with at least 2 significant figures, and format Integers with commas.

formatNs :: FormatN -> [Double] -> [Text] Source #

textifier

projectTo :: (Ord a, Fractional a) => Rect a -> [Spot a] -> [Spot a] Source #

project a [Spot a] from it's folded space to the given area

>>> projectTo unitRect (SpotPoint <$> zipWith Point [0..2] [0..2])
[SpotPoint Point -0.5 -0.5,SpotPoint Point 0.0 0.0,SpotPoint Point 0.5 0.5]

projectSpots :: (Ord a, Fractional a) => Rect a -> [Chart a] -> [Chart a] Source #

projectSpotsWith :: (Ord a, Fractional a) => Rect a -> Rect a -> [Chart a] -> [Chart a] Source #

dataBox :: Ord a => [Chart a] -> Maybe (Rect a) Source #

 

moveChart :: (Ord a, Fractional a) => Spot a -> [Chart a] -> [Chart a] Source #

runHudWith Source #

Arguments

:: Rect Double

initial canvas dimension

-> Rect Double

initial data dimension

-> [Hud Double]

huds to add

-> [Chart Double]

underlying chart

-> [Chart Double]

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. used once in makePixelTick

runHud :: Rect Double -> [Hud Double] -> [Chart Double] -> [Chart Double] Source #

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. used once in renderHudChart

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 also return a blank chart with the new data dimension. The complexity internally 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.

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)

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

svg :: Chart Double -> Html () Source #

convert a Chart to svg

svgt :: Chart Double -> (TextStyle, Text) -> Html () Source #

add a tooltip to a chart

chartDef :: Chart a -> [Html ()] Source #

chartDefs :: [Chart a] -> Html () Source #

get chart definitions

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

the geometric dimensions of a Chart inclusive of style geometry

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

the extra geometric dimensions of a [Chart]

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

geometric dimensions of a [Chart] not including style

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

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

additively pad a [Chart]

>>> padChart 0.1 [Chart (RectA defaultRectStyle) [SpotRect unitRect]]
[Chart {annotation = RectA (RectStyle {borderSize = 1.0e-2, borderColor = RGBA 0.12 0.47 0.71 0.80, color = RGBA 0.12 0.47 0.71 0.30}), spots = [SpotRect Rect -0.5 0.5 -0.5 0.5]},Chart {annotation = BlankA, spots = [SpotRect Rect -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 blank
[Chart {annotation = RectA (RectStyle {borderSize = 1.0e-2, borderColor = RGBA 0.12 0.47 0.71 0.80, color = RGBA 0.12 0.47 0.71 0.30}), spots = []},Chart {annotation = BlankA, spots = []}]