amby-0.3.2: Statistical data visualization

Safe HaskellNone
LanguageHaskell2010

Amby

Contents

Synopsis

Modules

Types

Methods

toCat :: (Foldable f, Eq a, Show a) => f a -> Category Source #

Convert Foldable into a Category.

toCatOrdered :: (Foldable f, Eq a, Show a) => f a -> f a -> Category Source #

getCategoryLabels :: Category -> [String] Source #

Get list of category labels in order.

catSize :: Category -> Int Source #

Find number of distinct elements in a category.

Examples:

>>> catSize $ toCat ["dog", "cat", "dog"]
2

catValsLength :: Category -> Int Source #

Find the number of elements in a category.

filterMask :: [a] -> [Bool] -> [a] Source #

Filter list based on another equal sized list of bools.

Examples:

>>> filterMask [1..5] [True, False, True, False, False]
[1,3]

groupByCategory :: [a] -> Category -> [[a]] Source #

Group by category.

Examples:

>>> groupByCategory [1..5] (toCat [1, 1, 3, 2, 4])
[[1,2],[3],[4],[5]]

groupCategoryBy :: Category -> Category -> Category Source #

Group category internally

data AmbyColor Source #

Api facing color selection.

Constructors

DefaultColor 
R 
G 
B 
C 
M 
Y 
K 
W 
CustomColor (AlphaColour Double) 

Themes

Lenses

bgColor :: HasBgColor s a => Lens' s a Source #

plotBgColor :: HasPlotBgColor s a => Lens' s a Source #

gridLineColor :: HasGridLineColor s a => Lens' s a Source #

colorCycle :: HasColorCycle s a => Lens' s a Source #

fontFamily :: HasFontFamily s a => Lens' s a Source #

fontSize :: HasFontSize s a => Lens' s a Source #

Color helpers

toColour :: AmbyColor -> AlphaColour Double -> AlphaColour Double Source #

Conversion from Amby Api Color to underlying Colour type.

huslPalette :: Int -> Maybe Double -> Maybe Double -> Maybe Double -> Palette Source #

Get a set of evenly spaced colors in the HUSL space.

lightPalette :: AlphaColour Double -> Int -> Palette Source #

Get sequential palette of colors from light to dark

desaturate :: Double -> AlphaColour Double -> AlphaColour Double Source #

Desaturate color by a proporation.

alphaToHsl :: AlphaColour Double -> (Double, Double, Double) Source #

Converts 'AlphaColour Double' to triplet of Doubles in hsl encoding.

Examples:

>>> import qualified Data.Colour.Names as Colour
>>> alphaToHsl (opaque Colour.black)
(0.0,0.0,0.0)
>>> alphaToHsl (opaque Colour.blue)
(240.0,1.0,0.5)

hslToAlpha :: Double -> Double -> Double -> AlphaColour Double Source #

Converts hsl triplet of Doubles to 'AlphaColour Double'.

Ranges

contDistrDomain :: ContDistr d => d -> Int -> Vector Double Source #

contDistrDomain d n generates a domain of n evenly spaced points for the continuous distribution d.

contDistrRange :: ContDistr d => d -> Vector Double -> Vector Double Source #

contDistrRange d xs generates the pdf value of the continious distribution d for each value in xs.

linspace :: Double -> Double -> Int -> Vector Double Source #

linspace s e n generates n evenly spaced values between [s, e].

arange :: Double -> Double -> Double -> Vector Double Source #

arange s e i generates numbers between [s, e] spaced by amount i. arange is the equivalent of haskell's range notation except that it generates a Vector. As a result, the last element may be greater than less than, or greater than the stop point.

random :: ContGen d => d -> Int -> IO (Vector Double) Source #

Generates an unboxed vectors of random numbers from a distribution that is an instance of ContGen. This function is meant for ease of use and is expensive.

Frequencies

scoreAtPercentile :: Vector v Double => v Double -> Int -> Double Source #

scoreAtPercentile xs p calculates the score at percentile p.

Examples:

>>> let a = arange 0 99 1
>>> scoreAtPercentile a 50
49.5

interquartileRange :: Vector v Double => v Double -> Double Source #

Calculate the interquartile range.

Examples:

>>> interquartileRange demoData
2.5

freedmanDiaconisBins :: Vector v Double => v Double -> Int Source #

Estimate a good default bin size.

Examples:

>>> freedmanDiaconisBins demoData
2

class AmbyContainer c where Source #

Associated Types

type Value c :: * Source #

data AmbyState Source #

Instances

Default AmbyState Source # 

Methods

def :: AmbyState #

Saveable (AmbyChart ()) Source # 

Methods

toSaveObject :: AmbyChart () -> SaveObject Source #

type AmbyGrid a = State AmbyGridState a Source #

class Saveable a where Source #

Minimal complete definition

toSaveObject

Methods

toSaveObject :: a -> SaveObject Source #

Instances

Saveable (AmbyGrid ()) Source # 

Methods

