Redesign SourceWindow around start + space

Originally, SourceWindow was built around a start and an end point.
It turns out, this was a bad idea as it caused update issues when
switching files.

Now we keep around the extent information.
This commit is contained in:
CrystalSplitter 2024-03-17 12:26:07 -07:00 committed by Jordan R AW
parent 040e7bce79
commit 46ca959f51
6 changed files with 98 additions and 65 deletions

View File

@ -43,7 +43,8 @@ data AppConfig = AppConfig
-- ^ Command to run to initialise the interpreter. -- ^ Command to run to initialise the interpreter.
, getStartupCommands :: ![T.Text] , getStartupCommands :: ![T.Text]
-- ^ Commands to run in ghci during start up. -- ^ Commands to run in ghci during start up.
} deriving (Show) }
deriving (Show)
defaultConfig :: AppConfig defaultConfig :: AppConfig
defaultConfig = defaultConfig =

View File

@ -32,7 +32,8 @@ data AppInterpState s n = AppInterpState
, _cmdHistory :: ![[s]] , _cmdHistory :: ![[s]]
, historyPos :: !Int , historyPos :: !Int
-- ^ Current position -- ^ Current position
} deriving (Show) }
deriving (Show)
-- | Lens accessor for the editor. See '_liveEditor'. -- | Lens accessor for the editor. See '_liveEditor'.
liveEditor :: Lens.Lens' (AppInterpState s n) (BE.Editor s n) liveEditor :: Lens.Lens' (AppInterpState s n) (BE.Editor s n)

View File

