Safe Haskell | None |
---|---|
Language | Haskell2010 |
A haskell Charting library targetting SVGs
Synopsis
- data Chart a = Chart {
- annotation :: Annotation
- xys :: [XY a]
- moveChart :: Additive a => XY a -> [Chart a] -> [Chart a]
- projectXYs :: Rect Double -> [Chart Double] -> [Chart Double]
- projectXYsWith :: Rect Double -> Rect Double -> [Chart Double] -> [Chart Double]
- projectArcPosition :: Rect Double -> Rect Double -> ArcPosition Double -> ArcInfo Double
- data Annotation
- annotationText :: Annotation -> Text
- scaleAnn :: Double -> Annotation -> Annotation
- padRect :: Num a => a -> Rect a -> Rect a
- data RectStyle = RectStyle {
- borderSize :: Double
- borderColor :: Colour
- color :: Colour
- defaultRectStyle :: RectStyle
- blob :: Colour -> RectStyle
- clear :: RectStyle
- border :: Double -> Colour -> RectStyle
- data TextStyle = TextStyle {}
- defaultTextStyle :: TextStyle
- data GlyphStyle = GlyphStyle {}
- defaultGlyphStyle :: GlyphStyle
- data GlyphShape
- glyphText :: GlyphShape -> Text
- data LineStyle = LineStyle {}
- defaultLineStyle :: LineStyle
- data LineCap
- fromLineCap :: IsString s => LineCap -> s
- toLineCap :: (Eq s, IsString s) => s -> LineCap
- data LineJoin
- fromLineJoin :: IsString s => LineJoin -> s
- toLineJoin :: (Eq s, IsString s) => s -> LineJoin
- fromDashArray :: [Double] -> Text
- data Anchor
- fromAnchor :: IsString s => Anchor -> s
- toAnchor :: (Eq s, IsString s) => s -> Anchor
- data PathStyle = PathStyle {
- borderSize :: Double
- borderColor :: Colour
- color :: Colour
- toPathChart :: PathStyle -> [(PathInfo Double, Point Double)] -> Chart Double
- defaultPathStyle :: PathStyle
- data ChartDims a = ChartDims {}
- newtype HudT m a = Hud {}
- type Hud = HudT Identity
- simulHud :: (Ord a, Monad m) => HudT m a -> HudT m a -> HudT m a
- data HudOptions = HudOptions {
- hudCanvas :: Maybe RectStyle
- hudTitles :: [Title]
- hudAxes :: [AxisOptions]
- hudLegend :: Maybe (LegendOptions, [(Annotation, Text)])
- defaultHudOptions :: HudOptions
- defaultCanvas :: RectStyle
- runHudWith :: Rect Double -> Rect Double -> [Hud Double] -> [Chart Double] -> [Chart Double]
- runHud :: Rect Double -> [Hud Double] -> [Chart Double] -> [Chart Double]
- makeHud :: Rect Double -> HudOptions -> ([Hud Double], [Chart Double])
- data ChartAspect
- toChartAspect :: (Eq s, IsString s) => s -> Double -> ChartAspect
- fromChartAspect :: IsString s => ChartAspect -> s
- initialCanvas :: ChartAspect -> [Chart Double] -> Rect Double
- chartAspectHud :: Monad m => ChartAspect -> HudT m Double
- canvas :: Monad m => RectStyle -> HudT m Double
- title :: Monad m => Title -> HudT m Double
- tick :: Monad m => Place -> Tick -> HudT m Double
- data AxisOptions = AxisOptions {}
- defaultAxisOptions :: AxisOptions
- flipAxis :: AxisOptions -> AxisOptions
- data Place
- placeText :: Place -> Text
- data AxisBar = AxisBar {}
- defaultAxisBar :: AxisBar
- data Title = Title {}
- defaultTitle :: Text -> Title
- data Tick = Tick {}
- defaultGlyphTick :: GlyphStyle
- defaultTextTick :: TextStyle
- defaultLineTick :: LineStyle
- defaultTick :: Tick
- data TickStyle
- = TickNone
- | TickLabels [Text]
- | TickRound FormatN Int TickExtend
- | TickExact FormatN Int
- | TickPlaced [(Double, Text)]
- defaultTickStyle :: TickStyle
- tickStyleText :: TickStyle -> Text
- data TickExtend
- adjustTick :: Adjustments -> Rect Double -> Rect Double -> Place -> Tick -> Tick
- makeTickDates :: PosDiscontinuous -> Maybe Text -> Int -> [UTCTime] -> [(Int, Text)]
- makeTickDatesContinuous :: PosDiscontinuous -> Maybe Text -> Int -> [UTCTime] -> [(Double, Text)]
- data Adjustments = Adjustments {
- maxXRatio :: Double
- maxYRatio :: Double
- angledRatio :: Double
- allowDiagonal :: Bool
- defaultAdjustments :: Adjustments
- data LegendOptions = LegendOptions {}
- defaultLegendOptions :: LegendOptions
- legendHud :: LegendOptions -> [Chart Double] -> Hud Double
- data Orientation
- fromOrientation :: IsString s => Orientation -> s
- toOrientation :: (Eq s, IsString s) => s -> Orientation
- data CssOptions
- data SvgOptions = SvgOptions {}
- defaultSvgOptions :: SvgOptions
- defaultSvgFrame :: RectStyle
- padChart :: Double -> [Chart Double] -> [Chart Double]
- frameChart :: RectStyle -> Double -> [Chart Double] -> [Chart Double]
- hori :: Double -> [[Chart Double]] -> [Chart Double]
- vert :: Double -> [[Chart Double]] -> [Chart Double]
- stack :: Int -> Double -> [[Chart Double]] -> [Chart Double]
- padBox :: Maybe (Rect Double) -> Rect Double
- dataBox :: Chart Double -> Maybe (Rect Double)
- dataBoxes :: [Chart Double] -> Maybe (Rect Double)
- dataBoxesS :: [Chart Double] -> Rect Double
- styleBox :: Chart Double -> Maybe (Rect Double)
- styleBoxes :: [Chart Double] -> Maybe (Rect Double)
- styleBoxesS :: [Chart Double] -> Rect Double
- styleBoxText :: TextStyle -> Text -> Point Double -> Rect Double
- styleBoxGlyph :: GlyphStyle -> Rect Double
- module Chart.Render
- module Chart.Bar
- module Chart.Surface
- module Data.Colour
- module Data.FormatN
- module Data.Path
- module NumHask.Space
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:
- the data to be represented.
- how the data will be represented on a screen, and.
- 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 = [[(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)]] :: [[(Double, Double)]]
>>>
let ls = fmap (uncurry P) <$> xs
>>>
:t ls
ls :: [[XY 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 lineChart = zipWith Chart anns ls
>>>
:t lineChart
lineChart :: [Chart Double]
Most charts will, in reality, be a list of charts such as this, and much of the library API is designed for this.
writeChartSvgDefault "other/lines.svg" lineChart
chart-svg takes inspiration from gaming heads-up display aesthetics. Chart decorations such as titles and axes are tools to interpret the landscape of data being viewed. They should be readily transparent, have sane defaults but be fully configurable.
The library considers a hud to be a recipe for the creation of a Chart
list, but with the physical, on-the-page representation of the data in mind.
Here is the line chart presented with default hud options.
writeChartSvgHud "other/lineshud.svg" lineChart
Hud
creation is a process of integrating the data domain and the physical representation. In the chart above, for example, the axis placement takes into account the physical attributes of the thick blue line which extends slightly beyond the abstract data range. The data area (the canvas) has also been extended so that a tick value (3.5 on the x-axis) can be included.
Beyond this, there is nothing special about hud elements such as tick marks and titles, axes. Once they are created (with runHudWith
) they themselves become charts.
Chart
A Chart
is annotated xy-data.
Chart | |
|
Instances
Eq a => Eq (Chart a) Source # | |
Show a => Show (Chart a) Source # | |
Generic (Chart a) Source # | |
type Rep (Chart a) Source # | |
Defined in Chart.Types type Rep (Chart a) = D1 ('MetaData "Chart" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" 'False) (C1 ('MetaCons "Chart" 'PrefixI 'True) (S1 ('MetaSel ('Just "annotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Annotation) :*: S1 ('MetaSel ('Just "xys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [XY a]))) |
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.
RectA RectStyle | |
TextA TextStyle [Text] | |
GlyphA GlyphStyle | |
LineA LineStyle | |
PathA PathStyle [PathInfo Double] | |
BlankA |
Instances
annotationText :: Annotation -> Text Source #
textifier
scaleAnn :: Double -> Annotation -> Annotation Source #
Generically scale an Annotation.
Styles
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}
writeChartSvgDefault "other/unit.svg" [Chart (RectA defaultRectStyle) [one]]
RectStyle | |
|
Instances
Eq RectStyle Source # | |
Show RectStyle Source # | |
Generic RectStyle Source # | |
type Rep RectStyle Source # | |
Defined in Chart.Types type Rep RectStyle = D1 ('MetaData "RectStyle" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" '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)))) |
defaultRectStyle :: RectStyle Source #
the style
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}
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}
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}
>>>
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]]
writeChartSvgDefault "other/text.svg" t
Instances
defaultTextStyle :: TextStyle Source #
the offical text style
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}
See glyphsExample
.
Instances
defaultGlyphStyle :: GlyphStyle Source #
the offical glyph style
data GlyphShape Source #
glyph shapes
Instances
glyphText :: GlyphShape -> Text Source #
textifier
line style
>>>
defaultLineStyle
LineStyle {width = 1.2e-2, color = RGBA 0.65 0.81 0.89 0.30, linecap = Nothing, linejoin = Nothing, dasharray = Nothing, dashoffset = Nothing}
See also https://developer.mozilla.org/en-US/docs/Web/SVG/Attribute
Instances
Eq LineStyle Source # | |
Show LineStyle Source # | |
Generic LineStyle Source # | |
type Rep LineStyle Source # | |
Defined in Chart.Types type Rep LineStyle = D1 ('MetaData "LineStyle" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" 'False) (C1 ('MetaCons "LineStyle" 'PrefixI 'True) ((S1 ('MetaSel ('Just "width") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: (S1 ('MetaSel ('Just "color") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Colour) :*: S1 ('MetaSel ('Just "linecap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LineCap)))) :*: (S1 ('MetaSel ('Just "linejoin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe LineJoin)) :*: (S1 ('MetaSel ('Just "dasharray") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Double])) :*: S1 ('MetaSel ('Just "dashoffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Double)))))) |
defaultLineStyle :: LineStyle Source #
the official default line style
line cap style
Instances
Eq LineCap Source # | |
Show LineCap Source # | |
Generic LineCap Source # | |
type Rep LineCap Source # | |
Defined in Chart.Types type Rep LineCap = D1 ('MetaData "LineCap" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" '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
line cap style
Instances
Eq LineJoin Source # | |
Show LineJoin Source # | |
Generic LineJoin Source # | |
type Rep LineJoin Source # | |
Defined in Chart.Types type Rep LineJoin = D1 ('MetaData "LineJoin" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" '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
fromDashArray :: [Double] -> Text Source #
Convert a dash representation from a list to text
position anchor
Instances
Eq Anchor Source # | |
Show Anchor Source # | |
Generic Anchor Source # | |
type Rep Anchor Source # | |
Defined in Chart.Types type Rep Anchor = D1 ('MetaData "Anchor" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" '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
Path styling
>>>
defaultPathStyle
PathStyle {borderSize = 1.0e-2, borderColor = RGBA 0.12 0.47 0.71 0.80, color = RGBA 0.12 0.47 0.71 0.30}
PathStyle | |
|
Instances
Eq PathStyle Source # | |
Show PathStyle Source # | |
Generic PathStyle Source # | |
type Rep PathStyle Source # | |
Defined in Chart.Types type Rep PathStyle = D1 ('MetaData "PathStyle" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" 'False) (C1 ('MetaCons "PathStyle" '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)))) |
toPathChart :: PathStyle -> [(PathInfo Double, Point Double)] -> Chart Double Source #
Convert from a path command list to a PathA chart
defaultPathStyle :: PathStyle Source #
the style
Hud types
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.
Instances
Eq a => Eq (ChartDims a) Source # | |
Show a => Show (ChartDims a) Source # | |
Generic (ChartDims a) Source # | |
type Rep (ChartDims a) Source # | |
Defined in Chart.Types type Rep (ChartDims a) = D1 ('MetaData "ChartDims" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" '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))))) |
Hud monad transformer
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
.
HudOptions | |
|
Instances
defaultHudOptions :: HudOptions Source #
The official hud options.
defaultCanvas :: RectStyle Source #
The official hud canvas
:: 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).
:: 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.
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
toChartAspect :: (Eq s, IsString s) => s -> Double -> ChartAspect Source #
readifier
fromChartAspect :: IsString s => ChartAspect -> s Source #
textifier
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
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
defaultAxisOptions :: AxisOptions Source #
The official axis
flipAxis :: AxisOptions -> AxisOptions Source #
flip an axis from being an X dimension to a Y one or vice-versa.
Placement of elements around (what is implicity but maybe shouldn't just be) a rectangular canvas
Instances
Eq Place Source # | |
Show Place Source # | |
Generic Place Source # | |
type Rep Place Source # | |
Defined in Chart.Types type Rep Place = D1 ('MetaData "Place" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" '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)))))) |
The bar on an axis representing the x or y plane.
>>>
defaultAxisBar
AxisBar {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}
Instances
Eq AxisBar Source # | |
Show AxisBar Source # | |
Generic AxisBar Source # | |
type Rep AxisBar Source # | |
Defined in Chart.Types type Rep AxisBar = D1 ('MetaData "AxisBar" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" 'False) (C1 ('MetaCons "AxisBar" 'PrefixI 'True) (S1 ('MetaSel ('Just "rstyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RectStyle) :*: (S1 ('MetaSel ('Just "wid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "buff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))) |
defaultAxisBar :: AxisBar Source #
The official axis bar
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 = RGBA 0.20 0.20 0.20 1.00, anchor = AnchorMiddle, hsize = 0.5, vsize = 1.45, nudge1 = -0.2, rotation = Nothing, translate = Nothing}, place = PlaceTop, anchor = AnchorMiddle, buff = 4.0e-2}
Instances
Eq Title Source # | |
Show Title Source # | |
Generic Title Source # | |
type Rep Title Source # | |
Defined in Chart.Types type Rep Title = D1 ('MetaData "Title" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" 'False) (C1 ('MetaCons "Title" 'PrefixI 'True) ((S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "style") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TextStyle)) :*: (S1 ('MetaSel ('Just "place") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Place) :*: (S1 ('MetaSel ('Just "anchor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Anchor) :*: S1 ('MetaSel ('Just "buff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))))) |
defaultTitle :: Text -> Title Source #
The official hud title
xy coordinate markings
>>>
defaultTick
Tick {tstyle = TickRound (FormatComma (Just 2)) 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},1.5e-2), ltick = Just (LineStyle {width = 5.0e-3, color = RGBA 0.50 0.50 0.50 0.05, linecap = Nothing, linejoin = Nothing, dasharray = Nothing, dashoffset = Nothing},0.0)}
Instances
Eq Tick Source # | |
Show Tick Source # | |
Generic Tick Source # | |
type Rep Tick Source # | |
Defined in Chart.Types type Rep Tick = D1 ('MetaData "Tick" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" 'False) (C1 ('MetaCons "Tick" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tstyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TickStyle) :*: S1 ('MetaSel ('Just "gtick") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (GlyphStyle, Double)))) :*: (S1 ('MetaSel ('Just "ttick") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (TextStyle, Double))) :*: S1 ('MetaSel ('Just "ltick") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (LineStyle, Double)))))) |
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
Style of tick marks on an axis.
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
defaultTickStyle :: TickStyle Source #
The official tick style
tickStyleText :: TickStyle -> Text Source #
textifier
data TickExtend Source #
Whether Ticks are allowed to extend the data range
Instances
Eq TickExtend Source # | |
Defined in Chart.Types (==) :: TickExtend -> TickExtend -> Bool # (/=) :: TickExtend -> TickExtend -> Bool # | |
Show TickExtend Source # | |
Defined in Chart.Types showsPrec :: Int -> TickExtend -> ShowS # show :: TickExtend -> String # showList :: [TickExtend] -> ShowS # | |
Generic TickExtend Source # | |
Defined in Chart.Types type Rep TickExtend :: Type -> Type # from :: TickExtend -> Rep TickExtend x # to :: Rep TickExtend x -> TickExtend # | |
type Rep TickExtend Source # | |
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}
Adjustments | |
|
Instances
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}, 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
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
Instances
Eq Orientation Source # | |
Defined in Chart.Types (==) :: Orientation -> Orientation -> Bool # (/=) :: Orientation -> Orientation -> Bool # | |
Show Orientation Source # | |
Defined in Chart.Types showsPrec :: Int -> Orientation -> ShowS # show :: Orientation -> String # showList :: [Orientation] -> ShowS # | |
Generic Orientation Source # | |
Defined in Chart.Types type Rep Orientation :: Type -> Type # from :: Orientation -> Rep Orientation x # to :: Rep Orientation x -> Orientation # | |
type Rep Orientation Source # | |
fromOrientation :: IsString s => Orientation -> s Source #
textifier
toOrientation :: (Eq s, IsString s) => s -> Orientation Source #
readifier
SVG primitives
data CssOptions Source #
Instances
Eq CssOptions Source # | |
Defined in Chart.Types (==) :: CssOptions -> CssOptions -> Bool # (/=) :: CssOptions -> CssOptions -> Bool # | |
Show CssOptions Source # | |
Defined in Chart.Types showsPrec :: Int -> CssOptions -> ShowS # show :: CssOptions -> String # showList :: [CssOptions] -> ShowS # | |
Generic CssOptions Source # | |
Defined in Chart.Types type Rep CssOptions :: Type -> Type # from :: CssOptions -> Rep CssOptions x # to :: Rep CssOptions x -> CssOptions # | |
type Rep CssOptions Source # | |
Defined in Chart.Types type Rep CssOptions = D1 ('MetaData "CssOptions" "Chart.Types" "chart-svg-0.2.0-92kmzNutfhz4Yaw4NJVLJs" '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}
writeChartSvg "other/svgoptions.svg" (SvgChart (defaultSvgOptions & #chartAspect .~ FixedAspect 0.7) mempty [] lines)
SvgOptions | |
|
Instances
defaultSvgOptions :: SvgOptions Source #
The official svg options
defaultSvgFrame :: RectStyle Source #
frame style
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 = RGBA 0.12 0.47 0.71 0.80, color = RGBA 0.12 0.47 0.71 0.30}), 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 = RGBA 0.12 0.47 0.71 0.80, color = RGBA 0.12 0.47 0.71 0.30}), 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
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.Render
module Chart.Bar
module Chart.Surface
module Data.Colour
module Data.FormatN
module Data.Path
module NumHask.Space