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

Contents

Description

Simple interactive rendering of plots. See README for information on usage.

The main way to use this library is to use runPlotAuto or runPlot on some series you make using the series constructors (listSeries, funcSeries, etc.)

Synopsis

Construct Series

data Auto a Source #

Used to specify fields in PointStyle and SeriesF: Use Auto for automatic inference, and Given to provide a specific value.

Its Semigroup instance keeps the last Given.

Constructors

Auto 
Given a 
Instances
Monad Auto Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

(>>=) :: Auto a -> (a -> Auto b) -> Auto b #

(>>) :: Auto a -> Auto b -> Auto b #

return :: a -> Auto a #

fail :: String -> Auto a #

Functor Auto Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

fmap :: (a -> b) -> Auto a -> Auto b #

(<$) :: a -> Auto b -> Auto a #

Applicative Auto Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

pure :: a -> Auto a #

(<*>) :: Auto (a -> b) -> Auto a -> Auto b #

liftA2 :: (a -> b -> c) -> Auto a -> Auto b -> Auto c #

(*>) :: Auto a -> Auto b -> Auto b #

(<*) :: Auto a -> Auto b -> Auto a #

MonadPlus Auto Source #

Opposite behavior of Semigroup instance: like Maybes Alternative instance, or First.

Instance details

Defined in Interactive.Plot.Core

Methods

mzero :: Auto a #

mplus :: Auto a -> Auto a -> Auto a #

Alternative Auto Source #

Opposite behavior of Semigroup instance: like Maybes Alternative instance, or First.

Instance details

Defined in Interactive.Plot.Core

Methods

empty :: Auto a #

(<|>) :: Auto a -> Auto a -> Auto a #

some :: Auto a -> Auto [a] #

many :: Auto a -> Auto [a] #

Eq a => Eq (Auto a) Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

(==) :: Auto a -> Auto a -> Bool #

(/=) :: Auto a -> Auto a -> Bool #

Ord a => Ord (Auto a) Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

compare :: Auto a -> Auto a -> Ordering #

(<) :: Auto a -> Auto a -> Bool #

(<=) :: Auto a -> Auto a -> Bool #

(>) :: Auto a -> Auto a -> Bool #

(>=) :: Auto a -> Auto a -> Bool #

max :: Auto a -> Auto a -> Auto a #

min :: Auto a -> Auto a -> Auto a #

Show a => Show (Auto a) Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

showsPrec :: Int -> Auto a -> ShowS #

show :: Auto a -> String #

showList :: [Auto a] -> ShowS #

Generic (Auto a) Source # 
Instance details

Defined in Interactive.Plot.Core

Associated Types

type Rep (Auto a) :: Type -> Type #

Methods

from :: Auto a -> Rep (Auto a) x #

to :: Rep (Auto a) x -> Auto a #

Semigroup (Auto a) Source #

Keeps the final Given: like Last

Instance details

Defined in Interactive.Plot.Core

Methods

(<>) :: Auto a -> Auto a -> Auto a #

sconcat :: NonEmpty (Auto a) -> Auto a #

stimes :: Integral b => b -> Auto a -> Auto a #

Monoid (Auto a) Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

mempty :: Auto a #

mappend :: Auto a -> Auto a -> Auto a #

mconcat :: [Auto a] -> Auto a #

type Rep (Auto a) Source # 
Instance details

Defined in Interactive.Plot.Core

type Rep (Auto a) = D1 (MetaData "Auto" "Interactive.Plot.Core" "interactive-plot-0.1.0.0-3hlWKkOzuXtEUcnz41zcbZ" False) (C1 (MetaCons "Auto" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Given" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

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 #

sItems :: Lens' (SeriesF f) (Map Double (Set Double)) Source #

Getter/setter lens to the items field of a SeriesF

sStyle :: Lens' (SeriesF f) (PointStyleF f) Source #

Getter/setter lens to the style field of a SeriesF

sStyle :: Lens SeriesF PointStyle
sStyle :: Lens AutoSeries AutoPointStyle

Making common serieses

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.

toCoordMap :: Eq a => Set (Coord a) -> Map a (Set a) Source #

Turn a set of coordinates into a map of x's to the y's found in the set.

Note that this forms an isomorphism with fromCoordMap.

fromCoordMap :: Map a (Set a) -> Set (Coord a) Source #

Convert a map of x's to y's into a set of x-y coordinates.

Note that this forms an isomorphism with toCoordMap.

Series from AutoSeroes

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.

Types

type PointStyle = PointStyleF Identity Source #

Specification of a style for a point.

Construct this wiht the PointStyle pattern synonym.

pattern PointStyle :: Char -> Color -> PointStyle Source #

Pattern synonym/constructor for PointStyle.

This comes with two record fields, _psMarker and _psColor.

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))))

data Coord a Source #

