chart-unit-0.6.3.0: Native haskell charts.

Safe HaskellNone
LanguageHaskell2010

Chart.Hud

Description

Hud (Heads up display) is a collective noun for axes, titles & legends

Synopsis

Documentation

data HudOptions Source #

Various options for a hud.

Defaults to the classical x- and y-axis, no titles and no legends

hud :: HudOptions -> Rect Double -> Rect Double -> Chart b Source #

Create a hud.

hud def sixbyfour one

withHud :: HudOptions -> Rect Double -> Rect Double -> (Rect Double -> Rect Double -> [f (Pair Double)] -> Chart b) -> [f (Pair Double)] -> Chart b Source #

attach a hud to a chart with a specific range

withHud_ :: Foldable f => HudOptions -> Rect Double -> (Rect Double -> Rect Double -> [f (Pair Double)] -> Chart b) -> [f (Pair Double)] -> Chart b Source #

attach a hud to a chart using the data range

withHudExample :: Chart b
withHudExample = withHud_ hopts sixbyfour (lineChart lopts) ls
  where
    hopts =
      #titles .~ [(def, "withHud Example")] $
      #legends .~
      [ #chartType .~ zipWith
        (\x y -> (LegendLine x 0.05, y))
        lopts
        ["line1", "line2", "line3"]
        $ def
      ] $ def

placeOutside :: Num n => Place -> V2 n Source #

Direction to place stuff on the outside of the built-up hud

placeGap :: (Monoid m, Semigroup m, Ord n, Floating n) => Place -> n -> QDiagram b V2 n m -> QDiagram b V2 n m Source #

A gap to add when placing elements.

data TickStyle Source #

Style of tick marks on an axis.

Constructors

TickNone

no ticks on axis

TickLabels [Text]

specific labels

TickRound Int

sensibly rounded ticks and a guide to how many

TickExact Int

exactly n equally spaced ticks

TickPlaced [(Double, Text)]

specific labels and placement

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

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

data AxisOptions Source #

Axes are somewhat complicated. For instance, they contain a range within which tick marks need to be supplied or computed.

Instances

Show AxisOptions Source # 
Generic AxisOptions Source # 

Associated Types

type Rep AxisOptions :: * -> * #

Default AxisOptions Source # 

Methods

def :: AxisOptions #

type Rep AxisOptions Source # 

defXAxis :: AxisOptions Source #

default X axis

defYAxis :: AxisOptions Source #

default Y axis

axis :: AxisOptions -> Range Double -> Range Double -> Chart b Source #

create an axis, based on AxisOptions, a physical aspect, and a range

Under-the-hood, the axis function has gone through many a refactor, and still has a ways to go. A high degree of technical debt tends to acrue here.

axisExample :: Chart b
axisExample = axis aopts one (Range 0 100000)
  where
    aopts :: AxisOptions
    aopts =
      #label . #text %~
      ((#rotation .~ -45) .
       (#size .~ 0.06) .
       (#alignH .~ AlignLeft)) $
      #gap .~ 0.0001 $ def

adjustAxis :: AutoOptions -> Range Double -> Range Double -> AxisOptions -> AxisOptions Source #

adjust an axis for sane font sizes etc

axisSane :: AutoOptions -> AxisOptions -> Range Double -> Range Double -> Chart b Source #

create an axis, with adjustment to axis options if needed

computeTicks :: AxisOptions -> Range Double -> Range Double -> ([Double], [Text]) Source #

compute tick values and labels given options and ranges

data TitleOptions Source #

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

Constructors

TitleOptions 

Fields

title :: Rect Double -> TitleOptions -> Text -> Chart b Source #

Create a title for 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)

data LegendType Source #

LegendType reuses all the various chart option types to help formulate a legend

Instances

Show LegendType Source # 
Generic LegendType Source # 

Associated Types

type Rep LegendType :: * -> * #

type Rep LegendType Source # 
type Rep LegendType = D1 * (MetaData "LegendType" "Chart.Hud" "chart-unit-0.6.3.0-JcgWI3NOyX2Z7zYwyCLbD" False) ((:+:) * ((:+:) * (C1 * (MetaCons "LegendText" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TextOptions))) ((:+:) * (C1 * (MetaCons "LegendGlyph" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GlyphOptions))) (C1 * (MetaCons "LegendLine" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LineOptions)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "LegendGLine" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * GlyphOptions)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * LineOptions)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double))))) (C1 * (MetaCons "LegendRect" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * RectOptions)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double))))) ((:+:) * (C1 * (MetaCons "LegendArrow" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ArrowOptions)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)))) (C1 * (MetaCons "LegendPixel" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * RectOptions)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Double)))))))

data LegendOptions Source #

Legend options. todo: allow for horizontal concatenation.

Instances

Show LegendOptions Source # 
Generic LegendOptions Source # 

Associated Types

type Rep LegendOptions :: * -> * #

Default LegendOptions Source # 

Methods

def :: LegendOptions #

type Rep LegendOptions Source # 

legend :: LegendOptions -> Chart b Source #

Create a legend based on a LegendOptions

legends' :: [(LegendType, Text)]
legends' =
  [(LegendText def, "legend")] <> [(LegendPixel (blob ublue) 0.05, "pixel")] <>
    -- [ (LegendArrow (def & #minStaffWidth .~ 0.01 & #minHeadLength .~ 0.03) 0.05, "arrow")] <>
  [(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"]

legendExample :: Chart b
legendExample = legend $ #chartType .~ legends' $ def

data GridStyle Source #

Style of grid lines

Constructors

GridNone

no ticks on axis

GridRound GridPos Int

sensibly rounded line placement and a guide to how many

GridExact GridPos Int

exactly n lines using Pos

GridPlaced [Double]

specific line placement

data GridPos Source #

The positioning of boundaries for a grid over a space

Instances

Eq GridPos Source # 

Methods

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

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

Show GridPos Source # 
Generic GridPos Source # 

Associated Types

type Rep GridPos :: * -> * #

Methods

from :: GridPos -> Rep GridPos x #

to :: Rep GridPos x -> GridPos #

type Rep GridPos Source # 
type Rep GridPos = D1 * (MetaData "GridPos" "Chart.Hud" "chart-unit-0.6.3.0-JcgWI3NOyX2Z7zYwyCLbD" False) ((:+:) * ((:+:) * (C1 * (MetaCons "GridOuterPos" PrefixI False) (U1 *)) (C1 * (MetaCons "GridInnerPos" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "GridLowerPos" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "GridUpperPos" PrefixI False) (U1 *)) (C1 * (MetaCons "GridMidPos" PrefixI False) (U1 *)))))

gridPos :: GridPos -> Pos Source #

conversion from a chart-unit GridPos to a numhask-range Pos

defXGrid :: GridOptions Source #

default horizontal grid

defYGrid :: GridOptions Source #

default vertical grid

gridl :: GridOptions -> Rect Double -> Rect Double -> Chart b Source #

Create a grid line for a chart.