Allow resizing of panels

This allows the use of +/- to change the panel sizes, like
in PuDB.
This commit is contained in:
CrystalSplitter 2023-12-10 19:22:23 -08:00 committed by Jordan R AW
parent 17616a4df2
commit 9b632cb00d
4 changed files with 109 additions and 17 deletions

View File

@ -82,6 +82,14 @@ additional keybindings.
currently running. For example, it can display the current bindings, loaded
modules, and the current program trace.
----------
Navigation
----------
At any point in time, you can revert back to the Source Viewer panel with the
``<Esc>`` key, and you can always quit by hitting ``<Esc>`` in the Source Viewer
panel.
-----------
Keybindings
-----------
@ -100,6 +108,7 @@ Source Viewer
- ``Down``, ``j``: Move the cursor down. (``j`` and ``k`` from Vim keybinds).
- ``PgUp``: Move the source viewer one page up.
- ``PgDown``: Move the source viewer one page down.
- ``+``, ``-``: Increase/decrease the Info panel size.
- ``b``: Toggle breakpoint at current line. Not every line in a source file can
have a breakpoint placed on it.
- ``s``: Advance execution by one step. Same as the ``:step`` in GHCi.
@ -108,9 +117,9 @@ Source Viewer
- ``t``: Advance execution until next breakpoint under tracing. Same as
``:trace`` in GHCi.
****************
Live Interpreter
****************
***********************
Live Interpreter (REPL)
***********************
- ``Ctrl+x``: Toggle between the Source Viewer and the Live Interpreter
panels.
@ -119,4 +128,7 @@ Live Interpreter
- ``Down``: Scroll forward in time through the REPL command history.
- ``PgUp``: Scroll the Live Interpreter window one page up.
- ``PgDown``: Scroll the Live Interpreter window one page down.
- ``Ctrl+n``: Toggle scrolling mode.
- ``+``, ``-`` while in scrolling mode: Increase/decrease the live
panel size.
- ``<Enter>``: Enter a command to the REPL.

View File