An ordered pair in a.

Constructors

C 

Fields

  • _cX :: a

    Access x.

  • _cY :: a

    Access y.

Instances
Monad Coord Source #

Basically the same as Reader Bool, for x and y.

Instance details

Defined in Interactive.Plot.Core

Methods

(>>=) :: Coord a -> (a -> Coord b) -> Coord b #

(>>) :: Coord a -> Coord b -> Coord b #

return :: a -> Coord a #

fail :: String -> Coord a #

Functor Coord Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

fmap :: (a -> b) -> Coord a -> Coord b #

(<$) :: a -> Coord b -> Coord a #

Applicative Coord Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

pure :: a -> Coord a #

(<*>) :: Coord (a -> b) -> Coord a -> Coord b #

liftA2 :: (a -> b -> c) -> Coord a -> Coord b -> Coord c #

(*>) :: Coord a -> Coord b -> Coord b #

(<*) :: Coord a -> Coord b -> Coord a #

Foldable Coord Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

fold :: Monoid m => Coord m -> m #

foldMap :: Monoid m => (a -> m) -> Coord a -> m #

foldr :: (a -> b -> b) -> b -> Coord a -> b #

foldr' :: (a -> b -> b) -> b -> Coord a -> b #

foldl :: (b -> a -> b) -> b -> Coord a -> b #

foldl' :: (b -> a -> b) -> b -> Coord a -> b #

foldr1 :: (a -> a -> a) -> Coord a -> a #

foldl1 :: (a -> a -> a) -> Coord a -> a #

toList :: Coord a -> [a] #

null :: Coord a -> Bool #

length :: Coord a -> Int #

elem :: Eq a => a -> Coord a -> Bool #

maximum :: Ord a => Coord a -> a #

minimum :: Ord a => Coord a -> a #

sum :: Num a => Coord a -> a #

product :: Num a => Coord a -> a #

Traversable Coord Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

traverse :: Applicative f => (a -> f b) -> Coord a -> f (Coord b) #

sequenceA :: Applicative f => Coord (f a) -> f (Coord a) #

mapM :: Monad m => (a -> m b) -> Coord a -> m (Coord b) #

sequence :: Monad m => Coord (m a) -> m (Coord a) #

Eq a => Eq (Coord a) Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

(==) :: Coord a -> Coord a -> Bool #

(/=) :: Coord a -> Coord a -> Bool #

Num a => Num (Coord a) Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

(+) :: Coord a -> Coord a -> Coord a #

(-) :: Coord a -> Coord a -> Coord a #

(*) :: Coord a -> Coord a -> Coord a #

negate :: Coord a -> Coord a #

abs :: Coord a -> Coord a #

signum :: Coord a -> Coord a #

fromInteger :: Integer -> Coord a #

Ord a => Ord (Coord a) Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

compare :: Coord a -> Coord a -> Ordering #

(<) :: Coord a -> Coord a -> Bool #

(<=) :: Coord a -> Coord a -> Bool #

(>) :: Coord a -> Coord a -> Bool #

(>=) :: Coord a -> Coord a -> Bool #

max :: Coord a -> Coord a -> Coord a #

min :: Coord a -> Coord a -> Coord a #

Show a => Show (Coord a) Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

showsPrec :: Int -> Coord a -> ShowS #

show :: Coord a -> String #

showList :: [Coord a] -> ShowS #

cX :: Lens' (Coord a) a Source #

Getter/setter lens to the x position in a Coord.

cY :: Lens' (Coord a) a Source #

Getter/setter lens to the x position in a Coord.

data Range a Source #

A specification for a range. Using R, contains the minimum and maximum. Using RAbout, contains the midpoint and size.

Constructors

R 

Fields

  • _rMin :: a

    Minimum of range.

  • _rMax :: a

    Maximum of range.

Bundled Patterns

pattern RAbout :: Fractional a => a -> a -> Range a

An alternative "constructor" for R, which takes a midpoint and size instead of a min and max.

This comes with record fields, _rMid and _rSize'.

Instances
Monad Range Source #

Basically the same as Reader Bool, for minimum and maximum fields.

Instance details

Defined in Interactive.Plot.Core

Methods

(>>=) :: Range a -> (a -> Range b) -> Range b #

(>>) :: Range a -> Range b -> Range b #

return :: a -> Range a #

fail :: String -> Range a #

Functor Range Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

fmap :: (a -> b) -> Range a -> Range b #

(<$) :: a -> Range b -> Range a #

Applicative Range Source #

Zipping behavior on minimum and maximum

Instance details

Defined in Interactive.Plot.Core

Methods

pure :: a -> Range a #

(<*>) :: Range (a -> b) -> Range a -> Range b #

liftA2 :: (a -> b -> c) -> Range a -> Range b -> Range c #

