| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Chart.Glyph
Description
Glyphs are (typically) small shapes symbolically representing a data point.
- data GlyphOptions = GlyphOptions {
- size :: Double
- color :: UColor Double
- borderColor :: UColor Double
- borderSize :: Double
- shape :: GlyphShape
- data GlyphShape
- glyphShape :: GlyphShape -> Double -> Chart b
- glyph_ :: GlyphOptions -> Chart b
- glyphs :: (R2 r, Traversable f) => GlyphOptions -> f (r Double) -> Chart b
- lglyphs :: (R2 r, Traversable f) => LabelOptions -> GlyphOptions -> f (Text, r Double) -> Chart b
- glyphChart :: Traversable f => [GlyphOptions] -> Rect Double -> Rect Double -> [f (Pair Double)] -> Chart b
- glyphChart_ :: Traversable f => [GlyphOptions] -> Rect Double -> [f (Pair Double)] -> Chart b
- lglyphChart :: Traversable f => [LabelOptions] -> [GlyphOptions] -> Rect Double -> Rect Double -> [f (Text, Pair Double)] -> Chart b
- lglyphChart_ :: Traversable f => [LabelOptions] -> [GlyphOptions] -> Rect Double -> [f (Text, Pair Double)] -> Chart b
Documentation
data GlyphOptions Source #
The actual shape of a glyph can be any Chart element
Constructors
| GlyphOptions | |
Fields
| |
Instances
data GlyphShape Source #
shape of the glyph expressed in diagrams terms
Constructors
| Circle | |
| Square | |
| Ellipse Double | |
| Triangle | |
| Pentagon | |
| Hexagon | |
| Septagon | |
| Octagaon | |
| RectSharp Double | |
| RectRounded Double Double | |
| VLine Double | |
| HLine Double |
Instances
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 gdatalglyphChart :: 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]