@ -4,6 +4,11 @@ module AppState
( ActiveWindow (..)
, AppConfig (..)
, AppState (..)
, WidgetSizes
, changeInfoWidgetSize
, changeReplWidgetSize
, getInfoWidth
, getReplHeight
, appInterpState
, getSourceContents
, getSourceLineCount
@ -33,15 +38,29 @@ import AppTopLevel (AppName (..))
import Ghcid.Daemon (toggleBreakpointLine)
import qualified Ghcid.Daemon as Daemon
import qualified Loc
import qualified Util
data ActiveWindow = ActiveCodeViewport | ActiveLiveInterpreter | ActiveInfoWindow
deriving (Show, Eq, Ord)
{- | Size information of the current GHCiTUI main boxes.
type WindowSizes = [(ActiveWindow, (Maybe Int, Maybe Int))]
-}
data MaxState = NoMaxState | Maximised | Minimised
-- | Application state wrapper
-- | Size information of the current GHCiTUI main boxes.
data WidgetSizes = WidgetSizes
{ _wsInfoWidth :: !Int
, _wsInfoMaxState :: !MaxState
, _wsReplHeight :: !Int
, _wsReplMaxState :: !MaxState
}
{- | Application state wrapper.
Contains information about the UI and configuration. It also holds a
handle to the actual interpreter under the hood, but on the high level
it should not hold anything internal to GHCi or GHCiD.
Prefer to create this with 'makeInitialState'.
-}
data AppState n = AppState
{ interpState :: Daemon.InterpState ()
-- ^ The interpreter handle.
@ -61,6 +80,9 @@ data AppState n = AppState
-- ^ Currently selected line number. Resets back to 1.
, sourceMap :: Map.Map FilePath T.Text
-- ^ Mapping between source filepaths and their contents.
, _currentWidgetSizes :: WidgetSizes
-- ^ Current window/box/panel sizes (since it can change). Do not edit
-- directly.
, displayDebugConsoleLogs :: !Bool
-- ^ Whether to display debug Console logs.
, debugConsoleLogs :: [Text]
@ -95,6 +117,15 @@ appInterpState = Lens.lens _appInterpState (\x ais -> x{_appInterpState = ais})
liveEditor' :: Lens.Lens' (AppState n) (BE.Editor T.Text n)
liveEditor' = appInterpState . AIS.liveEditor
currentWidgetSizes :: Lens.Lens' (AppState n) WidgetSizes
currentWidgetSizes = Lens.lens _currentWidgetSizes (\x cws -> x{_currentWidgetSizes = cws})
wsInfoWidth :: Lens.Lens' WidgetSizes Int
wsInfoWidth = Lens.lens _wsInfoWidth (\x ipw -> x{_wsInfoWidth = ipw})
wsReplHeight :: Lens.Lens' WidgetSizes Int
wsReplHeight = Lens.lens _wsReplHeight (\x rh -> x{_wsReplHeight = rh})
-- | Write a debug log entry.
writeDebugLog :: T.Text -> AppState n -> AppState n
writeDebugLog lg s = s{debugConsoleLogs = lg : debugConsoleLogs s}
@ -155,6 +186,30 @@ getSourceContents s = s.selectedFile >>= (s.sourceMap Map.!?)
getSourceLineCount :: AppState n -> Maybe Int
getSourceLineCount s = length . T.lines <$> getSourceContents s
changeInfoWidgetSize :: Int -> AppState n -> AppState n
changeInfoWidgetSize amnt s =
Lens.set
(currentWidgetSizes . wsInfoWidth)
-- Do not let the min go too low (<=2), because this causes a memory leak in Brick?
(Util.clamp (10, 120) (getInfoWidth s + amnt))
s
changeReplWidgetSize :: Int -> AppState n -> AppState n
changeReplWidgetSize amnt s =
Lens.set
(currentWidgetSizes . wsReplHeight)
-- Do not let the min go too low, because the box disappears then.
(Util.clamp (1, 80) (getReplHeight s + amnt))
s
-- | Return the info box's desired width in character columns.
getInfoWidth :: AppState n -> Int
getInfoWidth = _wsInfoWidth . _currentWidgetSizes
-- | Return the REPL (interactive interpreter)'s box in lines.
getReplHeight :: AppState n -> Int
getReplHeight = _wsReplHeight . _currentWidgetSizes
-- | Initialise the state from the config.
makeInitialState
:: AppConfig
@ -199,5 +254,12 @@ makeInitialState appConfig target cwd = do
, selectedFile
, selectedLine = 1
, sourceMap = mempty
, _currentWidgetSizes =
WidgetSizes
{ _wsInfoWidth = 30
, _wsInfoMaxState = NoMaxState
, _wsReplHeight = 11 -- 10 plus 1 for the entry line.
, _wsReplMaxState = NoMaxState
}
, splashContents
}

View File

@ -28,6 +28,7 @@ import AppState
, liveEditor'
, makeInitialState
)
import qualified AppState
import AppTopLevel (AppName (..))
import qualified Events
import qualified Ghcid.Daemon as Daemon
@ -58,6 +59,7 @@ appDraw s =
else "Interpreter (Scrolling)"
)
-- For seeing the source code.
viewportBox :: B.Widget AppName
viewportBox =
B.borderWithLabel sourceLabel
@ -72,16 +74,16 @@ appDraw s =
Just h -> B.padBottom B.Max (w <=> B.hBorder <=> B.txt h)
_ -> w
-- For the REPL.
interpreterBox :: B.Widget AppName
interpreterBox =
B.borderWithLabel interpreterLabel
. B.vLimit (displayLimit + 1) -- Plus one for the current line.
. B.vLimit (AppState.getReplHeight s)
. B.withVScrollBars B.OnRight
. B.viewport LiveInterpreterViewport B.Vertical
$ previousOutput <=> lockToBottomOnViewLock promptLine
where
enableCursor = True
displayLimit = 10
previousOutput =
if null s.interpLogs
then B.emptyWidget
@ -119,7 +121,7 @@ appDraw s =
infoBox :: AppS -> B.Widget AppName
infoBox appState =
B.borderWithLabel (B.txt "Info")
. B.hLimit 30
. B.hLimit (AppState.getInfoWidth appState)
. B.padRight B.Max
. B.padBottom B.Max
$ bindingBox

