chart-unit-0.6.1.0: Native haskell charts.

Safe HaskellNone
LanguageHaskell2010

Chart

Contents

Description

The Chart module exports all of the chart-unit functionality, and most of what you need from outside libraries.

Chart is designed to be used in conjunction with both the numhask and diagrams preludes. Diagrams.Prelude conatins much of the lens library and many re-exports that clash with NumHask, so best to import qualified.

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLabels #-}
{-# OPTIONS_GHC -Wall #-}

import Chart
import Control.Lens
import Data.Generics.Labels()
import qualified Diagrams.Prelude as D
import NumHask.Prelude

Each chart type is built up from a few different elements:

  • data
  • a type of chart
  • representation options specific to the chart type
  • axes
  • other chart bling, such as titles and legends

Chart data is most often one or more traversable series. Also most often, the data is 2-dimensional, representing where on the chart to place the representation. Some sort of `(Traversable f) => [f Pair]` is commonly used in the library api.

ls :: [[Pair Double]]
ls =
  map (uncurry Pair) <$>
  [ [(0.0, 1.0), (1.0, 1.0), (2.0, 5.0)]
  , [(0.0, 0.0), (3.0, 3.0)]
  , [(0.5, 4.0), (0.5, 0)]
  ]

Each data series has representation options dependent on the chart type

lopts :: [LineOptions]
lopts =
  zipWith
  (\x y -> LineOptions x (withOpacity (d3Colors1 y) 0.6))
  [0.01, 0.02, 0.005]
  [0,1,2]

The lens library is used extensively for configuration, and generic-lens-labels has been adopted to reduce line noise ...

as :: [AxisOptions]
as = 
  [ defXAxis
  , defYAxis
  , #label . #orientation .~ Pair 0 1 $
    #place .~ PlaceTop $
    defXAxis
  , #label . #orientation .~ Pair 1 0 $
    #place .~ PlaceRight $
    defYAxis
  ] 

in the examples (but not in core library code), Data.Generic.Labels is used which has its detractions in the form of orphan instance fuss and bother. For example, using core generic-lens:

#label . #orientation .~ Pair 0 1

translates to:

field @"label" . field @"orientation" .~ Pair 0 1

which is also a pretty fine api.

Using data-default, lens and OverloadedLabels tends to encourage a vertical style, which may annoy line counters, but lead to clear code and ease of editing.

titles' :: [(TitleOptions, Text)]
titles' =
  [ (def, "Example Chart")
  , ( #align .~ AlignCenter $
      #text . #rotation .~ 90 $
      #text . #size .~ 0.12 $
      #place .~ PlaceLeft $
      def
    , "left axis title")
  , ( #text . #color .~ ublue $
      #text . #size .~ 0.08 $
      #align .~ AlignRight $
      #place .~ PlaceBottom $
      def
    , "bottom right, non-essential note")
  ]

legends' :: [(LegendType, Text)]
legends' =
  [(LegendText def, "legend")] <>
  [(LegendPixel (blob ublue) 0.05, "pixel")] <>
  [(LegendRect def 0.05, "rect")] <>
  [(LegendGLine def def 0.10, "glyph+line")] <>
  [(LegendGlyph def, "just a glyph")] <>
  zipWith
    (\x y -> (LegendLine x 0.05, y))
    lopts
    ["short", "much longer name", "line 3"]

All of which makes chart-unit highly customisable ...

mainExample :: Chart b
mainExample = withHud_ opts sixbyfour (lineChart lopts) ls
  where
    opts =
      #titles .~ titles' $
      #axes .~ as $
      #axes %~ map (#outerPad .~ 1) $
      #legends .~ [#chartType .~ legends' $ def] $
      def

main :: IO ()
main = fileSvg "other/mainExample.svg" def mainExample

There are three different ways of combining charts (and note adding a hud to a chart is a subset of combining charts):

  • mappend them
hud ho asp r <>
lineChart ld sixbyfour r d
withHud_ ho asp (lineChart ld) d
renderChart (ChartOptions (Just r) asp [HudChart ho, LineChart (zip ld d)])

And these three methods are morally equivalent.

Synopsis

chart-unit

module Chart.ADT

module Chart.Bar

module Chart.Core

module Chart.Data

module Chart.Hud

module Chart.Line

module Chart.Rect

module Chart.Svg

module Chart.Text

numhask-range

color

fonts

Default

class Default a where #

A class for types with a default value.

Methods

def :: a #

The default value for this type.

Instances

Default Double 

Methods

def :: Double #

Default Float 

Methods

def :: Float #

Default Int 

Methods

def :: Int #

Default Int8 

Methods

def :: Int8 #

Default Int16 

Methods

def :: Int16 #

Default Int32 

Methods

def :: Int32 #

Default Int64 

Methods

def :: Int64 #

Default Integer 

Methods

def :: Integer #

Default Ordering 

Methods

def :: Ordering #

Default Word 

Methods

def :: Word #

Default Word8 

Methods

def :: Word8 #

Default Word16 

Methods

def :: Word16 #

Default Word32 

Methods

def :: Word32 #

Default Word64 

Methods

def :: Word64 #

Default () 

Methods

def :: () #

Default All 

Methods

def :: All #

Default Any 

Methods

def :: Any #

Default CShort 

Methods

def :: CShort #

Default CUShort 

Methods

def :: CUShort #

Default CInt 

Methods

def :: CInt #

Default CUInt 

Methods

def :: CUInt #

Default CLong 

Methods

def :: CLong #

Default CULong 

Methods

def :: CULong #

Default CLLong 

Methods

def :: CLLong #

Default CULLong 

Methods

def :: CULLong #

Default CFloat 

Methods

def :: CFloat #

Default CDouble 

Methods

def :: CDouble #

Default CPtrdiff 

Methods

def :: CPtrdiff #

Default CSize 

Methods

def :: CSize #

Default CSigAtomic 

Methods

def :: CSigAtomic #

Default CClock 

Methods

def :: CClock #

Default CTime 

Methods

def :: CTime #

Default CUSeconds 

Methods

def :: CUSeconds #

Default CSUSeconds 

Methods

def :: CSUSeconds #

Default CIntPtr 

Methods

def :: CIntPtr #

Default CUIntPtr 

Methods

def :: CUIntPtr #

Default CIntMax 

Methods

def :: CIntMax #

Default CUIntMax 

Methods

def :: CUIntMax #

Default FontSlant 

Methods

def :: FontSlant #

Default FontWeight 

Methods

def :: FontWeight #

Default FillRule 

Methods

def :: FillRule #

Default LineCap 

Methods

def :: LineCap #

Default LineJoin 

Methods

def :: LineJoin #

Default LineMiterLimit 

Methods

def :: LineMiterLimit #

Default ArrowOptions # 

Methods

def :: ArrowOptions #

Default PixelationOptions # 
Default RectOptions # 

Methods

def :: RectOptions #

Default SvgOptions # 

Methods

def :: SvgOptions #

Default LabelOptions # 

Methods

def :: LabelOptions #

Default TextOptions # 

Methods

def :: TextOptions #

Default TextSvgOptions # 

Methods

def :: TextSvgOptions #

Default TextPathOptions # 
Default GlyphOptions # 

Methods

def :: GlyphOptions #

Default LineOptions # 

Methods

def :: LineOptions #

Default GridOptions # 

Methods

def :: GridOptions #

Default LegendOptions # 

Methods

def :: LegendOptions #

Default TitleOptions # 

Methods

def :: TitleOptions #

Default AutoOptions # 

Methods

def :: AutoOptions #

Default AxisOptions # 

Methods

def :: AxisOptions #

Default HudOptions # 

Methods

def :: HudOptions #

Default BarOptions # 

Methods

def :: BarOptions #

Default ChartOptions # 

Methods

def :: ChartOptions #

Default [a] 

Methods

def :: [a] #

Default (Maybe a) 

Methods

def :: Maybe a #

Integral a => Default (Ratio a) 

Methods

def :: Ratio a #

Default a => Default (IO a) 

Methods

def :: IO a #

(Read n, RealFloat n) => Default (TextOpts n) 

Methods

def :: TextOpts n #

(Default a, RealFloat a) => Default (Complex a) 

Methods

def :: Complex a #

Default a => Default (Dual a) 

Methods

def :: Dual a #

Default (Endo a) 

Methods

def :: Endo a #

Num a => Default (Sum a) 

Methods

def :: Sum a #

Num a => Default (Product a) 

Methods

def :: Product a #

Default (First a) 

Methods

def :: First a #

Default (Last a) 

Methods

def :: Last a #

TypeableFloat n => Default (ArrowOpts n) 

Methods

def :: ArrowOpts n #

Default (LineTexture n) 

Methods

def :: LineTexture n #

Default (FillTexture n) 

Methods

def :: FillTexture n #

Default (StrokeOpts a) 

Methods

def :: StrokeOpts a #

Num d => Default (RoundedRectOpts d) 

Methods

def :: RoundedRectOpts d #

Num n => Default (CatOpts n) 

Methods

def :: CatOpts n #

Num n => Default (FontSizeM n) 

Methods

def :: FontSizeM n #

OrderedField n => Default (LineWidthM n) 

Methods

def :: LineWidthM n #

Default r => Default (e -> r) 

Methods

def :: e -> r #

(Default a, Default b) => Default (a, b) 

Methods

def :: (a, b) #

(Default a, Default b, Default c) => Default (a, b, c) 

Methods

def :: (a, b, c) #

(Default a, Default b, Default c, Default d) => Default (a, b, c, d) 

Methods

def :: (a, b, c, d) #

(Default a, Default b, Default c, Default d, Default e) => Default (a, b, c, d, e) 

Methods

def :: (a, b, c, d, e) #

(Default a, Default b, Default c, Default d, Default e, Default f) => Default (a, b, c, d, e, f) 

Methods

def :: (a, b, c, d, e, f) #

(Default a, Default b, Default c, Default d, Default e, Default f, Default g) => Default (a, b, c, d, e, f, g) 

Methods

def :: (a, b, c, d, e, f, g) #