Reorganise modules, clean up formatting

This moves the ghcitui libs which don't require Brick to ghcitui-core,
and the other library files to ghcitui-brick.
This commit is contained in:
CrystalSplitter 2024-01-14 22:20:47 -08:00 committed by Jordan R AW
parent 301446ee85
commit 4e533fe4bb
18 changed files with 298 additions and 252 deletions

View File

@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module AppConfig (AppConfig(..), defaultConfig, resolveStartupSplashPath) where
module AppConfig (AppConfig (..), defaultConfig, resolveStartupSplashPath) where
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
@ -31,6 +31,7 @@ data AppConfig = AppConfig
-- ^ Display the debug console on start up.
, getDebugLogPath :: !FilePath
, getVerbosity :: !Int
-- ^ Verbosity level.
, getStartupSplashPath :: !(Maybe FilePath)
, getCmd :: !T.Text
-- ^ Command to run to initialise the interpreter.

View File

@ -44,12 +44,13 @@ import qualified Lens.Micro as Lens
import AppConfig (AppConfig (..), resolveStartupSplashPath)
import qualified AppInterpState as AIS
import AppTopLevel (AppName (..))
import Ghcitui.Ghcid.Daemon (toggleBreakpointLine) -- Re-export
import qualified Ghcitui.Brick.SourceWindow as SourceWindow
import Ghcitui.Ghcid.Daemon (toggleBreakpointLine)
import qualified Ghcitui.Ghcid.Daemon as Daemon
import qualified Ghcitui.Ghcid.LogConfig as LogConfig
import qualified Ghcitui.Loc as Loc
import qualified SourceWindow
import qualified Util
import qualified Ghcitui.Util as Util
data ActiveWindow
= ActiveCodeViewport
@ -59,16 +60,10 @@ data ActiveWindow
| ActiveDialogHelp
deriving (Show, Eq, Ord)
data MaxState = NoMaxState
-- \| Maximised | Minimised
-- | Size information of the current GHCiTUI main boxes.
data WidgetSizes = WidgetSizes
{ _wsInfoWidth :: !Int
, _wsInfoMaxState :: !MaxState
, _wsReplHeight :: !Int
, _wsReplMaxState :: !MaxState
}
{- | Application state wrapper.
@ -152,8 +147,7 @@ selectedFile = _selectedFile
setSelectedFile :: (MonadIO m) => Maybe FilePath -> AppState n -> m (AppState n)
setSelectedFile mayFP appState =
if mayFP == _selectedFile appState
then
-- If we're selecting the same file again, do nothing.
then -- If we're selecting the same file again, do nothing.
pure appState
else do
-- Update the source map with the new file, and replace the window contents.
@ -340,9 +334,7 @@ makeInitialState appConfig target cwd = do
, _currentWidgetSizes =
WidgetSizes
{ _wsInfoWidth = 30
, _wsInfoMaxState = NoMaxState
, _wsReplHeight = 11 -- 10 plus 1 for the entry line.
, _wsReplMaxState = NoMaxState
}
, splashContents
, _sourceWindow = SourceWindow.mkSourcWindow SourceList ""

View File

@ -13,4 +13,4 @@ data AppName
| ModulesViewport
| TraceViewport
| SourceList
deriving (Eq, Show, Ord)
deriving (Eq, Show, Ord)

View File

@ -31,12 +31,12 @@ import qualified AppState
import AppTopLevel (AppName (..))
import qualified DrawSourceViewer
import qualified Events
import qualified Ghcitui.Brick.SourceWindow as SourceWindow
import qualified Ghcitui.Ghcid.Daemon as Daemon
import qualified Ghcitui.Loc as Loc
import qualified Ghcitui.NameBinding as NameBinding
import qualified Ghcitui.Util as Util
import qualified HelpText
import qualified SourceWindow
import qualified Util
-- | Alias for 'AppState AppName' convenience.
type AppS = AppState AppName
@ -316,7 +316,8 @@ brickApp =
-- | Start the Brick UI
launchBrick :: AppConfig.AppConfig -> T.Text -> FilePath -> IO ()
launchBrick conf target cwd = do
T.putStrLn $ "Starting up GHCiTUI with: '" <> AppConfig.getCmd conf <> "'..."
T.putStrLn $ "Starting up GHCiTUI with: `" <> AppConfig.getCmd conf <> "`..."
T.putStrLn "This can take a while..."
initialState <- makeInitialState conf target cwd
_ <- B.defaultMain brickApp initialState
T.putStrLn "GHCiTUI has shut down; have a nice day :)"

View File

@ -5,7 +5,7 @@ module DrawSourceViewer (drawSourceViewer) where
import qualified Brick as B
import qualified Brick.Widgets.Center as B
import Brick.Widgets.Core ((<+>), (<=>))
import Control.Error
import Control.Error (fromMaybe)
import Data.Function ((&))
import Data.Functor ((<&>))
import qualified Data.Text as T
@ -16,10 +16,10 @@ import Lens.Micro ((^.))
import AppState (AppState)
import qualified AppState
import AppTopLevel (AppName (..))
import qualified Ghcitui.Brick.SourceWindow as SourceWindow
import qualified Ghcitui.Ghcid.Daemon as Daemon
import qualified Ghcitui.Loc as Loc
import qualified SourceWindow
import qualified Util
import qualified Ghcitui.Util as Util
-- | Make the primary viewport widget.
drawSourceViewer :: AppState AppName -> B.Widget AppName
@ -95,7 +95,7 @@ drawSourceViewer' s sourceWindow = composedTogether
isSelectedLine lineno = Just lineno == sourceWindow ^. SourceWindow.srcSelectedLineL
composedTogether :: B.Widget AppName
composedTogether = SourceWindow.renderSourceWindow createWidget sourceWindow
composedTogether = SourceWindow.renderSourceWindow createWidget sourceWindow
where
createWidget lineno _old lineTxt =
styliseLine $ composedTogetherHelper lineno lineTxt
@ -152,13 +152,13 @@ drawSourceViewer' s sourceWindow = composedTogether
, gutterDigitWidth = Util.getNumDigits $ sourceWindowLength sourceWindow
, isSelected = isSelectedLine lineno
}
where
breakpoints :: [Int]
breakpoints =
maybe
mempty
(\f -> Daemon.getBpInFile f (AppState.interpState s))
(AppState.selectedFile s)
where
breakpoints :: [Int]
breakpoints =
maybe
mempty
(\f -> Daemon.getBpInFile f (AppState.interpState s))
(AppState.selectedFile s)
originalLookupLineNo :: Int
originalLookupLineNo =

