Skip to content

Commit

Permalink
auto system generalized
Browse files Browse the repository at this point in the history
  • Loading branch information
mstksg committed Sep 3, 2019
1 parent e121cdb commit 81a8a14
Show file tree
Hide file tree
Showing 3 changed files with 13 additions and 7 deletions.
8 changes: 6 additions & 2 deletions src/Interactive/Plot/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ module Interactive.Plot.Core (
, PointStyleF(.., PointStyle), PointStyle, AutoPointStyle, psMarker, psColor
, SeriesF(..), Series, AutoSeries, sItems, sStyle, toCoordMap, fromCoordMap
, Alignment(..)
, PlotOpts(..), poTermRatio, poAspectRatio, poXRange, poYRange, poRange
, PlotOpts(..), poTermRatio, poAspectRatio, poXRange, poYRange, poRange, poAutoMethod
, renderPlot
-- * Internal
, plotRange
Expand All @@ -42,6 +42,7 @@ module Interactive.Plot.Core (

import Control.Applicative
import Control.Monad
import Control.Monad.Random
import Data.Coerce
import Data.Default
import Data.Foldable
Expand Down Expand Up @@ -133,6 +134,7 @@ data PointStyleF f = PointStyleF

makeLenses ''PointStyleF

-- | Specification of a style for a point.
type PointStyle = PointStyleF Identity

-- | A version of 'PointStyle' where you can leave the marker or color
Expand Down Expand Up @@ -187,6 +189,7 @@ data PlotOpts = PO
, _poAspectRatio :: Maybe Double -- ^ plot aspect ratio (H/W)
, _poXRange :: Maybe (Range Double) -- ^ X Range. Use 'Nothing' for automatic.
, _poYRange :: Maybe (Range Double) -- ^ Y Range. Use 'Nothing' for automatic.
, _poAutoMethod :: Maybe StdGen -- ^ How to fill in missing values. 'Nothing' for IO, 'Just' for deterministic seed.
}

makeLenses ''PlotOpts
Expand All @@ -196,6 +199,7 @@ instance Default PlotOpts where
, _poAspectRatio = Just 1
, _poXRange = Nothing
, _poYRange = Nothing
, _poAutoMethod = Just $ mkStdGen 28922710942259
}

-- | An alternative "constructor" for 'R', which takes a midpoint and size
Expand Down Expand Up @@ -242,7 +246,7 @@ within x r = x >= r ^. rMin && x <= r ^. rMax

-- | Lens into a 'PlotOpts' getting its range X and range Y settings.
poRange :: Lens' PlotOpts (Maybe (Range Double), Maybe (Range Double))
poRange f (PO r a x y) = uncurry (PO r a) <$> f (x, y)
poRange f (PO r a x y s) = (\(x', y') -> PO r a x' y' s) <$> f (x, y)

-- | Compute plot axis ranges based on a list of points and the size of the
-- display region.
Expand Down
4 changes: 3 additions & 1 deletion src/Interactive/Plot/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -77,7 +77,9 @@ runPlotAuto
:: PlotOpts
-> [AutoSeries]
-> IO ()
runPlotAuto po = runPlot po . fromAutoSeries
runPlotAuto po s = case po ^. poAutoMethod of
Nothing -> runPlot po =<< fromAutoSeriesIO s
Just g -> runPlot po (fromAutoSeries_ g s)

-- | Interactively plot serieses in the terminal.
runPlot
Expand Down
8 changes: 4 additions & 4 deletions src/Interactive/Plot/Series.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,11 +36,11 @@ import Lens.Micro
import qualified Data.Set as S

-- | Construct a series from any foldable container of y-values.
listSeries :: Foldable t => t Double -> AutoPointStyle -> AutoSeries
listSeries :: Foldable t => t Double -> PointStyleF f -> SeriesF f
listSeries xs = Series (toCoordMap . S.fromList . zipWith C [0..] . toList $ xs)

-- | Construct a series from any foldable container of x-y tuples.
tupleSeries :: Foldable t => t (Double, Double) -> AutoPointStyle -> AutoSeries
tupleSeries :: Foldable t => t (Double, Double) -> PointStyleF f -> SeriesF f
tupleSeries xs = Series (toCoordMap . S.fromList . foldMap ((:[]) . uncurry C) $ xs)

-- | Convert from a 'Series' back into an 'AutoSeries' with settings given.
Expand All @@ -66,8 +66,8 @@ funcSeries
:: Foldable t
=> (Double -> Double)
-> t Double
-> AutoPointStyle
-> AutoSeries
-> PointStyleF f
-> SeriesF f
funcSeries f xs = tupleSeries [ (x, f x) | x <- toList xs ]

-- | A set of default markers.
Expand Down

0 comments on commit 81a8a14

Please sign in to comment.