| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Chart.Rect
Description
rectangular chart elements
- data RectOptions = RectOptions {}
- blob :: AlphaColour Double -> RectOptions
- box :: AlphaColour Double -> RectOptions
- clear :: RectOptions
- bound :: RectOptions -> Double -> Chart b -> Chart b
- rect_ :: (N b ~ Double, V b ~ V2, Transformable b, HasOrigin b, TrailLike b, HasStyle b) => RectOptions -> Rect Double -> b
- rects :: (V a ~ V2, N a ~ Double, Functor t, HasStyle a, TrailLike a, HasOrigin a, Transformable a, Foldable t, Monoid a) => RectOptions -> t (Rect Double) -> a
- rectChart :: Traversable f => [RectOptions] -> Aspect -> Rect Double -> [f (Rect Double)] -> Chart b
- rectChart_ :: Traversable f => [RectOptions] -> Aspect -> [f (Rect Double)] -> Chart b
- data Pixel = Pixel {}
- pixel_ :: Pixel -> Chart b
- pixels :: Traversable f => f Pixel -> Chart b
- pixelChart :: Traversable f => Aspect -> Rect Double -> [f Pixel] -> Chart b
- pixelChart_ :: Traversable f => Aspect -> [f Pixel] -> Chart b
- data PixelationOptions = PixelationOptions {}
- pixelate :: PixelationOptions -> Rect Double -> (Pair Double -> Double) -> [Pixel]
- pixelateChart :: PixelationOptions -> Aspect -> Rect Double -> (Pair Double -> Double) -> Chart b
Documentation
data RectOptions Source #
Just about everything on a chart is a rectangle.
Constructors
| RectOptions | |
Fields | |
Instances
blob :: AlphaColour Double -> RectOptions Source #
solid rectangle, no border
box :: AlphaColour Double -> RectOptions Source #
clear rect, with border
clear :: RectOptions Source #
clear and transparent rect
bound :: RectOptions -> Double -> Chart b -> Chart b Source #
place a rect around an Chart, with a size equal to the chart range
rect_ :: (N b ~ Double, V b ~ V2, Transformable b, HasOrigin b, TrailLike b, HasStyle b) => RectOptions -> Rect Double -> b Source #
A single rectangle specified using a Rect x z y w where (x,y) is location of lower left corner (z,w) is location of upper right corner
let opts o = def {labelText = (labelText def) {textColor=withOpacity black 0.8,
textSize = 0.3}, labelOrientation=o}
labelled (opts (Pair 2 1)) ("z,w") $ labelled (opts (Pair -2 -1)) ("x,y")
(rect_ def (Ranges (2*.one) one))rects :: (V a ~ V2, N a ~ Double, Functor t, HasStyle a, TrailLike a, HasOrigin a, Transformable a, Foldable t, Monoid a) => RectOptions -> t (Rect Double) -> a Source #
Create rectangles (with the same configuration).
rects def $ zipWith (\x y -> Rect x (x+1) 0 y) [0..] [1,2,3,5,8,0,-2,11,2,1]
rectChart :: Traversable f => [RectOptions] -> Aspect -> Rect Double -> [f (Rect Double)] -> Chart b Source #
A chart of rects
rectChart_ :: Traversable f => [RectOptions] -> Aspect -> [f (Rect Double)] -> Chart b Source #
A chart of rectangles scaled to its own range
let ropts = [def {rectBorderSize=0}, def
{rectBorderSize=0,rectColor=ucolor 0.3 0.3 0.3 0.2}]
let pss = transpose [[exp (-(x**2)/2), 0.5 * exp (-(x**2)/8)] |
x <- grid LowerPos (Range -5 5) 1000]
let rss = (zipWith (\x y -> Rect x (x+1) 0 y) [0..]) <$> pss
rectChart_ ropts widescreen rssAt some point, a color of a rect becomes more about data than stylistic option, hence the pixel. Echewing rect border leaves a Pixel with no stylistic options to choose.
Constructors
| Pixel | |
Fields | |
pixel_ :: Pixel -> Chart b Source #
A pixel is a rectangle with a color.
let opt = def {textColor=withOpacity black 0.8, textSize = 0.2}
text_ opt "I'm a pixel!" <> pixel_ (Pixel one ublue)pixels :: Traversable f => f Pixel -> Chart b Source #
Render multiple pixels
pixels $ [Pixel (Rect (5*x) (5*x+0.1) (sin (10*x)) (sin (10*x) + 0.1)) (dissolve (2*x) ublue) | x <- grid OuterPos (Range 0 1) 100]
pixelChart :: Traversable f => Aspect -> Rect Double -> [f Pixel] -> Chart b Source #
A chart of pixels
pixelChart_ :: Traversable f => Aspect -> [f Pixel] -> Chart b Source #
A chart of pixels scaled to its own range
pixelChart_ asquare [[Pixel (Rect x (x+0.05) y (y+0.05)) (blend (x*y+x*x) ugrey ublue)
| x <- grid OuterPos (one::Range Double) 20,
y <- grid OuterPos (one::Range Double) 20]]data PixelationOptions Source #
Options to pixelate a Rect using a function
Constructors
| PixelationOptions | |
Fields | |
Instances