| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Chart.Line
Description
Points on a chart connected by lines.
- data LineOptions = LineOptions {}
 - oneline :: R2 r => LineOptions -> Pair (r Double) -> Chart b
 - lines :: (Traversable f, R2 r) => LineOptions -> f (r Double) -> Chart b
 - glines :: (Traversable f, R2 r) => LineOptions -> GlyphOptions -> f (r Double) -> Chart b
 - lineChart :: Traversable f => [LineOptions] -> Rect Double -> Rect Double -> [f (Pair Double)] -> Chart b
 - lineChart_ :: Traversable f => [LineOptions] -> Rect Double -> [f (Pair Double)] -> Chart b
 - glineChart :: Traversable f => [LineOptions] -> [GlyphOptions] -> Rect Double -> Rect Double -> [f (Pair Double)] -> Chart b
 - glineChart_ :: Traversable f => [LineOptions] -> [GlyphOptions] -> Rect Double -> [f (Pair Double)] -> Chart b
 
Documentation
data LineOptions Source #
The main features of a line (that distinguish it from a glyph say) is that:
- it exists over multiple points (a line can't exist at a single point)
 - line rendering is normalized to the eventual physical chart
 
Instances
oneline :: R2 r => LineOptions -> Pair (r Double) -> Chart b Source #
A single line connecting 2 points
lines :: (Traversable f, R2 r) => LineOptions -> f (r Double) -> Chart b Source #
A line connecting a series of points
linesExample :: Int -> Chart b linesExample n = lines (#color .~ red `withOpacity` 0.5 $ def) (dataXY cos (Range 0 (4*pi)) n)
glines :: (Traversable f, R2 r) => LineOptions -> GlyphOptions -> f (r Double) -> Chart b Source #
Lines with glyphs atop eack point
lineChart :: Traversable f => [LineOptions] -> Rect Double -> Rect Double -> [f (Pair Double)] -> Chart b Source #
A chart of lines
lineChart_ :: Traversable f => [LineOptions] -> Rect Double -> [f (Pair Double)] -> Chart b Source #
A chart of lines scaled to its own range
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)] ] lopts :: [LineOptions] lopts = zipWith (\x y -> LineOptions x (withOpacity (d3Colors1 y) 0.6)) [0.01, 0.02, 0.005] [0,1,2] lineChart_Example :: Chart b lineChart_Example = lineChart_ lopts sixbyfour ls
glineChart :: Traversable f => [LineOptions] -> [GlyphOptions] -> Rect Double -> Rect Double -> [f (Pair Double)] -> Chart b Source #
A chart of glines
glineChart_ :: Traversable f => [LineOptions] -> [GlyphOptions] -> Rect Double -> [f (Pair Double)] -> Chart b Source #
A chart of glyphs_lines scaled to its own range
gopts3 :: [GlyphOptions]
gopts3 =
  zipWith
  (\x y ->
     #color .~ withOpacity (d3Colors1 x) 0.2 $
     #borderColor .~ withOpacity (d3Colors1 x) 1 $
     #borderSize .~ 0.005 $
     #shape .~ y $
     #size .~ 0.08 $
     def)
  [6,8,2]
  [Triangle, Square, Circle]
glineChart_Example :: Chart b
glineChart_Example = glineChart_ lopts gopts3 sixbyfour ls