(*>) :: Range a -> Range b -> Range b #

(<*) :: Range a -> Range b -> Range a #

Foldable Range Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

fold :: Monoid m => Range m -> m #

foldMap :: Monoid m => (a -> m) -> Range a -> m #

foldr :: (a -> b -> b) -> b -> Range a -> b #

foldr' :: (a -> b -> b) -> b -> Range a -> b #

foldl :: (b -> a -> b) -> b -> Range a -> b #

foldl' :: (b -> a -> b) -> b -> Range a -> b #

foldr1 :: (a -> a -> a) -> Range a -> a #

foldl1 :: (a -> a -> a) -> Range a -> a #

toList :: Range a -> [a] #

null :: Range a -> Bool #

length :: Range a -> Int #

elem :: Eq a => a -> Range a -> Bool #

maximum :: Ord a => Range a -> a #

minimum :: Ord a => Range a -> a #

sum :: Num a => Range a -> a #

product :: Num a => Range a -> a #

Traversable Range Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

traverse :: Applicative f => (a -> f b) -> Range a -> f (Range b) #

sequenceA :: Applicative f => Range (f a) -> f (Range a) #

mapM :: Monad m => (a -> m b) -> Range a -> m (Range b) #

sequence :: Monad m => Range (m a) -> m (Range a) #

Show a => Show (Range a) Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

showsPrec :: Int -> Range a -> ShowS #

show :: Range a -> String #

showList :: [Range a] -> ShowS #

_rMid :: Range a -> Fractional a -> a Source #

rMin :: Lens' (Range a) a Source #

Getter/setter lens to the minimum value in a Range.

rMax :: Lens' (Range a) a Source #

Getter/setter lens to the maximum value in a Range.

rSize :: Fractional a => Lens' (Range a) a Source #

Lens into the size of a Range Modifying this size results in a scaling about the midpoint of the range.

view rSize (R 2 4)
-- 2
over rSize (* 2) (R 2 4)
-- R 1 5

rMid :: Fractional a => Lens' (Range a) a Source #

Lens into the midpoint of a Range. Modifying this midpoint shifts the range to a new midpoint, preserving the size.

view rMid (R 2 4)
-- 3
over rMid (+ 3) (R 2 4)
-- R 5 7

_rSize :: Num a => Range a -> a Source #

Gets the size of a Range.

A version of _rSize' that works for any instance of Num.

Run a Plot

runPlot Source #

Arguments

:: PlotOpts

options (can be defaultPlotOpts)

-> Maybe String

title

-> [Series]

series data

-> IO () 

Display fixed plot and title interactively.

See runPlotDynamic for more control.

runPlotAuto Source #

Arguments

:: PlotOpts

options (can be defaultPlotOpts)

-> Maybe String

title

-> [AutoSeries]

uninitialized series data

-> IO () 

Display fixed plot and title interactively, filling in default values.

See runPlotDynamic for more control.

Animated

animatePlot Source #

Arguments

:: PlotOpts

options (can be defaultPlotOpts)

-> Double

update rate (frames per second)

-> Maybe String

title

-> [[Series]]

list of series data (potentially infinite)

-> IO () 

Display a series of plots ([SeriesF]) with a time delay between each one. Will quit when the last plot is displayed. Use lastForever on the input list to repeat the last item indefinitely, or cycle to cycle through the list forever.

Note that this behavior is pretty simple; more advanced functionality can be achieved with runPlotDynamic directly.

lastForever :: [a] -> [a] Source #

Handy function to use with animatePlot to extend the last frame into eternity.

animatePlotFunc Source #

Arguments

:: PlotOpts

options (can be defaultPlotOpts, but remember to set a framerate)

-> Maybe String

title

-> (Double -> Maybe [Series])

function from time to plot. will quit as soon as Nothing is returned.

-> IO () 

Animate (according to the framerate in the PlotOpts) a function Double -> Maybe [Series], where the input is the current time in seconds and the output is the plot to display at that time. Will quit as soon as Nothing is given.

Remember to give a PlotOpts with a Just framerate.

This is a simple wrapper over animatePlotMoore with a stateless function. For more advanced functionality, use animatePlotMoore or runPlotDynamic directly.

Options

data PlotOpts Source #

Options used for running the plot interactively in a terminal.

Constructors

PO 

Fields

Instances
Default PlotOpts Source # 
Instance details

Defined in Interactive.Plot.Core

Methods

def :: PlotOpts #

poRange :: Lens' PlotOpts (Maybe (Range Double), Maybe (Range Double)) Source #

Lens into a PlotOpts getting its range X and range Y settings.

poDelay :: Lens' PlotOpts (Maybe Int) Source #

Lens into microsecond delay between frames, specified by a PlotOpts.

defaultPlotOpts :: PlotOpts Source #

Sensible defaults for most terminals.