Skip to content

Commit feda2da

Browse files
committed
Wrap REPL history
- use Seq as inner storage - skip same entries using predicate - store index of first input that is not saved
1 parent cc15c19 commit feda2da

File tree

3 files changed

+132
-66
lines changed

3 files changed

+132
-66
lines changed

src/Swarm/TUI/Controller.hs

+35-24
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,7 @@ module Swarm.TUI.Controller (
3131
handleREPLEvent,
3232
validateREPLForm,
3333
adjReplHistIndex,
34+
TimeDir (..),
3435

3536
-- ** World panel
3637
handleWorldEvent,
@@ -65,6 +66,8 @@ import qualified Graphics.Vty as V
6566

6667
import qualified Control.Carrier.Lift as Fused
6768
import qualified Control.Carrier.State.Lazy as Fused
69+
import Data.Foldable (toList)
70+
import qualified Data.Sequence as Seq
6871
import Swarm.Game.CESK (cancel, emptyStore, initMachine)
6972
import Swarm.Game.Entity hiding (empty)
7073
import Swarm.Game.Robot
@@ -151,15 +154,12 @@ toggleModal s modal = do
151154
-- the updated REPL history to a @.swarm_history@ file.
152155
shutdown :: AppState -> EventM Name (Next AppState)
153156
shutdown s = do
154-
let hist = mapMaybe getNewEntry (s ^. uiState . uiReplHistory)
157+
let hist = mapMaybe getREPLEntry . toList . snd . Seq.splitAt (history ^. replStart) $ history ^. replSeq
155158
liftIO $ (`T.appendFile` T.unlines hist) =<< getSwarmHistoryPath True
156-
let s' = s & uiState . uiReplHistory . traverse %~ markOld
159+
let s' = s & uiState . uiReplHistory . replStart .~ replLength history
157160
halt s'
158161
where
159-
markOld (REPLEntry _ d e) = REPLEntry False d e
160-
markOld r = r
161-
getNewEntry (REPLEntry True _ t) = Just t
162-
getNewEntry _ = Nothing
162+
history = s ^. uiState . uiReplHistory
163163

164164
------------------------------------------------------------
165165
-- Handling Frame events
@@ -320,7 +320,7 @@ updateUI = do
320320
-- result as a REPL output, with its type, and reset the replStatus.
321321
REPLWorking pty (Just v) -> do
322322
let out = T.intercalate " " [into (prettyValue v), ":", prettyText (stripCmd pty)]
323-
uiState . uiReplHistory %= (REPLOutput out :)
323+
uiState . uiReplHistory %= addREPLOutput out
324324
gameState . replStatus .= REPLDone
325325
pure True
326326

@@ -403,8 +403,7 @@ handleREPLEvent s (VtyEvent (V.EvKey V.KEnter [])) =
403403
s
404404
& uiState . uiReplForm %~ updateFormState ""
405405
& uiState . uiReplType .~ Nothing
406-
& uiState . uiReplHistory %~ prependReplEntry
407-
& uiState . uiReplHistIdx .~ (-1)
406+
& uiState . uiReplHistory %~ addREPLEntry entry
408407
& uiState . uiError .~ Nothing
409408
& gameState . replStatus .~ REPLWorking ty Nothing
410409
& gameState . robotMap . ix "base" . machine .~ initMachine t topValCtx topStore
@@ -422,13 +421,10 @@ handleREPLEvent s (VtyEvent (V.EvKey V.KEnter [])) =
422421
topStore =
423422
fromMaybe emptyStore $
424423
s ^? gameState . robotMap . at "base" . _Just . robotContext . defStore
425-
prependReplEntry replHistory
426-
| firstReplEntry replHistory == Just entry = REPLEntry True True entry : replHistory
427-
| otherwise = REPLEntry True False entry : replHistory
428424
handleREPLEvent s (VtyEvent (V.EvKey V.KUp [])) =
429-
continue $ s & adjReplHistIndex (+)
425+
continue $ s & adjReplHistIndex Older
430426
handleREPLEvent s (VtyEvent (V.EvKey V.KDown [])) =
431-
continue $ s & adjReplHistIndex (-)
427+
continue $ s & adjReplHistIndex Newer
432428
handleREPLEvent s ev = do
433429
f' <- handleFormEvent ev (s ^. uiState . uiReplForm)
434430
continue $ validateREPLForm (s & uiState . uiReplForm .~ f')
@@ -449,22 +445,37 @@ validateREPLForm s =
449445
_ -> Nothing
450446
validate = setFieldValid (isRight result) REPLInput
451447

448+
data TimeDir = Newer | Older deriving (Eq, Ord, Show)
449+
452450
-- | Update our current position in the REPL history.
453-
adjReplHistIndex :: (Int -> Int -> Int) -> AppState -> AppState
454-
adjReplHistIndex (+/-) s =
455-
s & uiState . uiReplHistIdx .~ newIndex
456-
& (if curIndex == -1 then saveLastEntry else id)
451+
adjReplHistIndex :: TimeDir -> AppState -> AppState
452+
adjReplHistIndex d s =
453+
s & uiState . uiReplHistory . replIndex .~ newIndex
454+
& (if curIndex == historyLen then saveLastEntry else id)
457455
& (if newIndex /= curIndex then uiState . uiReplForm %~ updateFormState newEntry else id)
458456
& validateREPLForm
459457
where
458+
-- get REPL data
460459
saveLastEntry = uiState . uiReplLast .~ formState (s ^. uiState . uiReplForm)
461-
entries = [e | REPLEntry _ False e <- s ^. uiState . uiReplHistory]
462-
curIndex = s ^. uiState . uiReplHistIdx
463-
histLen = length entries
464-
newIndex = min (histLen - 1) (max (-1) (curIndex +/- 1))
460+
replLast = s ^. uiState . uiReplLast
461+
history = s ^. uiState . uiReplHistory
462+
historyLen = replLength history
463+
curText = maybe replLast replItemText $ Seq.lookup curIndex entries
464+
curIndex = history ^. replIndex
465+
entries = history ^. replSeq
466+
-- split repl at index
467+
(olderP, newer) = Seq.splitAt curIndex entries
468+
-- find first different entry in direction
469+
notSameEntry = \case
470+
REPLEntry t -> t /= curText
471+
_ -> False
472+
newIndex = case d of
473+
Newer -> maybe historyLen (curIndex +) $ Seq.findIndexL notSameEntry newer
474+
Older -> fromMaybe curIndex $ Seq.findIndexR notSameEntry olderP
475+
oops = "Oops, failed to index in REPL history, please report this bug."
465476
newEntry
466-
| newIndex == -1 = s ^. uiState . uiReplLast
467-
| otherwise = entries !! newIndex
477+
| newIndex == historyLen = replLast
478+
| otherwise = maybe oops replItemText $ entries Seq.!? newIndex
468479

469480
------------------------------------------------------------
470481
-- World events

src/Swarm/TUI/Model.hs

+91-37
Original file line numberDiff line numberDiff line change
@@ -20,20 +20,33 @@ module Swarm.TUI.Model (
2020
Modal (..),
2121

2222
-- * UI state
23+
24+
-- ** REPL
2325
REPLHistItem (..),
2426
firstReplEntry,
27+
replItemText,
28+
isREPLEntry,
29+
getREPLEntry,
30+
REPLHistory,
31+
replSeq,
32+
replStart,
33+
replIndex,
34+
addREPLEntry,
35+
addREPLOutput,
36+
replLength,
37+
38+
-- ** Inventory
2539
InventoryListEntry (..),
2640
_Separator,
2741
_InventoryEntry,
2842
_InstalledEntry,
29-
UIState,
3043

31-
-- ** Fields
44+
-- ** UI Model
45+
UIState,
3246
uiFocusRing,
3347
uiReplForm,
3448
uiReplType,
3549
uiReplHistory,
36-
uiReplHistIdx,
3750
uiReplLast,
3851
uiInventory,
3952
uiMoreInfoTop,
@@ -79,7 +92,7 @@ import Control.Lens
7992
import Control.Monad.Except
8093
import Control.Monad.State
8194
import Data.List (findIndex, sortOn)
82-
import Data.Maybe (fromMaybe)
95+
import Data.Maybe (fromMaybe, isJust)
8396
import Data.Text (Text)
8497
import qualified Data.Text as T
8598
import qualified Data.Vector as V
@@ -91,6 +104,8 @@ import Brick.Forms
91104
import qualified Brick.Widgets.List as BL
92105

93106
import Data.Bits (FiniteBits (finiteBitSize))
107+
import Data.Sequence (Seq)
108+
import qualified Data.Sequence as Seq
94109
import Swarm.Game.Entity as E
95110
import Swarm.Game.Robot
96111
import Swarm.Game.State
@@ -148,29 +163,74 @@ data Modal
148163

149164
-- | An item in the REPL history.
150165
data REPLHistItem
151-
= -- | Something entered by the user. The first
152-
-- @Bool@ indicates whether it is
153-
-- something entered this session (it
154-
-- will be @False@ for entries that were
155-
-- loaded from the history file). This is
156-
-- so we know which ones to append to the
157-
-- history file on shutdown.
158-
-- The second @Bool@ indicates whether it
159-
-- is a duplicate of the preceding item (it
160-
-- will be @True@ for duplicate entries).
161-
-- This is so we can ignore it when scrolling
162-
-- through the REPL history in the REPL window.
163-
REPLEntry Bool Bool Text
166+
= -- | Something entered by the user.
167+
REPLEntry Text
164168
| -- | A response printed by the system.
165169
REPLOutput Text
166170
deriving (Eq, Ord, Show, Read)
167171

172+
getREPLEntry :: REPLHistItem -> Maybe Text
173+
getREPLEntry = \case
174+
REPLEntry t -> Just t
175+
_ -> Nothing
176+
177+
isREPLEntry :: REPLHistItem -> Bool
178+
isREPLEntry = isJust . getREPLEntry
179+
180+
replItemText :: REPLHistItem -> Text
181+
replItemText = \case
182+
REPLEntry t -> t
183+
REPLOutput t -> t
184+
185+
-- | History of the REPL with indices (0 is first entry) to the current
186+
-- line and to the first entry since loading saved history.
187+
-- We also (ab)use the length of the REPL as the index of current
188+
-- input line, since that number is one past the index of last entry.
189+
data REPLHistory = REPLHistory
190+
{ _replSeq :: Seq REPLHistItem
191+
, _replIndex :: Int
192+
, _replStart :: Int
193+
}
194+
195+
makeLensesWith (lensRules & generateSignatures .~ False) ''REPLHistory
196+
197+
-- | Sequence of REPL inputs and outputs, oldest entry is leftmost.
198+
--
199+
-- TODO: The ideal would be not to expose inner storage, but currently
200+
-- namely the index+predicate functions on Seq are hard to resist.
201+
replSeq :: Lens' REPLHistory (Seq REPLHistItem)
202+
203+
-- | The current index in the REPL history (if the user is going back
204+
-- through the history using up/down keys).
205+
replIndex :: Lens' REPLHistory Int
206+
207+
-- | The index of the first entry since loading saved history.
208+
replStart :: Lens' REPLHistory Int
209+
210+
-- | Current (vertical) length of the REPL - used as index of input buffer.
211+
replLength :: REPLHistory -> Int
212+
replLength = length . _replSeq
213+
214+
-- | Add new REPL input - the index must have been pointing one past
215+
-- the last element already, so we increment it to keep it that way.
216+
addREPLItem :: (Text -> REPLHistItem) -> Text -> REPLHistory -> REPLHistory
217+
addREPLItem rc t h =
218+
h
219+
& replSeq %~ (|> rc t)
220+
& replIndex .~ replLength h
221+
222+
-- | Add new REPL input and increment index to last.
223+
addREPLEntry :: Text -> REPLHistory -> REPLHistory
224+
addREPLEntry = addREPLItem REPLEntry
225+
226+
-- | Add new REPL output and increment index to last.
227+
addREPLOutput :: Text -> REPLHistory -> REPLHistory
228+
addREPLOutput = addREPLItem REPLOutput
229+
168230
-- | Given a REPL history return @Just@ the most recent @Text@
169231
-- entered by the user or @Nothing@ if there is none.
170-
firstReplEntry :: [REPLHistItem] -> Maybe Text
171-
firstReplEntry ((REPLEntry _ _ entry) : _) = Just entry
172-
firstReplEntry (_ : rest) = firstReplEntry rest
173-
firstReplEntry [] = Nothing
232+
firstReplEntry :: REPLHistory -> Maybe Text
233+
firstReplEntry = foldr (const . getREPLEntry) Nothing . _replSeq
174234

175235
-- | An entry in the inventory list displayed in the info panel. We
176236
-- can either have an entity with a count in the robot's inventory,
@@ -192,8 +252,7 @@ data UIState = UIState
192252
, _uiReplForm :: Form Text AppEvent Name
193253
, _uiReplType :: Maybe Polytype
194254
, _uiReplLast :: Text
195-
, _uiReplHistory :: [REPLHistItem]
196-
, _uiReplHistIdx :: Int
255+
, _uiReplHistory :: REPLHistory
197256
, _uiInventory :: Maybe (Int, BL.List Name InventoryListEntry)
198257
, _uiMoreInfoTop :: Bool
199258
, _uiMoreInfoBot :: Bool
@@ -238,11 +297,7 @@ uiReplLast :: Lens' UIState Text
238297

239298
-- | History of things the user has typed at the REPL, interleaved
240299
-- with outputs the system has generated.
241-
uiReplHistory :: Lens' UIState [REPLHistItem]
242-
243-
-- | The current index in the REPL history (if the user is going back
244-
-- through the history using up/down keys).
245-
uiReplHistIdx :: Lens' UIState Int
300+
uiReplHistory :: Lens' UIState REPLHistory
246301

247302
-- | The hash value of the focused robot entity (so we can tell if its
248303
-- inventory changed) along with a list of the items in the
@@ -335,27 +390,26 @@ initReplForm =
335390
initLgTicksPerSecond :: Int
336391
initLgTicksPerSecond = 3 -- 2^3 = 8 ticks / second
337392

338-
createHistory :: [Text] -> [REPLHistItem]
339-
createHistory = map (uncurry $ REPLEntry False) . zipLines . reverse
340-
where
341-
zipLines ls = zipWith samePair ls $ tail ls ++ [""]
342-
samePair n o = (n == o, n)
343-
344393
-- | Initialize the UI state. This needs to be in the IO monad since
345394
-- it involves reading a REPL history file and getting the current
346395
-- time.
347396
initUIState :: ExceptT Text IO UIState
348397
initUIState = liftIO $ do
349398
historyT <- readFileMayT =<< getSwarmHistoryPath False
350-
let history = maybe [] (createHistory . T.lines) historyT
399+
let history = maybe Seq.empty (Seq.fromList . map REPLEntry . T.lines) historyT
400+
historyLen = length history
351401
startTime <- getTime Monotonic
352402
return $
353403
UIState
354404
{ _uiFocusRing = initFocusRing
355405
, _uiReplForm = initReplForm
356406
, _uiReplType = Nothing
357-
, _uiReplHistory = history
358-
, _uiReplHistIdx = -1
407+
, _uiReplHistory =
408+
REPLHistory
409+
{ _replSeq = history
410+
, _replIndex = historyLen -- one past rightmost=newest
411+
, _replStart = historyLen
412+
}
359413
, _uiReplLast = ""
360414
, _uiInventory = Nothing
361415
, _uiMoreInfoTop = False

src/Swarm/TUI/View.hs

+6-5
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,7 @@ import qualified Data.List as L
4747
import Data.List.Split (chunksOf)
4848
import qualified Data.Map as M
4949
import Data.Maybe (fromMaybe)
50+
import qualified Data.Sequence as Seq
5051
import Data.Text (Text)
5152
import qualified Data.Text as T
5253
import Linear
@@ -62,6 +63,7 @@ import Brick.Widgets.Dialog
6263
import qualified Brick.Widgets.List as BL
6364
import qualified Brick.Widgets.Table as BT
6465

66+
import Data.Foldable (toList)
6567
import Swarm.Game.Display
6668
import Swarm.Game.Entity as E
6769
import Swarm.Game.Recipe
@@ -555,13 +557,12 @@ drawRobotLog s =
555557
drawREPL :: AppState -> Widget Name
556558
drawREPL s =
557559
vBox $
558-
map fmt (reverse (take (replHeight - 1) . filter newEntry $ (s ^. uiState . uiReplHistory)))
560+
map fmt (take (replHeight - 1) . toList . ignoreLoaded $ history ^. replSeq)
559561
++ case isActive <$> (s ^. gameState . robotMap . at "base") of
560562
Just False -> [renderForm (s ^. uiState . uiReplForm)]
561563
_ -> [padRight Max $ txt "..."]
562564
where
563-
newEntry (REPLEntry False _ _) = False
564-
newEntry _ = True
565-
566-
fmt (REPLEntry _ _ e) = txt replPrompt <+> txt e
565+
history = s ^. uiState . uiReplHistory
566+
ignoreLoaded = snd . Seq.splitAt (history ^. replStart)
567+
fmt (REPLEntry e) = txt replPrompt <+> txt e
567568
fmt (REPLOutput t) = txt t

0 commit comments

Comments
 (0)