View File

@ -1,5 +1,5 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE NamedFieldPuns #-}
module Events (handleEvent, handleCursorPosition) where
@ -19,10 +19,10 @@ import AppState
import AppTopLevel
( AppName (..)
)
import qualified Ghcitui.Brick.SourceWindow as SourceWindow
import qualified Ghcitui.Ghcid.Daemon as Daemon
import qualified Ghcitui.Loc as Loc
import qualified SourceWindow
import Util (showT)
import Ghcitui.Util (showT)
-- | Handle any Brick event and update the state.
handleEvent :: B.BrickEvent AppName e -> B.EventM AppName (AppState AppName) ()
@ -250,7 +250,6 @@ handleSrcWindowEvent (B.VtyEvent (V.EvKey key ms))
moveSelectedLineby 1
| key `elem` [V.KUp, V.KChar 'k'] = do
moveSelectedLineby (-1)
| key == V.KPageDown = do
scrollPage SourceWindow.Down
| key == V.KPageUp = do
@ -287,7 +286,7 @@ moveSelectedLineby movAmnt = do
-- These two lines need to be re-rendered.
invalidateCachedLine oldLineno
invalidateCachedLine newLineno
B.put $ writeDebugLog ("Selected line is: " <> Util.showT newLineno) movedAppState
B.put $ writeDebugLog ("Selected line is: " <> showT newLineno) movedAppState
scrollPage :: SourceWindow.ScrollDir -> B.EventM AppName (AppState AppName) ()
scrollPage dir = do
@ -342,7 +341,7 @@ invalidateLineCache = B.invalidateCache
-- | Run a DaemonIO function on a given interpreter state, within an EventM monad.
runDaemon
:: (Ord n)
:: (Ord n)
=> (Daemon.InterpState () -> Daemon.DaemonIO (Daemon.InterpState ()))
-> AppState n
-> B.EventM n m (AppState n)
@ -360,7 +359,9 @@ runDaemon2
-> AppState n
-> B.EventM n m (AppState n, a)
runDaemon2 f appState = do
(interp, x) <- liftIO $ (Daemon.run . f) appState.interpState >>= \case
(interp, x) <-
liftIO $
(Daemon.run . f) appState.interpState >>= \case
Right out -> pure out
Left er -> error $ show er
newState <- selectPausedLine appState{interpState = interp}
@ -431,4 +432,4 @@ handleDialogHelp _ = pure ()
-- | Stop the TUI.
quit :: AppState n -> B.EventM n s ()
quit appState = liftIO (Daemon.quit appState.interpState) >> B.halt
quit appState = liftIO (Daemon.quit appState.interpState) >> B.halt

