chart-unit-0.6.0.2: Native haskell charts.

Safe HaskellNone
LanguageHaskell2010

Chart.Core

Contents

Description

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 wrapped Rect 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]))

Synopsis

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 Charts, 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.

asquare :: Rect Double Source #

a 1:1 aspect

sixbyfour :: Rect Double Source #

a 1.5:1 aspect

golden :: Rect Double Source #

golden ratio

widescreen :: Rect Double Source #

a 3:1 aspect

skinny :: Rect Double Source #

a skinny 5:1 aspect

data AlignH Source #

horizontal alignment

Instances

data AlignV Source #

vertical alignment

Constructors

AlignTop 
AlignMid 
AlignBottom 

Instances

alignHU :: AlignH -> Double Source #

conversion of horizontal alignment to (one :: Range Double) limits

alignHTU :: AlignH -> Double Source #

svg text is forced to be lower left (-0.5) by default

alignVU :: AlignV -> Double Source #

conversion of vertical alignment to (one :: Range Double) limits

alignVTU :: AlignV -> Double Source #

svg text is lower by default

Types

data Orientation Source #

Orientation for an element. Watch this space for curvature!

Constructors

Hori 
Vert 

data Place Source #

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

Instances

Eq Place Source # 

Methods

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

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

Show Place Source # 

Methods

showsPrec :: Int -> Place -> ShowS #

show :: Place -> String #

showList :: [Place] -> ShowS #

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.

positioned :: R2 r => r Double -> Chart b -> Chart b Source #

position an element at a point

p_ :: R2 r => r Double -> Point V2 Double Source #

convert an R2 to a diagrams Point

r_ :: R2 r => r a -> V2 a Source #

convert an R2 to a V2

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

sepVert :: Double -> Chart b -> Chart b Source #

vertical separator

sepHori :: Double -> Chart b -> Chart b Source #

horizontal separator

Color

chart-unit exposes the colour and palette libraries for color combinators

ucolor :: (Floating a, Ord a) => a -> a -> a -> a -> AlphaColour a Source #

convert an rgba spec to an AlphaColour

ublue :: AlphaColour Double Source #

the official chart-unit blue

ugrey :: AlphaColour Double Source #

the official chart-unit grey

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

Orphan instances

R1 Pair Source #

These are difficult to avoid

Methods

_x :: Functor f => (a -> f a) -> Pair a -> f (Pair a) #

R2 Pair Source # 

Methods

_y :: Functor f => (a -> f a) -> Pair a -> f (Pair a) #

_xy :: Functor f => (V2 a -> f (V2 a)) -> Pair a -> f (Pair a) #