View File

@ -38,10 +38,10 @@ handleEvent ev = do
-- | Handle events when the interpreter (live GHCi) is selected.
handleInterpreterEvent :: B.BrickEvent AppName e -> B.EventM AppName (AppState AppName) ()
handleInterpreterEvent ev =
handleInterpreterEvent ev = do
appState <- B.get
case ev of
B.VtyEvent (V.EvKey V.KEnter []) -> do
appState <- B.get
let cmd = T.strip (T.unlines (editorContents appState))
-- Actually run the command.
@ -70,7 +70,6 @@ handleInterpreterEvent ev =
B.invalidateCache
B.VtyEvent (V.EvKey (V.KChar '\t') []) -> do
-- Tab completion?
appState <- B.get
let cmd = T.strip (T.unlines (editorContents appState))
(newAppState1, _output) <-
runDaemon2
@ -94,7 +93,6 @@ handleInterpreterEvent ev =
<> (showT . AIS.historyPos . getAis $ s)
)
s
appState <- B.get
let appState' =
wDebug
. replaceCommandBufferWithHist -- Display the history.
@ -103,7 +101,6 @@ handleInterpreterEvent ev =
$ appState
B.put appState'
B.VtyEvent (V.EvKey V.KDown _) -> do
appState <- B.get
let wDebug s =
writeDebugLog
( "Handled Down; historyPos is "
@ -120,10 +117,22 @@ handleInterpreterEvent ev =
B.vScrollPage (B.viewportScroll LiveInterpreterViewport) B.Down
B.VtyEvent (V.EvKey V.KPageUp _) -> do
B.vScrollPage (B.viewportScroll LiveInterpreterViewport) B.Up
appState <- B.get
B.put (Lens.set (appInterpState . AIS.viewLock) False appState)
B.VtyEvent (V.EvKey (V.KChar 'n') [V.MCtrl]) -> do
-- Invert the viewLock.
B.put (Lens.over (appInterpState . AIS.viewLock) not appState)
-- While scrolling (viewLock disabled), allow resizing the live interpreter history.
B.VtyEvent (V.EvKey (V.KChar '+') [])
| not (appState ^. appInterpState . AIS.viewLock) -> do
B.put (AppState.changeReplWidgetSize 1 appState)
B.VtyEvent (V.EvKey (V.KChar '-') [])
| not (appState ^. appInterpState . AIS.viewLock) -> do
B.put (AppState.changeReplWidgetSize (-1) appState)
-- Actually handle keystrokes.
ev' -> do
appState <- B.get
-- When typing, bring us back down to the terminal.
B.put (Lens.set (appInterpState . AIS.viewLock) True appState)
-- Actually handle text input commands.
B.zoom liveEditor' $ BE.handleEditorEvent ev'
@ -192,6 +201,13 @@ handleViewportEvent (B.VtyEvent (V.EvKey key ms))
moveSelectedLineBy 1
| key `elem` [V.KUp, V.KChar 'k'] = do
moveSelectedLineBy (-1)
-- '+' and '-' move the middle border.
| key == V.KChar '+' && null ms = do
appState <- B.get
B.put (AppState.changeInfoWidgetSize 1 appState)
| key == V.KChar '-' && null ms = do
appState <- B.get
B.put (AppState.changeInfoWidgetSize (-1) appState)
| key == V.KPageDown = do
appState <- B.get
mViewport <- B.lookupViewport CodeViewport