toSaveObject :: AmbyGrid () -> SaveObject Source #

Saveable (AmbyChart ()) Source # 

Methods

toSaveObject :: AmbyChart () -> SaveObject Source #

General accessors

getSize :: SaveObject -> (Int, Int) Source #

Grid

gridScale :: (Double, Double) -> AmbyGrid () Source #

Scale current grid size by percentage. Scaling will snap to nearest integer point.

Plot options

data Axis Source #

Constructors

XAxis 
YAxis 

Instances

Eq Axis Source # 

Methods

(==) :: Axis -> Axis -> Bool #

(/=) :: Axis -> Axis -> Bool #

Show Axis Source # 

Methods

showsPrec :: Int -> Axis -> ShowS #

show :: Axis -> String #

showList :: [Axis] -> ShowS #

data PlotKind Source #

Constructors

Box 

bins :: HasBins s a => Lens' s a Source #

hist :: HasHist s a => Lens' s a Source #

rug :: HasRug s a => Lens' s a Source #

rugHeight :: HasRugHeight s a => Lens' s a Source #

cut :: HasCut s a => Lens' s a Source #

shade :: HasShade s a => Lens' s a Source #

kde :: HasKde s a => Lens' s a Source #

axis :: HasAxis s a => Lens' s a Source #

height :: HasHeight s a => Lens' s a Source #

gridsize :: HasGridsize s a => Lens' s a Source #

bw :: HasBw s a => Lens' s a Source #

color :: HasColor s a => Lens' s a Source #

linewidth :: HasLinewidth s a => Lens' s a Source #

histLinewidth :: HasHistLinewidth s a => Lens' s a Source #

kdeLinewidth :: HasKdeLinewidth s a => Lens' s a Source #

rugLinewidth :: HasRugLinewidth s a => Lens' s a Source #

kind :: HasKind s a => Lens' s a Source #

hueLegend :: HasHueLegend s a => Lens' s a Source #

facLegend :: HasFacLegend s a => Lens' s a Source #

Categorical options

fac :: HasFac s a b => Setter s s a b Source #

hue :: HasHue s a b => Setter s s a b Source #

row :: HasRow s a b => Setter s s a b Source #

col :: HasCol s a b => Setter s s a b Source #

saturation :: HasSaturation s a => Lens' s a Source #

facL :: HasFacL s a => Lens' s a Source #

hueL :: HasHueL s a => Lens' s a Source #

rowL :: HasRowL s a => Lens' s a Source #

colL :: HasColL s a => Lens' s a Source #

datLabel :: HasDatLabel s a => Lens' s a Source #

facLabel :: HasFacLabel s a => Lens' s a Source #

rowLabel :: HasRowLabel s a => Lens' s a Source #

colLabel :: HasColLabel s a => Lens' s a Source #

getEC :: AmbyChart () -> EC (Layout Double Double) () Source #

Convert AmbyChart into Chart's 'EC (Layout Double Double) ()'.

getRenderable :: AmbyChart () -> Renderable (LayoutPick Double Double Double) Source #

Convert AmbyGrid into Chart's 'Renderable a'.

save :: Saveable s => s -> IO () Source #

saveSvg :: Saveable s => s -> IO () Source #

Short-hand to render to svg using Cairo backend

cairoDefSave :: FilePath Source #

Default save filename for Cairo.

diagramsDefSave :: FilePath Source #

Default save filename for Diagrams.

getCol :: Loader a => Lens (RowValue a) (RowValue a) b b -> a -> b Source #

Datasets

data Tip Source #

Tip lenses

totalBill :: HasTotalBill s a => Lens' s a Source #

tip :: HasTip s a => Lens' s a Source #

sex :: HasSex s a => Lens' s a Source #

day :: HasDay s a => Lens' s a Source #

smoker :: HasSmoker s a => Lens' s a Source #

time :: HasTime s a => Lens' s a Source #

tipSize :: HasTipSize s a => Lens' s a Source #

Iris lenses

sepalLength :: HasSepalLength s a => Lens' s a Source #

sepalWidth :: HasSepalWidth s a => Lens' s a Source #

petalLength :: HasPetalLength s a => Lens' s a Source #

petalWidth :: HasPetalWidth s a => Lens' s a Source #

irisClass :: HasIrisClass s a => Lens' s a Source #

Lens operators

(.=) :: MonadState s m => ASetter s s a b -> b -> m () infix 4 #

Replace the target of a Lens or all of the targets of a Setter or Traversal in our monadic state with a new value, irrespective of the old.

This is an infix version of assign.

>>> execState (do _1 .= c; _2 .= d) (a,b)
(c,d)
>>> execState (both .= c) (a,b)
(c,c)
(.=) :: MonadState s m => Iso' s a       -> a -> m ()
(.=) :: MonadState s m => Lens' s a      -> a -> m ()
(.=) :: MonadState s m => Traversal' s a -> a -> m ()
(.=) :: MonadState s m => Setter' s a    -> a -> m ()

It puts the state in the monad or it gets the hose again.