chart-unit-0.5.4: Native haskell charts.

Safe HaskellNone
LanguageHaskell2010

Chart.Glyph

Description

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

Synopsis

Documentation

data GlyphOptions b Source #

The actual shape of a glyph can be any Chart element

Instances

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

Horizontal line glyph shape with a reasonable thickness as "hline_ 1"

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

Vertical line glyph shape with a reasonable thickness at "vline_ 1"

glyph_ :: GlyphOptions b -> Chart b Source #

Create a glyph.

let glyph_Example = glyph_ def

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

Create positioned glyphs.

glyphsExample :: Chart b
glyphsExample = glyphs def (dataXY sin (Range 0 (2*pi)) 30)

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

Create labelled, positioned glyphs.

lglyphs def def $ zip (show <$> [0..]) ps

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

A chart of glyphs

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

A chart of glyphs scaled to its own range

gopts :: [GlyphOptions b]
gopts = [ glyphBorderSize_ .~ 0.001 $ def
        , glyphBorderSize_ .~ 0.001 $
          glyphSize_ .~ 0.1 $
          glyphColor_ .~ rybColor 7 `withOpacity` 0.4 $
          def {glyphShape = triangle}
        ]

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 b] -> Aspect -> Rect Double -> [f (Text, Pair Double)] -> Chart b Source #

A chart of labelled glyphs

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

A chart of labelled glyphs scaled to its own range

let g = Pair <$> [0..5] <*> [0..5] :: [Pair Int]
let xs = [(\(p@(Pair x y)) -> ((show x <> "," <> show y), fromIntegral <$> p)) <$> g]
lglyphChart_ [def {labelGap=0.01}] [def] sixbyfour xs

circle :: (TrailLike t, (~) (* -> *) (V t) V2, (~) * (N t) n, Transformable t) => n -> t #

A circle of the given radius, centered at the origin. As a path, it begins at (r,0).

square :: (InSpace V2 n t, TrailLike t) => n -> t #

A square with its center at the origin and sides of the given length, oriented parallel to the axes.

triangle :: (InSpace V2 n t, TrailLike t) => n -> t #

An equilateral triangle, with sides of the given length and base parallel to the x-axis.