View File

@ -7,137 +7,138 @@ import Data.String (IsString)
-- import Data.FileEmbed
helpText :: (IsString a) => a
helpText = "\
\GHCITUI MANUAL() GHCITUI MANUAL()\n\
\\n\
\NAME\n\
\ GHCiTUI MANUAL -\n\
\\n\
\CLI SYNOPSIS\n\
\ Usage: ghcitui [OPTIONS] [TARGET]\n\
\\n\
\ ghcitui: A TUI interface for GHCi\n\
\\n\
\ Available options:\n\
\ -h,--help Show this help text\n\
\ -d,--debug-console Display the debug console\n\
\ -c,--cmd CMD Command to start the internal\n\
\ interpreter\n\
\ -C,--workdir DIR Set working dir\n\
\\n\
\STARTING AND STOPPING\n\
\ Starting\n\
\ GHCiTUI runs a REPL in the current directory by default. By default,\n\
\ it launches cabal repl.\n\
\\n\
\ $ cd your/cabal/project/root/directory\n\
\ $ ghcitui\n\
\\n\
\ You can specify another starting directory with the -C <DIR> flag.\n\
\\n\
\ $ ghcitui -C some/other/directory\n\
\\n\
\ Stopping\n\
\ To quit, press <ESC> or q while in the code viewport panel to quit.\n\
\ While not in the code viewport panel, you may press <ESC> to get to\n\
\ the viewport panel.\n\
\\n\
\LAYOUT\n\
\ GHCiTUI is an in-terminal viewer for GHCi. The TUI is broken up into\n\
\ three primary panels, with some additional auxiliary panels for spe\n\
\ cial use cases:\n\
\\n\
\ \n\
\ Info \n\
\ \n\
\ Source Viewer \n\
\ \n\
\ \n\
\ \n\
\ \n\
\ Live Interpreter \n\
\ \n\
\ \n\
\\n\
\ Source Viewer: This panel shows source code. You can step, continue,\n\
\ and toggle breakpoints among other operations in this panel.\n\
\\n\
\ Live Interpreter: This panel shows the GHCi/REPL passthrough. You can\n\
\ enter expressions and GHCi commands here like you would normally,\n\
\ with some additional keybindings.\n\
\\n\
\ Info: This panel displays miscellaneous info about whatever is cur\n\
\ rently running. For example, it can display the current bindings,\n\
\ loaded modules, and the current program trace.\n\
\\n\
\NAVIGATION\n\
\ At any point in time, you can revert back to the Source Viewer panel\n\
\ with the <Esc> key, and you can always quit by hitting <Esc> in the\n\
\ Source Viewer panel.\n\
\\n\
\KEYBINDINGS\n\
\ At this time, keybindings are hardcoded. This will hopefully change\n\
\ in the future with a keybinding configuration file.\n\
\\n\
\ Source Viewer\n\
\ Ctrl+x: Toggle between the Source Viewer and the Live Interpreter\n\
\ panels.\n\
\\n\
\ <Esc>, q: Quit.\n\
\\n\
\ <Up>, k: Move the cursor up. (j and k from Vim keybinds)\n\
\\n\
\ <Down>, j: Move the cursor down. (j and k from Vim keybinds).\n\
\\n\
\ <PgUp>: Move the source viewer one page up.\n\
\\n\
\ <PgDown>: Move the source viewer one page down.\n\
\\n\
\ +, -: Increase/decrease the Info panel size.\n\
\\n\
\ b: Toggle breakpoint at current line. Not every line in a source\n\
\ file can have a breakpoint placed on it.\n\
\\n\
\ s: Advance execution by one step. Same as the :step in GHCi.\n\
\\n\
\ c: Advance execution until next breakpoint. Same as :continue in\n\
\ GHCi.\n\
\\n\
\ t: Advance execution until next breakpoint under tracing. Same as\n\
\ :trace in GHCi.\n\
\\n\
\ Live Interpreter (REPL)\n\
\ Ctrl+x: Toggle between the Source Viewer and the Live Interpreter\n\
\ panels.\n\
\\n\
\ <Esc>: Switch to Source Viewer.\n\
\\n\
\ <Up>: Scroll back in time through the REPL command history.\n\
\\n\
\ <Down>: Scroll forward in time through the REPL command history.\n\
\\n\
\ <PgUp>: Scroll the Live Interpreter window one page up.\n\
\\n\
\ <PgDown>: Scroll the Live Interpreter window one page down.\n\
\\n\
\ Ctrl+n: Toggle scrolling mode.\n\
\\n\
\ +, - while in scrolling mode: Increase/decrease the live panel\n\
\ size.\n\
\\n\
\ <Enter>: Enter a command to the REPL.\n\
\\n\
\ Modules\n\
\ Ctrl+x: Switch to the Live Interpreter.\n\
\\n\
\ <Esc>: Switch to Source Viewer.\n\
\\n\
\ <Up>, k: Move the module selection up.\n\
\\n\
\ <Down>, j: Move the module selection down.\n\
\\n\
\ +, -: Increase/decrease the info panel size.\n\
\\n\
\ <Enter>, o: Open the selected module.\n\
\\n\
\ GHCITUI MANUAL()"
helpText =
"\
\GHCITUI MANUAL() GHCITUI MANUAL()\n\
\\n\
\NAME\n\
\ GHCiTUI MANUAL -\n\
\\n\
\CLI SYNOPSIS\n\
\ Usage: ghcitui [OPTIONS] [TARGET]\n\
\\n\
\ ghcitui: A TUI interface for GHCi\n\
\\n\
\ Available options:\n\
\ -h,--help Show this help text\n\
\ -d,--debug-console Display the debug console\n\
\ -c,--cmd CMD Command to start the internal\n\
\ interpreter\n\
\ -C,--workdir DIR Set working dir\n\
\\n\
\STARTING AND STOPPING\n\
\ Starting\n\
\ GHCiTUI runs a REPL in the current directory by default. By default,\n\
\ it launches cabal repl.\n\
\\n\
\ $ cd your/cabal/project/root/directory\n\
\ $ ghcitui\n\
\\n\
\ You can specify another starting directory with the -C <DIR> flag.\n\
\\n\
\ $ ghcitui -C some/other/directory\n\
\\n\
\ Stopping\n\
\ To quit, press <ESC> or q while in the code viewport panel to quit.\n\
\ While not in the code viewport panel, you may press <ESC> to get to\n\
\ the viewport panel.\n\
\\n\
\LAYOUT\n\
\ GHCiTUI is an in-terminal viewer for GHCi. The TUI is broken up into\n\
\ three primary panels, with some additional auxiliary panels for spe\n\
\ cial use cases:\n\
\\n\
\ \n\
\ Info \n\
\ \n\
\ Source Viewer \n\
\ \n\
\ \n\
\ \n\
\ \n\
\ Live Interpreter \n\
\ \n\
\ \n\
\\n\
\ Source Viewer: This panel shows source code. You can step, continue,\n\
\ and toggle breakpoints among other operations in this panel.\n\
\\n\
\ Live Interpreter: This panel shows the GHCi/REPL passthrough. You can\n\
\ enter expressions and GHCi commands here like you would normally,\n\
\ with some additional keybindings.\n\
\\n\
\ Info: This panel displays miscellaneous info about whatever is cur\n\
\ rently running. For example, it can display the current bindings,\n\
\ loaded modules, and the current program trace.\n\
\\n\
\NAVIGATION\n\
\ At any point in time, you can revert back to the Source Viewer panel\n\
\ with the <Esc> key, and you can always quit by hitting <Esc> in the\n\
\ Source Viewer panel.\n\
\\n\
\KEYBINDINGS\n\
\ At this time, keybindings are hardcoded. This will hopefully change\n\
\ in the future with a keybinding configuration file.\n\
\\n\
\ Source Viewer\n\
\ Ctrl+x: Toggle between the Source Viewer and the Live Interpreter\n\
\ panels.\n\
\\n\
\ <Esc>, q: Quit.\n\
\\n\
\ <Up>, k: Move the cursor up. (j and k from Vim keybinds)\n\
\\n\
\ <Down>, j: Move the cursor down. (j and k from Vim keybinds).\n\
\\n\
\ <PgUp>: Move the source viewer one page up.\n\
\\n\
\ <PgDown>: Move the source viewer one page down.\n\
\\n\
\ +, -: Increase/decrease the Info panel size.\n\
\\n\
\ b: Toggle breakpoint at current line. Not every line in a source\n\
\ file can have a breakpoint placed on it.\n\
\\n\
\ s: Advance execution by one step. Same as the :step in GHCi.\n\
\\n\
\ c: Advance execution until next breakpoint. Same as :continue in\n\
\ GHCi.\n\
\\n\
\ t: Advance execution until next breakpoint under tracing. Same as\n\
\ :trace in GHCi.\n\
\\n\
\ Live Interpreter (REPL)\n\
\ Ctrl+x: Toggle between the Source Viewer and the Live Interpreter\n\
\ panels.\n\
\\n\
\ <Esc>: Switch to Source Viewer.\n\
\\n\
\ <Up>: Scroll back in time through the REPL command history.\n\
\\n\
\ <Down>: Scroll forward in time through the REPL command history.\n\
\\n\
\ <PgUp>: Scroll the Live Interpreter window one page up.\n\
\\n\
\ <PgDown>: Scroll the Live Interpreter window one page down.\n\
\\n\
\ Ctrl+n: Toggle scrolling mode.\n\
\\n\
\ +, - while in scrolling mode: Increase/decrease the live panel\n\
\ size.\n\
\\n\
\ <Enter>: Enter a command to the REPL.\n\
\\n\
\ Modules\n\
\ Ctrl+x: Switch to the Live Interpreter.\n\
\\n\
\ <Esc>: Switch to Source Viewer.\n\
\\n\
\ <Up>, k: Move the module selection up.\n\
\\n\
\ <Down>, j: Move the module selection down.\n\
\\n\
\ +, -: Increase/decrease the info panel size.\n\
\\n\
\ <Enter>, o: Open the selected module.\n\
\\n\
\ GHCITUI MANUAL()"

