amby-0.3.1: Statistical data visualization

Safe HaskellNone
LanguageHaskell2010

Amby

Contents

Synopsis

Modules

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.

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 -> Double -> 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 #

Methods

plot :: c -> c -> State PlotOpts () -> AmbyChart () Source #

plot' :: c -> c -> AmbyChart () Source #

plotEq :: c -> (Value c -> Value c) -> State PlotEqOpts () -> AmbyChart () Source #

plotEq' :: c -> (Value c -> Value c) -> AmbyChart () Source #

distPlot :: c -> State DistPlotOpts () -> AmbyChart () Source #

distPlot' :: c -> AmbyChart () Source #

kdePlot :: c -> State KdePlotOpts () -> AmbyChart () Source #

kdePlot' :: c -> AmbyChart () Source #

rugPlot :: c -> State RugPlotOpts () -> AmbyChart () Source #

rugPlot' :: c -> AmbyChart () Source #

General accessors

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 #

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 #

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 #

save :: AmbyChart () -> IO () Source #

Quick render. Short-hand to render to png file using Cairo backend.

saveSvg :: AmbyChart () -> IO () Source #

Short-hand to render to svg using Cairo backend

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.