chart-unit-0.5.3: Native haskell charts.

Safe HaskellNone
LanguageHaskell2010

Chart.Rect

Description

rectangular chart elements

Synopsis

Documentation

data RectOptions Source #

Just about everything on a chart is a rectangle.

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 (rectOneD [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 rss = [ rectXY (\x -> exp (-(x ** 2) / 2)) (Range -5 5) 50
          , rectXY (\x -> 0.5 * exp (-(x ** 2) / 8)) (Range -5 5) 50
          ]
rectChart_ ropts widescreen rss

data Pixel Source #

At 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 

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_Example :: Chart b
pixelChart_Example =
    pixelChart_ asquare
    [ (\(r,c) -> Pixel r
                (blend c
                 (rybColor 14 `withOpacity` 1)
                 (ucolor 0.8 0.8 0.8 0.3))) <$>
      rectF (\(Pair x y) -> 4*(x*x+y*y))
      one (Pair 40 40)
    ]

data PixelationOptions Source #

Options to pixelate a Rect using a function

pixelate :: PixelationOptions -> Rect Double -> (Pair Double -> Double) -> [Pixel] Source #

Transform a Rect into Pixels using a function over a Pair

pixelateChart :: PixelationOptions -> Aspect -> Rect Double -> (Pair Double -> Double) -> Chart b Source #

Chart pixels using a function This is a convenience function, and the example below is equivalent to the pixelChart_ example

pixelateChart def asquare one (\(Pair x y) -> (x+y)*(x+y))