View File

@ -3,8 +3,8 @@
module Main where
import qualified Paths_ghcitui as CabalPkg
import qualified Data.Version
import qualified Paths_ghcitui as CabalPkg
import Control.Applicative (many)
import qualified Data.Text as T
@ -42,7 +42,7 @@ parseOpts = do
( Opt.long "daemon-log"
<> Opt.help daemonLogHelp
<> Opt.metavar "LOGFILE"
<> Opt.value "/tmp/ghcitui.log"
<> Opt.value "stderr"
)
cmd <-
Opt.strOption
@ -71,7 +71,7 @@ parseOpts = do
"File path for debugging daemon logs."
<> " Used with -v."
<> " Setting this to 'stdout' or 'stderr' sends logs to each, respectively."
<> " Defaults to /tmp/ghcitui.log."
<> " Defaults to 'stderr'"
-- | The cabal package version.
programVersion :: String
@ -98,4 +98,4 @@ main = do
where
programName = "ghcitui"
programDescription = Opt.progDesc (programName <> ": A TUI interface for GHCi")
parserInfo = Opt.info (Opt.helper <*> parseOpts) (Opt.fullDesc <> programDescription)
parserInfo = Opt.info (Opt.helper <*> parseOpts) (Opt.fullDesc <> programDescription)

