interactive-plot-0.1.0.0: Interactive quick time series plotting

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Interactive.Plot.Series

Contents

Description

Create common serieses.

Synopsis

Documentation

type Series = SeriesF Identity Source #

Data for a single series: contains the coordinate map with the point style for the series.

type AutoSeries = SeriesF Auto Source #

A version of SeriesF where you can leave the marker or color blank, to be automatically inferred.

data SeriesF f Source #

A parameterized version of SeriesF to unify functions in Interactive.Plot.Series.

Mainly you will be using either SeriesF or AutoSeries.

Constructors

Series 

Fields

Instances
(Show (f Char), Show (f Color)) => Show (SeriesF f) Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

showsPrec :: Int -> SeriesF f -> ShowS #

show :: SeriesF f -> String #

showList :: [SeriesF f] -> ShowS #

type PointStyle = PointStyleF Identity Source #

Specification of a style for a point.

Construct this wiht the PointStyle pattern synonym.

type AutoPointStyle = PointStyleF Auto Source #

A version of PointStyle where you can leave the marker or color blank, to be automatically inferred.

You can construct this with the PointStyleF constructor.

It has a very convenient Monoid instance: mempty gives a PointStyle where every field is Auto, and <> combines PointStyles field-by-field, keeping the last Given.

data PointStyleF f Source #

A parameterized version of PointStyle to unify functions in Interactive.Plot.Series.

Mainly you will be using either PointStyle or AutoPointStyle.

Constructors

PointStyleF 

Fields

Instances
(Eq (f Char), Eq (f Color)) => Eq (PointStyleF f) Source # 
Instance details

Defined in Interactive.Plot.Core

(Ord (f Char), Ord (f OrdColor), Functor f, Eq (f Color)) => Ord (PointStyleF f) Source # 
Instance details

Defined in Interactive.Plot.Core

(Show (f Char), Show (f Color)) => Show (PointStyleF f) Source # 
Instance details

Defined in Interactive.Plot.Core

Generic (PointStyleF f) Source # 
Instance details

Defined in Interactive.Plot.Core

Associated Types

type Rep (PointStyleF f) :: Type -> Type #

Methods

from :: PointStyleF f -> Rep (PointStyleF f) x #

to :: Rep (PointStyleF f) x -> PointStyleF f #

(Semigroup (f Char), Semigroup (f Color)) => Semigroup (PointStyleF f) Source # 
Instance details

Defined in Interactive.Plot.Core

(Monoid (f Char), Monoid (f Color)) => Monoid (PointStyleF f) Source # 
Instance details

Defined in Interactive.Plot.Core

type Rep (PointStyleF f) Source # 
Instance details

Defined in Interactive.Plot.Core

type Rep (PointStyleF f) = D1 (MetaData "PointStyleF" "Interactive.Plot.Core" "interactive-plot-0.1.0.0-3hlWKkOzuXtEUcnz41zcbZ" False) (C1 (MetaCons "PointStyleF" PrefixI True) (S1 (MetaSel (Just "_psMarkerF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f Char)) :*: S1 (MetaSel (Just "_psColorF") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f Color))))

Create common SeriesF

listSeries :: Foldable t => t Double -> PointStyleF f -> SeriesF f Source #

Construct a series from any foldable container of y-values. The x-values are automatically assigned to 0, 1, 2, 3 ... etc.

Note that this is polymorphic over both PointStyle and AutoPointStyle:

listSeries :: Foldable t => t Double -> PointStyle -> SeriesF
listSeries :: Foldable t => t Double -> AutoPointStyle -> AutoSeries

tupleSeries :: Foldable t => t (Double, Double) -> PointStyleF f -> SeriesF f Source #

Construct a series from any foldable container of x-y tuples.

Note that this is polymorphic over both PointStyle and AutoPointStyle:

tupleSeries :: Foldable t => t (Double, Double) -> PointStyle -> SeriesF
tupleSeries :: Foldable t => t (Double, Double) -> AutoPointStyle -> AutoSeries

funcSeries :: Foldable t => (Double -> Double) -> t Double -> PointStyleF f -> SeriesF f Source #

Construct a series from a function x to y, given a foldable container of x values.

Note that this is polymorphic over both PointStyle and AutoPointStyle:

funcSeries :: Foldable t => (Double -> Double) -> t Double -> PointStyle -> SeriesF
funcSeries :: Foldable t => (Double -> Double) -> t Double -> AutoPointStyle -> AutoSeries

enumRange Source #

Arguments

:: Fractional a 
=> Int

Number of points

-> Range a

Range to generate the points over

-> [a] 

enumRange n (R a b) generates a list of n equally spaced values between a and b.

Create a SeriesF from an AutoSeries.

fromAutoSeries :: [AutoSeries] -> [Series] Source #

Turn an AutoSeries into a SeriesF, assigning styles from a pre-specified "shuffled" order.

fromAutoSeriesIO :: [AutoSeries] -> IO [Series] Source #

Turn an AutoSeries into a SeriesF, drawing styles randomly in IO.

fromAutoSeries_ :: StdGen -> [AutoSeries] -> [Series] Source #

Turn an AutoSeries into a SeriesF, shuffling the default styles in a deterministic way from a given seed.

defaultStyles :: Set PointStyle Source #

A set of default point styles