@ -173,14 +173,27 @@ selectedLine s = fromMaybe 1 (s ^. sourceWindow . SourceWindow.srcSelectedLineL)
selectPausedLine :: (Ord n) => AppState n -> B.EventM n m (AppState n) selectPausedLine :: (Ord n) => AppState n -> B.EventM n m (AppState n)
selectPausedLine s@AppState{interpState} = do selectPausedLine s@AppState{interpState} = do
s' <- setSelectedFile ourSelectedFile s s' <- setSelectedFile ourSelectedFile s
let ourSelectedLine :: Int
ourSelectedLine =
fromMaybe
(selectedLine s')
(Loc.startLine . Loc.fSourceRange =<< interpState.pauseLoc)
newSrcW <- SourceWindow.setSelectionTo ourSelectedLine (s' ^. sourceWindow) newSrcW <- SourceWindow.setSelectionTo ourSelectedLine (s' ^. sourceWindow)
pure $ Lens.set sourceWindow newSrcW s' pure
. ( \s'' ->
writeDebugLog
( "replacing source window. new line: "
<> Util.showT (s'' ^. sourceWindow . SourceWindow.srcSelectedLineL)
<> " should be "
<> Util.showT ourSelectedLine
<> ", window start "
<> Util.showT (s'' ^. sourceWindow . SourceWindow.srcWindowStartL)
)
s''
)
. Lens.set sourceWindow newSrcW
$ s'
where where
ourSelectedLine :: Int
ourSelectedLine =
fromMaybe
(selectedLine s)
(Loc.startLine . Loc.fSourceRange =<< interpState.pauseLoc)
ourSelectedFile = maybe (selectedFile s) (Just . Loc.filepath) interpState.pauseLoc ourSelectedFile = maybe (selectedFile s) (Just . Loc.filepath) interpState.pauseLoc
-- | Write a debug log entry. -- | Write a debug log entry.

View File

@ -12,5 +12,6 @@ data AppName
| BindingViewport | BindingViewport
| ModulesViewport | ModulesViewport
| TraceViewport | TraceViewport
| SourceList | -- | Source Window Name.
SourceList
deriving (Eq, Show, Ord) deriving (Eq, Show, Ord)

View File

@ -31,9 +31,11 @@ handleEvent :: B.BrickEvent AppName e -> B.EventM AppName (AppState AppName) ()
handleEvent (B.VtyEvent (V.EvResize _ _)) = B.invalidateCache handleEvent (B.VtyEvent (V.EvResize _ _)) = B.invalidateCache
handleEvent ev = do handleEvent ev = do
appState <- B.get appState <- B.get
updatedSourceWindow <- SourceWindow.updateSrcWindowEnd (appState ^. AppState.sourceWindow) updatedSourceWindow <- SourceWindow.updateVerticalSpace (appState ^. AppState.sourceWindow)
let appStateUpdated = Lens.set AppState.sourceWindow updatedSourceWindow appState let appStateUpdated = Lens.set AppState.sourceWindow updatedSourceWindow appState
let handler = case appStateUpdated.activeWindow of B.put appStateUpdated
let handler :: B.BrickEvent AppName e -> B.EventM AppName (AppState AppName) ()
handler = case appStateUpdated.activeWindow of
AppState.ActiveCodeViewport -> handleSrcWindowEvent AppState.ActiveCodeViewport -> handleSrcWindowEvent
AppState.ActiveLiveInterpreter -> handleInterpreterEvent AppState.ActiveLiveInterpreter -> handleInterpreterEvent
AppState.ActiveInfoWindow -> handleInfoEvent AppState.ActiveInfoWindow -> handleInfoEvent

View File

@ -16,16 +16,17 @@ module Ghcitui.Brick.SourceWindow
, ScrollDir (..) , ScrollDir (..)
, scrollTo , scrollTo
, srcWindowScrollPage , srcWindowScrollPage
, updateSrcWindowEnd
, srcWindowMoveSelectionBy , srcWindowMoveSelectionBy
, srcWindowReplace , srcWindowReplace
, setSelectionTo , setSelectionTo
, updateVerticalSpace
-- * Lenses -- * Lenses
, srcElementsL , srcElementsL
, srcNameL , srcNameL
, srcSelectedLineL , srcSelectedLineL
, srcWindowStartL , srcWindowStartL
, srcWindowVerticalSpaceL
-- * Misc -- * Misc
, srcWindowLength , srcWindowLength
@ -48,7 +49,8 @@ data SourceWindow name elem = SourceWindow
, srcWindowStart :: !Int , srcWindowStart :: !Int
-- ^ The starting position of the window, as a line number (1-indexed). -- ^ The starting position of the window, as a line number (1-indexed).
-- No lines before this line number is rendered. -- No lines before this line number is rendered.
, srcWindowEnd :: !(Maybe Int) , srcWindowVerticalSpace :: !(Maybe Int)
-- ^ The maximum amount of visible lines at any point in time.
, srcName :: !name , srcName :: !name
-- ^ The name of the window. -- ^ The name of the window.
, srcSelectedLine :: !(Maybe Int) , srcSelectedLine :: !(Maybe Int)
@ -59,12 +61,23 @@ data SourceWindow name elem = SourceWindow
makeLensesFor makeLensesFor
[ ("srcElements", "srcElementsL") [ ("srcElements", "srcElementsL")
, ("srcWindowStart", "srcWindowStartL") , ("srcWindowStart", "srcWindowStartL")
, ("srcWindowEnd", "srcWindowEndL") , ("srcWindowVerticalSpace", "srcWindowVerticalSpaceL")
, ("srcName", "srcNameL") , ("srcName", "srcNameL")
, ("srcSelectedLine", "srcSelectedLineL") , ("srcSelectedLine", "srcSelectedLineL")
] ]
''SourceWindow ''SourceWindow
-- | The difference between the last rendered line and the first rendered line.
srcWindowLineDiffCount :: SourceWindow name elem -> Maybe Int
srcWindowLineDiffCount SourceWindow{srcWindowVerticalSpace = Just sWVS} = pure $ sWVS - 1
srcWindowLineDiffCount _ = Nothing
-- | The line number of the last viewable line in the window.
getLastRenderedLine :: SourceWindow name elem -> Maybe Int
getLastRenderedLine srcW@SourceWindow{srcWindowStart} = do
diffCount <- srcWindowLineDiffCount srcW
pure $ diffCount + srcWindowStart
-- | Render a 'SourceWindow' into a Brick 'B.Widget'. -- | Render a 'SourceWindow' into a Brick 'B.Widget'.
renderSourceWindow renderSourceWindow
:: (Ord n) :: (Ord n)
@ -103,23 +116,27 @@ renderSourceWindow func srcW = B.reportExtent (srcName srcW) (B.Widget B.Greedy
srcWindowLength :: SourceWindow n e -> Int srcWindowLength :: SourceWindow n e -> Int
srcWindowLength = Vec.length . srcElements srcWindowLength = Vec.length . srcElements
-- | Set the source window end line inside of the given 'EventM' Monad. {- | Set the source window end line inside of the given 'EventM' Monad.
updateSrcWindowEnd :: (Ord n) => SourceWindow n e -> B.EventM n m (SourceWindow n e) This is primarily for internal consistency, and is cheap. It should be called any time
updateSrcWindowEnd srcW@SourceWindow{srcWindowStart, srcName} = do the srcWindowStart changes.
mExtent <- B.lookupExtent srcName -}
let end = case mExtent of updateVerticalSpace :: (Ord n) => SourceWindow n e -> B.EventM n m (SourceWindow n e)
updateVerticalSpace srcW@SourceWindow{srcName {- , srcContainerName -}} = do
mSrcNameExtent <- B.lookupExtent srcName
let mSpace = case mSrcNameExtent of
Just extent -> Just extent ->
-- -1 offset since the end is inclusive. Just . snd . B.extentSize $ extent
Just $ (snd . B.extentSize $ extent) + srcWindowStart - 1
_ -> Nothing _ -> Nothing
pure (Lens.set srcWindowEndL end srcW) pure (Lens.set srcWindowVerticalSpaceL mSpace srcW)
-- | Scroll to a given position, and move the source line along the way if needed. -- | Scroll to a given position, and move the source line along the way if needed.
scrollTo :: Int -> SourceWindow n e -> SourceWindow n e scrollTo :: Int -> SourceWindow n e -> SourceWindow n e
scrollTo pos srcW@SourceWindow{srcWindowEnd = Just windowEnd} = scrollTo pos srcW@SourceWindow{srcWindowVerticalSpace = Just vSpace} =
srcW{srcWindowStart = clampedPos, srcSelectedLine = newSelection} srcW{srcWindowStart = clampedPos, srcSelectedLine = newSelection}
where where
clampedPos = Util.clamp (1, srcWindowLength srcW - renderHeight) pos -- Clamp between start line and one window away from the end.
clampedPos = Util.clamp (1, srcWindowLength srcW - vSpace) pos
newSelection newSelection
| -- Choose the starting line if we're trying to go past the beginning. | -- Choose the starting line if we're trying to go past the beginning.
isScrollingPastStart = isScrollingPastStart =
@ -128,13 +145,13 @@ scrollTo pos srcW@SourceWindow{srcWindowEnd = Just windowEnd} =
isScrollingPastEnd = isScrollingPastEnd =
Just $ srcWindowLength srcW Just $ srcWindowLength srcW
| otherwise = newClampedSelectedLine | otherwise = newClampedSelectedLine
renderHeight = windowEnd - srcWindowStart srcW
isScrollingPastStart = pos < 1 isScrollingPastStart = pos < 1
isScrollingPastEnd = pos >= srcWindowLength srcW -- Using >= because of a hack. isScrollingPastEnd = pos >= srcWindowLength srcW -- Using >= because of a hack.
newClampedSelectedLine = newClampedSelectedLine :: Maybe Int
Util.clamp newClampedSelectedLine = do
(clampedPos, clampedPos + renderHeight) ssl <- srcSelectedLine srcW
<$> srcSelectedLine srcW diffCount <- srcWindowLineDiffCount srcW
pure $ Util.clamp (clampedPos, clampedPos + diffCount) ssl
scrollTo _ srcW = srcW scrollTo _ srcW = srcW
-- | Direction to scroll by. -- | Direction to scroll by.
@ -142,18 +159,16 @@ data ScrollDir = Up | Down deriving (Eq, Show)
-- | Scroll by a full page in a direction. -- | Scroll by a full page in a direction.
srcWindowScrollPage :: (Ord n) => ScrollDir -> SourceWindow n e -> B.EventM n m (SourceWindow n e) srcWindowScrollPage :: (Ord n) => ScrollDir -> SourceWindow n e -> B.EventM n m (SourceWindow n e)
srcWindowScrollPage dir srcW = srcWindowScrollPage' dir <$> updateSrcWindowEnd srcW srcWindowScrollPage dir srcW = srcWindowScrollPage' dir <$> updateVerticalSpace srcW
-- | Internal helper.
srcWindowScrollPage' :: ScrollDir -> SourceWindow n e -> SourceWindow n e srcWindowScrollPage' :: ScrollDir -> SourceWindow n e -> SourceWindow n e
srcWindowScrollPage' dir srcW = srcWindowScrollPage' dir srcW@SourceWindow{srcWindowStart} =
case dir of case dir of
Up -> Up -> scrollTo onePageUpPos srcW
let renderHeight = windowEnd - srcWindowStart srcW Down -> scrollTo (fromMaybe srcWindowStart (getLastRenderedLine srcW)) srcW
in scrollTo (srcWindowStart srcW - renderHeight) srcW
Down -> scrollTo windowEnd srcW
where where
windowEnd = fromMaybe 1 $ srcWindowEnd srcW onePageUpPos = srcWindowStart - vSpace + 1 -- Plus one to preserve the top line.
vSpace = fromMaybe 0 (srcWindowVerticalSpace srcW)
-- | Set the selection to a given position, and scroll the window accordingly. -- | Set the selection to a given position, and scroll the window accordingly.
setSelectionTo setSelectionTo
@ -163,14 +178,20 @@ setSelectionTo
-> SourceWindow n e -> SourceWindow n e
-- ^ Source window to update. -- ^ Source window to update.
-> B.EventM n m (SourceWindow n e) -> B.EventM n m (SourceWindow n e)
setSelectionTo pos srcW@SourceWindow{srcSelectedLine = Just sl, srcWindowEnd = Just end} = setSelectionTo pos srcW = do
if pos < srcWindowStart srcW || pos > end srcW' <- updateVerticalSpace srcW
then srcWindowMoveSelectionBy delta srcW case (getLastRenderedLine srcW', srcSelectedLine srcW') of
else do (Just end, Just oldSelectedLine) -> do
pure $ srcW{srcSelectedLine = Just pos} let delta = pos - oldSelectedLine
where if pos < srcWindowStart srcW' || pos > end
delta = pos - sl then srcWindowMoveSelectionBy delta srcW
setSelectionTo _ srcW = pure srcW else do
pure $ srcW{srcSelectedLine = Just pos}
_ -> setSelectionToFallback pos srcW'
-- | Fallback function for setting the source window selection line, when we can't set it properly.
setSelectionToFallback :: Int -> SourceWindow name elem -> B.EventM name m (SourceWindow name elem)
setSelectionToFallback pos srcW = pure $ srcW{srcSelectedLine = Just pos, srcWindowStart = pos}
-- | Move the selected line by a given amount. -- | Move the selected line by a given amount.
srcWindowMoveSelectionBy srcWindowMoveSelectionBy
@ -181,23 +202,17 @@ srcWindowMoveSelectionBy
-- ^ Source window to update. -- ^ Source window to update.
-> B.EventM n m (SourceWindow n e) -> B.EventM n m (SourceWindow n e)
srcWindowMoveSelectionBy amnt sw = do srcWindowMoveSelectionBy amnt sw = do
srcW' <- updateSrcWindowEnd sw srcW <- updateVerticalSpace sw
case srcWindowEnd srcW' of case (getLastRenderedLine srcW, srcWindowLineDiffCount srcW, srcSelectedLine srcW) of
Just end -> do (Just end, Just renderHeight, Just oldSLine)
let start = srcWindowStart srcW' | newSLine < srcWindowStart srcW ->
let mSLine = srcSelectedLine srcW' pure $ scrollTo newSLine srcW{srcSelectedLine = Just newSLine}
let renderHeight = end - start | newSLine > end ->
pure $ case mSLine of pure $ scrollTo (newSLine - renderHeight) srcW{srcSelectedLine = Just newSLine}
Just sLine | otherwise -> pure $ srcW{srcSelectedLine = Just newSLine}
| newSLine < start -> where
scrollTo newSLine srcW'{srcSelectedLine = Just newSLine} newSLine = Util.clamp (1, Vec.length (srcElements srcW)) $ oldSLine + amnt
| newSLine > end -> _ -> pure srcW
scrollTo (newSLine - renderHeight) srcW'{srcSelectedLine = Just newSLine}
| otherwise -> srcW'{srcSelectedLine = Just newSLine}
where
newSLine = Util.clamp (1, Vec.length (srcElements srcW')) $ sLine + amnt
_ -> srcW'
Nothing -> pure srcW'
{- | Replace the contents of a given source window, and reset the pseudo-viewport's position {- | Replace the contents of a given source window, and reset the pseudo-viewport's position
to the top. to the top.
@ -215,13 +230,13 @@ mkSourcWindow
-> T.Text -> T.Text
-- ^ Text contents of the source window (to be split up). -- ^ Text contents of the source window (to be split up).
-> SourceWindow n T.Text -> SourceWindow n T.Text
mkSourcWindow name text = mkSourcWindow sourceWindowName text =
SourceWindow SourceWindow
{ srcElements = lineVec { srcElements = lineVec
, srcWindowStart = 1 , srcWindowStart = 1
, srcSelectedLine = Just 1 , srcSelectedLine = Just 1
, srcName = name , srcName = sourceWindowName
, srcWindowEnd = Nothing , srcWindowVerticalSpace = Nothing
} }
where where
lineVec = Vec.fromList (T.lines text) lineVec = Vec.fromList (T.lines text)