chart-unit-0.6.2.0: Native haskell charts.

Safe HaskellNone
LanguageHaskell2010

Chart.Glyph

Description

Glyphs are (typically) small shapes symbolically representing a data point.

Synopsis

Documentation

glyphShape :: GlyphShape -> Double -> Chart b Source #

convert from chart-unit to diagrams shapes

glyph_ :: GlyphOptions -> Chart b Source #

Create a glyph.

glyph_ def

glyphs :: (R2 r, Traversable f) => GlyphOptions -> f (r Double) -> Chart b Source #

Create positioned glyphs.

glyphs def (dataXY sin (Range 0 (2*pi)) 30)

lglyphs :: (R2 r, Traversable f) => LabelOptions -> GlyphOptions -> f (Text, r Double) -> Chart b Source #

Create labelled, positioned glyphs.

lglyphsExample :: Chart b
lglyphsExample =
  lglyphs def def $
  zip (show <$> [0 ..]) [Pair (x / 10) (sin x / 10) | x <- [0 .. 10]]

glyphChart :: Traversable f => [GlyphOptions] -> Rect Double -> Rect Double -> [f (Pair Double)] -> Chart b Source #

A chart of glyphs

glyphChart_ :: Traversable f => [GlyphOptions] -> Rect Double -> [f (Pair Double)] -> Chart b Source #

A chart of glyphs scaled to its own range

gopts :: [GlyphOptions]
gopts =
  [ #borderSize .~ 0.001 $ def
  , #borderSize .~ 0.001 $
    #size .~ 0.1 $
    #color .~ rybColor 7 `withOpacity` 0.4 $
    #shape .~ Triangle $ def
  ]

gdata :: [[Pair Double]]
gdata =
  [ dataXY sin (Range 0 (2*pi)) 30
  , dataXY cos (Range 0 (2*pi)) 30
  ]

glyphChart_Example :: Chart b
glyphChart_Example = glyphChart_ gopts widescreen gdata

lglyphChart :: Traversable f => [LabelOptions] -> [GlyphOptions] -> Rect Double -> Rect Double -> [f (Text, Pair Double)] -> Chart b Source #

A chart of labelled glyphs

lglyphChart_ :: Traversable f => [LabelOptions] -> [GlyphOptions] -> Rect Double -> [f (Text, Pair Double)] -> Chart b Source #

A chart of labelled glyphs scaled to its own range

lgdata :: [(Text, Pair Double)]
lgdata =
  [(\(p@(Pair x y)) -> (show x <> "," <> show y, fromIntegral <$> p)) <$>
    (Pair <$> [0 .. 5] <*> [0 .. 5] :: [Pair Int])
  ]

lglyphChart_Example :: Rect Double -> Chart b
lglyphChart_Example a =
  lglyphChart_
  [#gap .~ 0.015 $ #text . #size .~ 0.12 $ def]
  [#color .~ black `withOpacity` 1 $
   #borderSize .~ 0 $
   #size .~ 0.01 $
   def]
  a
  [lgdata]