Skip to content

Commit

Permalink
display help done
Browse files Browse the repository at this point in the history
  • Loading branch information
mstksg committed Sep 3, 2019
1 parent df4c5bb commit f7c3da3
Show file tree
Hide file tree
Showing 3 changed files with 53 additions and 6 deletions.
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,5 +6,5 @@ Simple terminal interactive plotter.
Todo
----

* Display controls on-screen
* Display title
* Allow for changing of plot dynamically
6 changes: 4 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 (
, PointStyle, pattern PointStyle, _psMarker, _psColor, PointStyleF(..), AutoPointStyle, psMarker, psColor
, Series, SeriesF(..), AutoSeries, sItems, sStyle, toCoordMap, fromCoordMap
, Alignment(..)
, PlotOpts(..), poTermRatio, poAspectRatio, poXRange, poYRange, poRange, poAutoMethod
, PlotOpts(..), poTermRatio, poAspectRatio, poXRange, poYRange, poRange, poAutoMethod, poHelp
, defaultPlotOpts
, renderPlot
-- * Internal
Expand Down Expand Up @@ -255,6 +255,7 @@ data PlotOpts = PO
-- 'Interactive.Plot.Run.runPlot'.
-- Default is an arbitrarily
-- selected seed.
, _poHelp :: Bool -- ^ Whether or not to show help box initially. Box can always be toggled with @?@. (Default is 'True')
}

makeLenses ''PlotOpts
Expand All @@ -267,6 +268,7 @@ defaultPlotOpts = PO
, _poXRange = Nothing
, _poYRange = Nothing
, _poAutoMethod = Just $ mkStdGen 28922710942259
, _poHelp = True
}

instance Default PlotOpts where
Expand Down Expand Up @@ -320,7 +322,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 s) = (\(x', y') -> PO r a x' y' s) <$> f (x, y)
poRange f (PO r a x y s h) = (\(x', y') -> PO r a x' y' s h) <$> f (x, y)

-- | Compute plot axis ranges based on a list of points and the size of the
-- display region.
Expand Down
51 changes: 48 additions & 3 deletions src/Interactive/Plot/Run.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TemplateHaskell #-}

-- |
-- Module : Interative.Plot.Run
Expand All @@ -26,11 +27,13 @@ import Graphics.Vty
import Interactive.Plot.Core
import Interactive.Plot.Series
import Lens.Micro
import Lens.Micro.TH

data PEvent = PEQuit
| PEZoom (Coord Double)
| PEPan (Coord Double)
| PEResize (Coord Int)
| PEHelp
| PEReset

processEvent :: Event -> Maybe PEvent
Expand All @@ -48,6 +51,10 @@ processEvent = \case
EvKey (KChar 'j') [] -> Just $ PEPan (C 0 (-0.2))
EvKey (KChar 'k') [] -> Just $ PEPan (C 0 0.2 )
EvKey (KChar 'l') [] -> Just $ PEPan (C 0.2 0 )
EvKey (KChar 'w') [] -> Just $ PEPan (C (-0.2) 0 )
EvKey (KChar 'a') [] -> Just $ PEPan (C 0 (-0.2))
EvKey (KChar 's') [] -> Just $ PEPan (C 0 0.2 )
EvKey (KChar 'd') [] -> Just $ PEPan (C 0.2 0 )
EvKey KLeft [] -> Just $ PEPan (C (-0.2) 0 )
EvKey KDown [] -> Just $ PEPan (C 0 (-0.2))
EvKey KUp [] -> Just $ PEPan (C 0 0.2 )
Expand All @@ -56,16 +63,18 @@ processEvent = \case
EvKey (KChar '^') [] -> Just $ PEZoom (C 1 (sqrt 0.5))
EvKey (KChar '<') [] -> Just $ PEZoom (C (sqrt 2 ) 1 )
EvKey (KChar '>') [] -> Just $ PEZoom (C (sqrt 0.5) 1 )
EvKey (KChar '?') [] -> Just $ PEHelp
EvKey (KChar '/') [] -> Just $ PEHelp
EvResize ht wd -> Just $ PEResize (C ht wd)
_ -> Nothing

data PlotState = PlotState
{ _psRange :: Coord (Range Double)
, _psSerieses :: [Series]
, _psHelp :: Bool
}

psRange :: Lens' PlotState (Coord (Range Double))
psRange f (PlotState r s) = (`PlotState` s) <$> f r
makeClassy ''PlotState

displayRange :: Output -> IO (Coord (Range Int))
displayRange o = do
Expand Down Expand Up @@ -101,6 +110,7 @@ runPlot po ss = do
dr <- displayRange $ outputIface vty
pure PlotState { _psRange = plotRange po dr ss
, _psSerieses = ss
, _psHelp = po ^. poHelp
}
plotLoop
:: Vty
Expand All @@ -111,7 +121,10 @@ runPlot po ss = do
plotLoop vty peChan psRef tPE = do
dr <- displayRange $ outputIface vty
ps <- readIORef psRef
let imgs = renderPlot dr (_psRange ps) (_psSerieses ps)
let displayHelp
| ps ^. psHelp = (box helpBox :)
| otherwise = id
imgs = displayHelp $ renderPlot dr (_psRange ps) (_psSerieses ps)

update vty $ picForLayers imgs
readChan peChan >>= \case
Expand Down Expand Up @@ -139,6 +152,38 @@ runPlot po ss = do
writeIORef psRef $
ps & psRange .~ newRange
pure True
PEHelp -> do
writeIORef psRef $
ps & psHelp %~ not
pure True
PEReset -> do
writeIORef psRef =<< initPS vty
pure True

helpText :: [(String, String)]
helpText =
[ ("-/+" , "zoom")
, ("arrows", "pan")
, ("v/^" , "vert stretch")
, ("</>" , "horiz stretch")
, ("r" , "reset")
, ("?" , "disp help")
, ("q" , "quit")
]

helpBox :: Image
helpBox = vertCat (string defAttr . (++ " ") <$> x)
`horizJoin` vertCat (string defAttr <$> y)
where
(x,y) = unzip helpText

box :: Image -> Image
box i = vertCat . map horizCat $
[ [c , tb, c ]
, [lr, i , lr]
, [c , tb, c ]
]
where
lr = charFill defAttr '|' 1 (imageHeight i)
tb = charFill defAttr '-' (imageWidth i) 1
c = char defAttr '+'

0 comments on commit f7c3da3

Please sign in to comment.