View File

@ -4,14 +4,19 @@ version: 0.1.0.0
synopsis: A Terminal User Interface (TUI) for GHCi
description:
A visual interface for GHCi debug mode inside the terminal.
A terminal user interface for GHCi debug mode.
.
Features:
* A source view window, with debug keybindings.
* Live variable bindings.
* Live loaded modules.
* Visible trace history.
* An GHCi session in the current context.
.
* A source view window, with debug keybindings.
.
* Live variable bindings.
.
* Live loaded modules.
.
* Visible trace history.
.
* An GHCi session in the current context.
bug-reports: https://github.com/CrystalSplitter/ghcitui
license: BSD-3-Clause
@ -19,7 +24,7 @@ license-file: LICENSE
author: Jordan 'CrystalSplitter' R AW
maintainer: crystal@crystalwobsite.gay
copyright: Jordan R AW
category: Debug
category: Debug
extra-source-files: CHANGELOG.md
, LICENSE
, MANUAL.rst
@ -35,21 +40,21 @@ executable ghcitui
, brick
, containers >= 0.6.7 && < 0.8
, errors ^>= 2.3.0
, ghcitui-lib
, ghcitui-core
, ghcitui-brick
, microlens ^>= 0.4.13.1
, microlens-th ^>= 0.4.3.14
, optparse-applicative ^>= 0.18.1.0
, safe ^>= 0.3.19
, text ^>= 2.0.2
, text-zipper ^>= 0.13
, vector ^>= 0.13.1.0
, vty ^>= 5.38
, word-wrap ^>= 0.5
, vector ^>= 0.13.1.0
hs-source-dirs: app
other-modules: BrickUI
, AppState
, AppTopLevel
, Util
, AppInterpState
, AppConfig
, DrawSourceViewer
@ -57,7 +62,6 @@ executable ghcitui
, HelpText
-- Cabal autogen module for package version info.
, Paths_ghcitui
, SourceWindow
ghc-options: -rtsopts
-threaded
-Wall
@ -75,8 +79,8 @@ executable ghcitui
MonoLocalBinds
NamedFieldPuns
library ghcitui-lib
hs-source-dirs: lib
library ghcitui-core
hs-source-dirs: lib/ghcitui-core
build-depends: base >= 4.17 && < 5
, array ^>= 0.5.4.0
, containers >= 0.6.7 && < 0.8
@ -109,6 +113,27 @@ library ghcitui-lib
MonoLocalBinds
NamedFieldPuns
library ghcitui-brick
hs-source-dirs: lib/ghcitui-brick
build-depends: base >= 4.17 && < 5
, brick
, containers >= 0.6.7 && < 0.8
, errors ^>= 2.3.0
, ghcitui-core
, microlens ^>= 0.4.13.1
, microlens-th ^>= 0.4.3.14
, text ^>= 2.0.2
, vector ^>= 0.13.1.0
exposed-modules: Ghcitui.Brick.SourceWindow
ghc-options: -Wall
-Wcompat
-Wincomplete-record-updates
-Wpartial-fields
-Wredundant-constraints
default-language: Haskell2010
default-extensions: OverloadedStrings
MonoLocalBinds
NamedFieldPuns
test-suite spec
hs-source-dirs: test
@ -116,7 +141,7 @@ test-suite spec
type: exitcode-stdio-1.0
build-depends: base >= 4.17 && < 5
, hspec ^>= 2.11.5
, ghcitui-lib
, ghcitui-core
other-modules: LocSpec
, UtilSpec
default-language: Haskell2010

