Safe Haskell | None |
---|---|
Language | Haskell2010 |
In making a chart, there are three main size domains you have to be concerned about:
- the range of the data being charted. This range is often projected onto chart elements such as axes and labels. A data range in two dimensions is a
Rect
a. - the scale of various chart primitives and elements. The overall dimensions of the chart canvas - the rectangular shape on which the data is represented - is referred to as an
Aspect
in the api, and is a wrappedRect
to distinguish aspects from rect ranges. The default chart options tend to be callibrated to Aspects around widths of one. - the size of the chart rendered as an image. Backends tend to shrink charts to fit the rectangle shape specified in the render function, and a loose sympathy is expected between the aspect and a chart's ultimate physical size.
Jumping ahead a bit, the code snippet below draws vertical lines using a data range of "Rect 0 12 0 0.2" (slightly different to the actual data range), using a widescreen (3:1) aspect, and renders the chart as a 300 by 120 pixel svg:
scaleExample :: IO () scaleExample = fileSvg "other/scaleExample.svg" (#size .~ Pair 300 120 $ def) $ withHud def widescreen (Rect 0 12 0 0.2) (lineChart (repeat def)) (vlineOneD ((0.01*) <$> [0..10]))
- type Chart b = (Renderable (Path V2 Double) b, Renderable (Text Double) b) => QDiagram b V2 Double Any
- range :: (Foldable f, Foldable g) => g (f (Pair Double)) -> Rect Double
- projectss :: (Functor f, Functor g) => Rect Double -> Rect Double -> g (f (Pair Double)) -> g (f (Pair Double))
- aspect :: (BoundedField a, Ord a, Multiplicative a, FromInteger a) => a -> Rect a
- asquare :: Rect Double
- sixbyfour :: Rect Double
- golden :: Rect Double
- widescreen :: Rect Double
- skinny :: Rect Double
- data AlignH
- data AlignV
- alignHU :: AlignH -> Double
- alignHTU :: AlignH -> Double
- alignVU :: AlignV -> Double
- alignVTU :: AlignV -> Double
- data Orientation
- data Place
- positioned :: R2 r => r Double -> Chart b -> Chart b
- p_ :: R2 r => r Double -> Point V2 Double
- r_ :: R2 r => r a -> V2 a
- stack :: (R2 r, V a ~ V2, Foldable t, Juxtaposable a, Semigroup a, N a ~ Double, Monoid a) => r Double -> (b -> a) -> t b -> a
- vert :: (V a ~ V2, Foldable t, Juxtaposable a, Semigroup a, N a ~ Double, Monoid a) => (b -> a) -> t b -> a
- hori :: (V a ~ V2, Foldable t, Juxtaposable a, Semigroup a, N a ~ Double, Monoid a) => (b -> a) -> t b -> a
- sepVert :: Double -> Chart b -> Chart b
- sepHori :: Double -> Chart b -> Chart b
- data UColor a = UColor {}
- acolor :: (Floating a, Num a, Ord a) => UColor a -> AlphaColour a
- ucolor :: (Floating a, Num a, Ord a) => AlphaColour a -> UColor a
- ccolor :: (Floating a, Num a, Ord a) => Colour a -> UColor a
- ublue :: UColor Double
- ugrey :: UColor Double
- utrans :: UColor Double
- ublack :: UColor Double
- uwhite :: UColor Double
- scaleX :: (N t ~ Double, Transformable t, R2 (V t), Additive (V t)) => Double -> t -> t
- scaleY :: (N t ~ Double, Transformable t, R2 (V t), Additive (V t)) => Double -> t -> t
- scale :: (N t ~ Double, Transformable t, R2 (V t), Additive (V t)) => Double -> t -> t
Chart types
type Chart b = (Renderable (Path V2 Double) b, Renderable (Text Double) b) => QDiagram b V2 Double Any Source #
A Chart is simply a type synonym for a typical Diagrams object. A close relation to this type is Diagram
B
, but this usage tends to force a single backend (B comes from the backend libraries), so making Chart b's maintains backend polymorphism.
Just about everything - text, circles, lines, triangles, charts, axes, titles, legends etc - are Chart
s, which means that most things are amenable to full use of the combinatorially-inclined diagrams-lib.
Scaling
range :: (Foldable f, Foldable g) => g (f (Pair Double)) -> Rect Double Source #
determine the range of a double-containered set of data
projectss :: (Functor f, Functor g) => Rect Double -> Rect Double -> g (f (Pair Double)) -> g (f (Pair Double)) Source #
project a double-containered set of data to a new Rect range
aspect :: (BoundedField a, Ord a, Multiplicative a, FromInteger a) => a -> Rect a Source #
the aspect of a chart expressed as a ratio of x-plane : y-plane.
widescreen :: Rect Double Source #
a 3:1 aspect
horizontal alignment
vertical alignment
alignHU :: AlignH -> Double Source #
conversion of horizontal alignment to (one :: Range Double) limits
alignVU :: AlignV -> Double Source #
conversion of vertical alignment to (one :: Range Double) limits
Types
data Orientation Source #
Orientation for an element. Watch this space for curvature!
Placement of elements around (what is implicity but maybe shouldn't just be) a rectangular canvas
Combinators
The concept of a point on a chart is the polymorphic R2
from the linear
library. Diagrams most often uses Point
, which is a wrapped V2
. The Pair
type from 'numhask-range' is often used as a point reference.
stack :: (R2 r, V a ~ V2, Foldable t, Juxtaposable a, Semigroup a, N a ~ Double, Monoid a) => r Double -> (b -> a) -> t b -> a Source #
foldMap for beside; stacking chart elements in a direction, with a premap
vert :: (V a ~ V2, Foldable t, Juxtaposable a, Semigroup a, N a ~ Double, Monoid a) => (b -> a) -> t b -> a Source #
combine elements vertically, with a premap
hori :: (V a ~ V2, Foldable t, Juxtaposable a, Semigroup a, N a ~ Double, Monoid a) => (b -> a) -> t b -> a Source #
combine elements horizontally, with a premap
Color
chart-unit exposes the colour
and palette
libraries for color combinators
acolor :: (Floating a, Num a, Ord a) => UColor a -> AlphaColour a Source #
convert a UColor to an AlphaColour
ucolor :: (Floating a, Num a, Ord a) => AlphaColour a -> UColor a Source #
convert an AlphaColour to a UColor
Compatability
scaleX :: (N t ~ Double, Transformable t, R2 (V t), Additive (V t)) => Double -> t -> t Source #
the diagrams scaleX with a zero divide guard to avoid error throws
scaleY :: (N t ~ Double, Transformable t, R2 (V t), Additive (V t)) => Double -> t -> t Source #
the diagrams scaleY with a zero divide guard to avoid error throws
scale :: (N t ~ Double, Transformable t, R2 (V t), Additive (V t)) => Double -> t -> t Source #
the diagrams scale with a zero divide guard to avoid error throws