| Copyright | (c) Justin Le 2018 |
|---|---|
| License | BSD3 |
| Maintainer | justin@jle.im |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Interactive.Plot.Core
Contents
Description
Core rendering functionality for the library.
Synopsis
- data Coord a = C {}
- cX :: Lens' (Coord a) a
- cY :: Lens' (Coord a) a
- data Range a where
- _rMid :: Range a -> Fractional a -> a
- _rSize' :: Range a -> Fractional a -> a
- rMin :: Lens' (Range a) a
- rMax :: Lens' (Range a) a
- rSize :: Fractional a => Lens' (Range a) a
- rMid :: Fractional a => Lens' (Range a) a
- _rSize :: Num a => Range a -> a
- data Auto a
- type PointStyle = PointStyleF Identity
- pattern PointStyle :: Char -> Color -> PointStyle
- _psMarker :: PointStyle -> Char
- _psColor :: PointStyle -> Color
- data PointStyleF f = PointStyleF {
- _psMarkerF :: f Char
- _psColorF :: f Color
- type AutoPointStyle = PointStyleF Auto
- psMarker :: Lens' PointStyle Char
- psColor :: Lens' PointStyle Color
- type Series = SeriesF Identity
- data SeriesF f = Series {}
- type AutoSeries = SeriesF Auto
- sItems :: Lens' (SeriesF f) (Map Double (Set Double))
- sStyle :: Lens' (SeriesF f) (PointStyleF f)
- toCoordMap :: Eq a => Set (Coord a) -> Map a (Set a)
- fromCoordMap :: Map a (Set a) -> Set (Coord a)
- data Alignment
- data PlotOpts = PO {
- _poTermRatio :: Double
- _poAspectRatio :: Maybe Double
- _poXRange :: Maybe (Range Double)
- _poYRange :: Maybe (Range Double)
- _poAutoMethod :: Maybe StdGen
- _poHelp :: Bool
- _poFramerate :: Maybe Double
- _poDescription :: Maybe Image
- poTermRatio :: Lens' PlotOpts Double
- poAspectRatio :: Lens' PlotOpts (Maybe Double)
- poXRange :: Lens' PlotOpts (Maybe (Range Double))
- poYRange :: Lens' PlotOpts (Maybe (Range Double))
- poRange :: Lens' PlotOpts (Maybe (Range Double), Maybe (Range Double))
- poAutoMethod :: Lens' PlotOpts (Maybe StdGen)
- poHelp :: Lens' PlotOpts Bool
- poFramerate :: Lens' PlotOpts (Maybe Double)
- poDelay :: Lens' PlotOpts (Maybe Int)
- poDescription :: Lens' PlotOpts (Maybe Image)
- defaultPlotOpts :: PlotOpts
- renderPlot :: Coord (Range Int) -> Coord (Range Double) -> [Series] -> [Image]
- plotRange :: PlotOpts -> Coord (Range Int) -> [Series] -> Coord (Range Double)
- newtype OrdColor = OC {}
- renderPoint :: PointStyle -> Image
- hzToDelay :: Lens' (Maybe Double) (Maybe Int)
Documentation
An ordered pair in a.
Instances
| Monad Coord Source # | Basically the same as |
| Functor Coord Source # | |
| Applicative Coord Source # | |
| Foldable Coord Source # | |
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 # elem :: Eq a => a -> Coord a -> Bool # maximum :: Ord a => Coord a -> a # minimum :: Ord a => Coord a -> a # | |
| Traversable Coord Source # | |
| Eq a => Eq (Coord a) Source # | |
| Num a => Num (Coord a) Source # | |
| Ord a => Ord (Coord a) Source # | |
Defined in Interactive.Plot.Core | |
| Show a => Show (Coord a) Source # | |
A specification for a range. Using R, contains the minimum and
maximum. Using RAbout, contains the midpoint and size.
Bundled Patterns
| pattern RAbout :: Fractional a => a -> a -> Range a | An alternative "constructor" for |
Instances
| Monad Range Source # | Basically the same as |
| Functor Range Source # | |
| Applicative Range Source # | Zipping behavior on minimum and maximum |
| Foldable Range Source # | |
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 # elem :: Eq a => a -> Range a -> Bool # maximum :: Ord a => Range a -> a # minimum :: Ord a => Range a -> a # | |
| Traversable Range Source # | |
| Show a => Show (Range a) Source # | |
_rMid :: Range a -> Fractional a -> a Source #
_rSize' :: Range a -> Fractional a -> a Source #
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
Used to specify fields in PointStyle and SeriesF: Use Auto for
automatic inference, and Given to provide a specific value.
Instances
| Monad Auto Source # | |
| Functor Auto Source # | |
| Applicative Auto Source # | |
| MonadPlus Auto Source # | Opposite behavior of |
| Alternative Auto Source # | Opposite behavior of |
| Eq a => Eq (Auto a) Source # | |
| Ord a => Ord (Auto a) Source # | |
| Show a => Show (Auto a) Source # | |
| Generic (Auto a) Source # | |
| Semigroup (Auto a) Source # | |
| Monoid (Auto a) Source # | |
| type Rep (Auto a) Source # | |
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 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.
_psMarker :: PointStyle -> Char Source #
_psColor :: PointStyle -> Color Source #
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
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.
type Series = SeriesF Identity Source #
Data for a single series: contains the coordinate map with the point style for the series.
A parameterized version of SeriesF to unify functions in
Interactive.Plot.Series.
Mainly you will be using either SeriesF or AutoSeries.
Constructors
| Series | |
Fields
| |
type AutoSeries = SeriesF Auto Source #
A version of SeriesF where you can leave the marker or color blank,
to be automatically inferred.
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:: LensSeriesFPointStylesStyle:: LensAutoSeriesAutoPointStyle
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.
Options used for running the plot interactively in a terminal.
Constructors
| PO | |
Fields
| |
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.
Arguments
| :: Coord (Range Int) | display region |
| -> Coord (Range Double) | plot axis range |
| -> [Series] | |
| -> [Image] |
Render serieses based on a display region and plot axis ranges.
Internal
Arguments
| :: PlotOpts | |
| -> Coord (Range Int) | display region |
| -> [Series] | Points |
| -> Coord (Range Double) | actual plot axis range |
Compute plot axis ranges based on a list of points and the size of the display region.
renderPoint :: PointStyle -> Image Source #
Render a single according to a PointStyle.