View File

@ -1,25 +0,0 @@
module Ghcitui.Util (showT, splitBy, linesToText) where
import Data.Text (Text, breakOn, drop, length, pack)
import Prelude hiding (drop, length)
-- | Split text based on a delimiter.
splitBy
:: Text
-- ^ Delimeter.
-> Text
-- ^ Text to split on.
-> [Text]
splitBy "" source = [source]
splitBy delim source =
case breakOn delim source of
(l, "") -> [l]
(l, r) -> l : splitBy delim (drop (length delim) r)
-- | Convert Strings to Text.
linesToText :: [String] -> Text
linesToText = pack . Prelude.unlines
-- | 'show' but to Text.
showT :: (Show a) => a -> Text
showT = pack . show

View File

@ -1,8 +1,9 @@
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module SourceWindow
module Ghcitui.Brick.SourceWindow
( SourceWindow (srcElements)
-- * Creation
@ -26,7 +27,7 @@ module SourceWindow
, srcSelectedLineL
, srcWindowStartL
-- * Misc
-- * Misc
, srcWindowLength
) where
@ -38,14 +39,20 @@ import Lens.Micro ((^.))
import qualified Lens.Micro as Lens
import Lens.Micro.TH (makeLensesFor)
import qualified Util
import qualified Ghcitui.Util as Util
data SourceWindow n e = SourceWindow
{ srcElements :: !(Vec.Vector e)
-- | Hold data regarding a code source viewing window.
data SourceWindow name elem = SourceWindow
{ srcElements :: !(Vec.Vector elem)
-- ^ The actual entries for each source window.
, srcWindowStart :: !Int
-- ^ The starting position of the window, as a line number (1-indexed).
-- No lines before this line number is rendered.
, srcWindowEnd :: !(Maybe Int)
, srcName :: !n
, srcName :: !name
-- ^ The name of the window.
, srcSelectedLine :: !(Maybe Int)
-- ^ The currently selected line in the window.
}
deriving (Show)
@ -58,11 +65,15 @@ makeLensesFor
]
''SourceWindow
-- | Render a 'SourceWindow' into a Brick 'B.Widget'.
renderSourceWindow
:: (Ord n)
=> (Int -> Bool -> e -> B.Widget n)
-- ^ Render function.
-> SourceWindow n e
-- ^ 'SourceWindow' to render.
-> B.Widget n
-- ^ The newly created widget.
renderSourceWindow func srcW = B.reportExtent (srcName srcW) (B.Widget B.Greedy B.Greedy renderM)
where
renderM = do
@ -85,6 +96,10 @@ renderSourceWindow func srcW = B.reportExtent (srcName srcW) (B.Widget B.Greedy
remainingElements = srcWindowLength srcW - startZeroIdx
elems = srcElements srcW
{- | Return the length of the full contents of the source code stored in the window.
Note, does NOT return the current length/height/size of the rendered widget.
-}
srcWindowLength :: SourceWindow n e -> Int
srcWindowLength = Vec.length . srcElements
@ -122,6 +137,7 @@ scrollTo pos srcW@SourceWindow{srcWindowEnd = Just windowEnd} =
<$> srcSelectedLine srcW
scrollTo _ srcW = srcW
-- | Direction to scroll by.
data ScrollDir = Up | Down deriving (Eq, Show)
-- | Scroll by a full page in a direction.
@ -139,7 +155,14 @@ srcWindowScrollPage' dir srcW =
where
windowEnd = fromMaybe 1 $ srcWindowEnd srcW
setSelectionTo :: (Ord n) => Int -> SourceWindow n e -> B.EventM n m (SourceWindow n e)
-- | Set the selection to a given position, and scroll the window accordingly.
setSelectionTo
:: (Ord n)
=> Int
-- ^ Line number to set the selection to (1-indexed)
-> SourceWindow n e
-- ^ Source window to update.
-> B.EventM n m (SourceWindow n e)
setSelectionTo pos srcW@SourceWindow{srcSelectedLine = Just sl, srcWindowEnd = Just end} =
if pos < srcWindowStart srcW || pos > end
then srcWindowMoveSelectionBy delta srcW
@ -150,7 +173,13 @@ setSelectionTo pos srcW@SourceWindow{srcSelectedLine = Just sl, srcWindowEnd = J
setSelectionTo _ srcW = pure srcW
-- | Move the selected line by a given amount.
srcWindowMoveSelectionBy :: (Ord n) => Int -> SourceWindow n e -> B.EventM n m (SourceWindow n e)
srcWindowMoveSelectionBy
:: (Ord n)
=> Int
-- ^ Delta to move the selected line.
-> SourceWindow n e
-- ^ Source window to update.
-> B.EventM n m (SourceWindow n e)
srcWindowMoveSelectionBy amnt sw = do
srcW' <- updateSrcWindowEnd sw
case srcWindowEnd srcW' of
@ -185,9 +214,9 @@ mkSourcWindow
-- ^ Name for the source window.
-> T.Text
-- ^ Text contents of the source window (to be split up).
-> SourceWindow.SourceWindow n T.Text
-> SourceWindow n T.Text
mkSourcWindow name text =
SourceWindow.SourceWindow
SourceWindow
{ srcElements = lineVec
, srcWindowStart = 1
, srcSelectedLine = Just 1
@ -195,4 +224,4 @@ mkSourcWindow name text =
, srcWindowEnd = Nothing
}
where
lineVec = Vec.fromList (T.lines text)
lineVec = Vec.fromList (T.lines text)

View File

@ -19,7 +19,7 @@ module Ghcitui.Ghcid.Daemon
-- * Startup and shutdown
, startup
, StartupConfig(..)
, StartupConfig (..)
, quit
-- * Base operations with the daemon
@ -50,7 +50,7 @@ module Ghcitui.Ghcid.Daemon
, run
, DaemonIO
, DaemonError
, LogOutput(..)
, LogOutput (..)
) where
import Control.Error
@ -62,14 +62,14 @@ import qualified Data.Text.IO as T
import qualified Language.Haskell.Ghcid as Ghcid
import System.IO (stderr)
import Ghcitui.Ghcid.LogConfig (LogLevel (..), LogOutput (..))
import qualified Ghcitui.Ghcid.ParseContext as ParseContext
import Ghcitui.Ghcid.StartupConfig (StartupConfig)
import qualified Ghcitui.Ghcid.StartupConfig as StartupConfig
import qualified Ghcitui.Loc as Loc
import qualified Ghcitui.NameBinding as NameBinding
import Ghcitui.Util (showT)
import qualified Ghcitui.Util as Util
import Ghcitui.Ghcid.LogConfig (LogLevel(..), LogOutput(..))
import Ghcitui.Ghcid.StartupConfig (StartupConfig)
import qualified Ghcitui.Ghcid.StartupConfig as StartupConfig
data InterpState a = InterpState
{ _ghci :: Ghcid.Ghci
@ -111,7 +111,7 @@ instance Show (InterpState a) where
in msg
{- | Create an empty/starting interpreter state.
Usually you don't want to call this directly. Instead use 'startup'.
Usually you don't want to call this directly. Instead use 'startup'.
-}
emptyInterpreterState :: (Monoid a) => Ghcid.Ghci -> StartupConfig -> InterpState a
emptyInterpreterState ghci startupConfig =
@ -132,14 +132,15 @@ emptyInterpreterState ghci startupConfig =
-- | Reset anything context-based in a 'InterpState'.
contextReset :: (Monoid a) => InterpState a -> InterpState a
contextReset state = state {
func = Nothing
, pauseLoc = Nothing
, stack = mempty
, bindings = Right mempty
, status = Right mempty
, traceHist = mempty
}
contextReset state =
state
{ func = Nothing
, pauseLoc = Nothing
, stack = mempty
, bindings = Right mempty
, status = Right mempty
, traceHist = mempty
}
-- | Append a string to the interpreter's history.
appendExecHist :: T.Text -> InterpState a -> InterpState a
@ -278,8 +279,7 @@ stepInto
stepInto func = execMuted (":step " <> func)
{- | Analogue to @:history@.
Returns either the 'Left' error messager, or 'Right': list the trace breakpoints.
Returns either a 'Left' error message, or a 'Right' list of trace breakpoints.
-}
history :: InterpState a -> DaemonIO (InterpState a, Either T.Text [T.Text])
history state = do
@ -309,8 +309,8 @@ load :: (Monoid a) => FilePath -> InterpState a -> DaemonIO (InterpState a)
load filepath = execMuted (T.pack $ ":load " <> filepath)
{- | Execute an arbitrary command, as if it was directly written in GHCi.
It is unlikely you want to call this directly, and instead want to call
one of the wrapped functions or 'execMuted' or 'execCleaned'.
It is unlikely you want to call this directly, and instead want to call
one of the wrapped functions or 'execMuted' or 'execCleaned'.
-}
exec :: (Monoid a) => T.Text -> InterpState a -> ExceptT DaemonError IO (InterpState a, [T.Text])
exec cmd state@InterpState{_ghci} = do
@ -476,7 +476,7 @@ logDebug msg state =
where
output = logOutput state
--Log a message at the Error level.
-- Log a message at the Error level.
logError :: (MonadIO m) => T.Text -> InterpState a -> m ()
logError msg state =
liftIO $ do
@ -514,7 +514,7 @@ data DaemonError
deriving (Eq, Show)
{- | An IO operation that can fail into a DaemonError.
Execute them to IO through 'run'.
Execute them to IO through 'run'.
-}
type DaemonIO r = ExceptT DaemonError IO r

View File

@ -4,4 +4,4 @@ module Ghcitui.Ghcid.LogConfig where
newtype LogLevel = LogLevel Int deriving (Eq, Ord, Show)
-- | Determines where the daemon logs are written.
data LogOutput = LogOutputStdOut | LogOutputStdErr | LogOutputFile FilePath deriving (Show)
data LogOutput = LogOutputStdOut | LogOutputStdErr | LogOutputFile FilePath deriving (Show)

View File

@ -1,9 +1,11 @@
module Ghcitui.Ghcid.StartupConfig (StartupConfig(..)) where
module Ghcitui.Ghcid.StartupConfig (StartupConfig (..)) where
import Ghcitui.Ghcid.LogConfig (LogLevel, LogOutput)
-- | Configuration passed during Daemon 'startup'
data StartupConfig = StartupConfig
{ logLevel :: !LogLevel
-- ^ How much do we want to log?
, logOutput :: !LogOutput
}
-- ^ Where do we log?
}

View File

@ -1,9 +1,28 @@
module Util (getNumDigits, formatDigits, clamp, showT) where
module Ghcitui.Util (showT, splitBy, linesToText, clamp, getNumDigits, formatDigits) where
import Data.Text (Text, pack)
import Data.Text (Text, breakOn, drop, length, pack)
import Prelude hiding (drop, length)
-- | Split text based on a delimiter.
splitBy
:: Text
-- ^ Delimeter.
-> Text
-- ^ Text to split on.
-> [Text]
splitBy "" source = [source]
splitBy delim source =
case breakOn delim source of
(l, "") -> [l]
(l, r) -> l : splitBy delim (drop (length delim) r)
-- | Convert Strings to Text.
linesToText :: [String] -> Text
linesToText = pack . Prelude.unlines
-- | 'show' but to Text.
showT :: (Show a) => a -> Text
showT = Data.Text.pack . show
showT = pack . show
-- Return the number of digits in a given integral
getNumDigits :: (Integral a) => a -> Int