Compare commits

...

10 Commits

Author SHA1 Message Date
Julian Ospald 1793fa43cf
Fix for screen readers 2024-03-23 15:10:55 +08:00
Luis Morillo b375398416 makes ctrl+c the shourtcut to exit menus + fix trailing new line in editor 2024-03-17 09:47:03 +01:00
Luis Morillo 04b29b0b98 fix regression #875 and build system 2024-03-16 16:27:04 +01:00
Luis Morillo 255f7c8eac Remove trailing white space 2024-03-16 16:14:24 +01:00
Luis Morillo 80a6c67cf3 Execute action only if inputs are valid + better UX 2024-03-13 18:14:37 +01:00
Luis Morillo cee4a0d610 untested compile HLS 2024-03-13 18:14:37 +01:00
Luis Morillo 9c4e64baf1 untested compileGHC IOAction 2024-03-13 18:14:37 +01:00
Luis Morillo 0b6e9289fc Visuals for compiling HLS 2024-03-13 18:14:37 +01:00
Luis Morillo cd8d13ff2b Advance Install menu implements functionality. 2024-03-13 18:14:37 +01:00
Luis Morillo 40f94fa016 Better aesth for context menu 2024-03-13 18:14:37 +01:00
16 changed files with 735 additions and 183 deletions

View File

@ -334,6 +334,7 @@ library ghcup-tui
GHCup.Brick.Widgets.Menus.Context GHCup.Brick.Widgets.Menus.Context
GHCup.Brick.Widgets.Menus.AdvanceInstall GHCup.Brick.Widgets.Menus.AdvanceInstall
GHCup.Brick.Widgets.Menus.CompileGHC GHCup.Brick.Widgets.Menus.CompileGHC
GHCup.Brick.Widgets.Menus.CompileHLS
GHCup.Brick.Actions GHCup.Brick.Actions
GHCup.Brick.App GHCup.Brick.App
GHCup.Brick.BrickState GHCup.Brick.BrickState

View File

@ -18,7 +18,7 @@ import GHCup.Types.Optics ( getDirs, getPlatformReq )
import GHCup.Types hiding ( LeanAppState(..) ) import GHCup.Types hiding ( LeanAppState(..) )
import GHCup.Utils import GHCup.Utils
import GHCup.OptParse.Common (logGHCPostRm) import GHCup.OptParse.Common (logGHCPostRm)
import GHCup.Prelude ( decUTF8Safe ) import GHCup.Prelude ( decUTF8Safe, runBothE' )
import GHCup.Prelude.Logger import GHCup.Prelude.Logger
import GHCup.Prelude.Process import GHCup.Prelude.Process
import GHCup.Prompts import GHCup.Prompts
@ -75,10 +75,15 @@ import Optics.Operators ((.~),(%~))
import Optics.Getter (view) import Optics.Getter (view)
import Optics.Optic ((%)) import Optics.Optic ((%))
import Optics ((^.), to) import Optics ((^.), to)
import qualified GHCup.Brick.Widgets.Menus.CompileHLS as CompileHLS
import Control.Concurrent (threadDelay)
import qualified GHCup.GHC as GHC
import qualified GHCup.OptParse.Common as OptParse
import qualified GHCup.HLS as HLS
{- Core Logic. {- Core Logic.
This module defines the IO actions we can execute within the Brick App: This module defines the IO actions we can execute within the Brick App:
- Install - Install
@ -111,7 +116,7 @@ constructList appD settings =
selectBy :: Tool -> (ListResult -> Bool) -> BrickInternalState -> BrickInternalState selectBy :: Tool -> (ListResult -> Bool) -> BrickInternalState -> BrickInternalState
selectBy tool predicate internal_state = selectBy tool predicate internal_state =
let new_focus = F.focusSetCurrent (Singular tool) (view sectionListFocusRingL internal_state) let new_focus = F.focusSetCurrent (Singular tool) (view sectionListFocusRingL internal_state)
tool_lens = sectionL (Singular tool) tool_lens = sectionL (Singular tool)
in internal_state in internal_state
& sectionListFocusRingL .~ new_focus & sectionListFocusRingL .~ new_focus
& tool_lens %~ L.listMoveTo 0 -- We move to 0 first & tool_lens %~ L.listMoveTo 0 -- We move to 0 first
@ -173,12 +178,19 @@ withIOAction action = do
pure (updateList data' as) pure (updateList data' as)
Left err -> throwIO $ userError err Left err -> throwIO $ userError err
install' :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m) installWithOptions :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> (Int, ListResult) => AdvanceInstall.InstallOptions
-> (Int, ListResult)
-> m (Either String ()) -> m (Either String ())
install' (_, ListResult {..}) = do installWithOptions opts (_, ListResult {..}) = do
AppState { ghcupInfo = GHCupInfo { _ghcupDownloads = dls }} <- ask AppState { ghcupInfo = GHCupInfo { _ghcupDownloads = dls }} <- ask
let
misolated = opts ^. AdvanceInstall.isolateDirL
shouldIsolate = maybe GHCupInternal IsolateDir (opts ^. AdvanceInstall.isolateDirL)
shouldForce = opts ^. AdvanceInstall.forceInstallL
shouldSet = opts ^. AdvanceInstall.instSetL
extraArgs = opts ^. AdvanceInstall.addConfArgsL
v = GHCTargetVersion lCross lVer
let run = let run =
runResourceT runResourceT
. runE . runE
@ -208,6 +220,7 @@ install' (_, ListResult {..}) = do
, UnsupportedSetupCombo , UnsupportedSetupCombo
, DistroNotFound , DistroNotFound
, NoCompatibleArch , NoCompatibleArch
, InstallSetError
] ]
run (do run (do
@ -216,20 +229,81 @@ install' (_, ListResult {..}) = do
dirs <- lift getDirs dirs <- lift getDirs
case lTool of case lTool of
GHC -> do GHC -> do
let vi = getVersionInfo (GHCTargetVersion lCross lVer) GHC dls let vi = getVersionInfo v GHC dls
liftE $ installGHCBin (GHCTargetVersion lCross lVer) GHCupInternal False [] $> (vi, dirs, ce) case opts ^. AdvanceInstall.instBindistL of
Nothing -> do
liftE $
runBothE'
(installGHCBin v shouldIsolate shouldForce extraArgs)
(when (shouldSet && isNothing misolated) (liftE $ void $ setGHC v SetGHCOnly Nothing))
pure (vi, dirs, ce)
Just uri -> do
liftE $
runBothE'
(installGHCBindist
(DownloadInfo uri (Just $ RegexDir "ghc-.*") "" Nothing Nothing)
v
shouldIsolate
shouldForce
extraArgs)
(when (shouldSet && isNothing misolated) (liftE $ void $ setGHC v SetGHCOnly Nothing))
pure (vi, dirs, ce)
Cabal -> do Cabal -> do
let vi = getVersionInfo (GHCTargetVersion lCross lVer) Cabal dls let vi = getVersionInfo v Cabal dls
liftE $ installCabalBin lVer GHCupInternal False $> (vi, dirs, ce) case opts ^. AdvanceInstall.instBindistL of
Nothing -> do
liftE $
runBothE'
(installCabalBin lVer shouldIsolate shouldForce)
(when (shouldSet && isNothing misolated) (liftE $ void $ setCabal lVer))
pure (vi, dirs, ce)
Just uri -> do
liftE $
runBothE'
(installCabalBindist (DownloadInfo uri Nothing "" Nothing Nothing) lVer shouldIsolate shouldForce)
(when (shouldSet && isNothing misolated) (liftE $ void $ setCabal lVer))
pure (vi, dirs, ce)
GHCup -> do GHCup -> do
let vi = snd <$> getLatest dls GHCup let vi = snd <$> getLatest dls GHCup
liftE $ upgradeGHCup Nothing False False $> (vi, dirs, ce) liftE $ upgradeGHCup Nothing False False $> (vi, dirs, ce)
HLS -> do HLS -> do
let vi = getVersionInfo (GHCTargetVersion lCross lVer) HLS dls let vi = getVersionInfo v HLS dls
liftE $ installHLSBin lVer GHCupInternal False $> (vi, dirs, ce) case opts ^. AdvanceInstall.instBindistL of
Nothing -> do
liftE $
runBothE'
(installHLSBin lVer shouldIsolate shouldForce)
(when (shouldSet && isNothing misolated) (liftE $ void $ setHLS lVer SetHLSOnly Nothing))
pure (vi, dirs, ce)
Just uri -> do
liftE $
runBothE'
(installHLSBindist
(DownloadInfo uri (if isWindows then Nothing else Just (RegexDir "haskell-language-server-*")) "" Nothing Nothing)
lVer
shouldIsolate
shouldForce)
(when (shouldSet && isNothing misolated) (liftE $ void $ setHLS lVer SetHLSOnly Nothing))
pure (vi, dirs, ce)
Stack -> do Stack -> do
let vi = getVersionInfo (GHCTargetVersion lCross lVer) Stack dls let vi = getVersionInfo v Stack dls
liftE $ installStackBin lVer GHCupInternal False $> (vi, dirs, ce) case opts ^. AdvanceInstall.instBindistL of
Nothing -> do
liftE $
runBothE'
(installStackBin lVer shouldIsolate shouldForce)
(when (shouldSet && isNothing misolated) (liftE $ void $ setStack lVer))
pure (vi, dirs, ce)
Just uri -> do
liftE $
runBothE'
(installStackBindist (DownloadInfo uri Nothing "" Nothing Nothing) lVer shouldIsolate shouldForce)
(when (shouldSet && isNothing misolated) (liftE $ void $ setStack lVer))
pure (vi, dirs, ce)
) )
>>= \case >>= \case
VRight (vi, Dirs{..}, Just ce) -> do VRight (vi, Dirs{..}, Just ce) -> do
@ -256,6 +330,9 @@ install' (_, ListResult {..}) = do
VLeft e -> pure $ Left $ prettyHFError e <> "\n" VLeft e -> pure $ Left $ prettyHFError e <> "\n"
<> "Also check the logs in ~/.ghcup/logs" <> "Also check the logs in ~/.ghcup/logs"
install' :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> (Int, ListResult) -> m (Either String ())
install' = installWithOptions (AdvanceInstall.InstallOptions Nothing False Nothing False [])
set' :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m) set' :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> (Int, ListResult) => (Int, ListResult)
@ -384,6 +461,175 @@ changelog' (_, ListResult {..}) = do
Right _ -> pure $ Right () Right _ -> pure $ Right ()
Left e -> pure $ Left $ prettyHFError e Left e -> pure $ Left $ prettyHFError e
compileGHC :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> CompileGHC.CompileGHCOptions -> (Int, ListResult) -> m (Either String ())
compileGHC compopts (_, lr@ListResult{lTool = GHC, ..}) = do
appstate <- ask
let run =
runResourceT
. runE @'[ AlreadyInstalled
, BuildFailed
, DigestError
, ContentLengthError
, GPGError
, DownloadFailed
, GHCupSetError
, NoDownload
, NotFoundInPATH
, PatchFailed
, UnknownArchive
, TarDirDoesNotExist
, NotInstalled
, DirNotEmpty
, ArchiveResult
, FileDoesNotExistError
, HadrianNotFound
, InvalidBuildConfig
, ProcessError
, CopyError
, BuildFailed
, UninstallFailed
, MergeFileTreeError
]
compileResult <- run (do
AppState { ghcupInfo = GHCupInfo { _ghcupDownloads = dls }} <- ask
let vi = getVersionInfo (mkTVer lVer) GHC dls
forM_ (_viPreCompile =<< vi) $ \msg -> do
logInfo msg
logInfo
"...waiting for 5 seconds, you can still abort..."
liftIO $ threadDelay 5000000 -- for compilation, give the user a sec to intervene
targetVer <- liftE $ GHCup.compileGHC
(GHC.SourceDist lVer)
(compopts ^. CompileGHC.crossTarget)
(compopts ^. CompileGHC.overwriteVer)
(compopts ^. CompileGHC.bootstrapGhc)
(compopts ^. CompileGHC.jobs)
(compopts ^. CompileGHC.buildConfig)
(compopts ^. CompileGHC.patches)
(compopts ^. CompileGHC.addConfArgs)
(compopts ^. CompileGHC.buildFlavour)
(compopts ^. CompileGHC.buildSystem)
(maybe GHCupInternal IsolateDir $ compopts ^. CompileGHC.isolateDir)
AppState { ghcupInfo = GHCupInfo { _ghcupDownloads = dls2 }} <- ask
let vi2 = getVersionInfo targetVer GHC dls2
when
(compopts ^. CompileGHC.setCompile)
(liftE . void $ GHCup.setGHC targetVer SetGHCOnly Nothing)
pure (vi2, targetVer)
)
case compileResult of
VRight (vi, tv) -> do
logInfo "GHC successfully compiled and installed"
forM_ (_viPostInstall =<< vi) $ \msg -> logInfo msg
liftIO $ putStr (T.unpack $ tVerToText tv)
pure $ Right ()
VLeft (V (AlreadyInstalled _ v)) -> do
logWarn $
"GHC ver " <> prettyVer v <> " already installed, remove it first to reinstall"
pure $ Right ()
VLeft (V (DirNotEmpty fp)) -> do
logError $
"Install directory " <> T.pack fp <> " is not empty."
pure $ Right ()
VLeft err@(V (BuildFailed tmpdir _)) -> do
case keepDirs (appstate & settings) of
Never -> logError $ T.pack $ prettyHFError err
_ -> logError $ T.pack (prettyHFError err) <> "\n"
<> "Check the logs at " <> T.pack (fromGHCupPath $ appstate & dirs & logsDir)
<> " and the build directory "
<> T.pack tmpdir <> " for more clues." <> "\n"
<> "Make sure to clean up " <> T.pack tmpdir <> " afterwards."
pure $ Right ()
VLeft e -> do
logError $ T.pack $ prettyHFError e
pure $ Right ()
-- This is the case when the tool is not GHC... which should be impossible but,
-- it exhaustes pattern matches
compileGHC _ (_, ListResult{lTool = _}) = pure (Right ())
compileHLS :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> CompileHLS.CompileHLSOptions -> (Int, ListResult) -> m (Either String ())
compileHLS compopts (_, lr@ListResult{lTool = HLS, ..}) = do
appstate <- ask
let run =
runResourceT
. runE @'[ AlreadyInstalled
, BuildFailed
, DigestError
, ContentLengthError
, GPGError
, DownloadFailed
, GHCupSetError
, NoDownload
, NotFoundInPATH
, PatchFailed
, UnknownArchive
, TarDirDoesNotExist
, TagNotFound
, DayNotFound
, NextVerNotFound
, NoToolVersionSet
, NotInstalled
, DirNotEmpty
, ArchiveResult
, UninstallFailed
, MergeFileTreeError
]
compileResult <- run (do
AppState { ghcupInfo = GHCupInfo { _ghcupDownloads = dls }} <- ask
let vi = getVersionInfo (mkTVer lVer) GHC dls
forM_ (_viPreCompile =<< vi) $ \msg -> do
logInfo msg
logInfo
"...waiting for 5 seconds, you can still abort..."
liftIO $ threadDelay 5000000 -- for compilation, give the user a sec to intervene
ghcs <-
liftE $ forM (compopts ^. CompileHLS.targetGHCs)
(\ghc -> fmap (_tvVersion . fst) . OptParse.fromVersion (Just ghc) $ GHC)
targetVer <- liftE $ GHCup.compileHLS
(HLS.SourceDist lVer)
ghcs
(compopts ^. CompileHLS.jobs)
(compopts ^. CompileHLS.overwriteVer)
(maybe GHCupInternal IsolateDir $ compopts ^. CompileHLS.isolateDir)
(compopts ^. CompileHLS.cabalProject)
(compopts ^. CompileHLS.cabalProjectLocal)
(compopts ^. CompileHLS.updateCabal)
(compopts ^. CompileHLS.patches)
(compopts ^. CompileHLS.cabalArgs)
AppState { ghcupInfo = GHCupInfo { _ghcupDownloads = dls2 }} <- ask
let vi2 = getVersionInfo (mkTVer targetVer) GHC dls2
when
(compopts ^. CompileHLS.setCompile)
(liftE . void $ GHCup.setHLS targetVer SetHLSOnly Nothing)
pure (vi2, targetVer)
)
case compileResult of
VRight (vi, tv) -> do
logInfo "HLS successfully compiled and installed"
forM_ (_viPostInstall =<< vi) $ \msg -> logInfo msg
liftIO $ putStr (T.unpack $ prettyVer tv)
pure $ Right ()
VLeft err@(V (BuildFailed tmpdir _)) -> do
case keepDirs (appstate & settings) of
Never -> logError $ T.pack $ prettyHFError err
_ -> logError $ T.pack (prettyHFError err) <> "\n"
<> "Check the logs at " <> T.pack (fromGHCupPath $ appstate & dirs & logsDir)
<> " and the build directory "
<> T.pack tmpdir <> " for more clues." <> "\n"
<> "Make sure to clean up " <> T.pack tmpdir <> " afterwards."
pure $ Right ()
VLeft e -> do
logError $ T.pack $ prettyHFError e
pure $ Right ()
-- This is the case when the tool is not HLS... which should be impossible but,
-- it exhaustes pattern matches
compileHLS _ (_, ListResult{lTool = _}) = pure (Right ())
settings' :: IORef AppState settings' :: IORef AppState
{-# NOINLINE settings' #-} {-# NOINLINE settings' #-}
@ -429,7 +675,7 @@ getAppData mgi = runExceptT $ do
lV <- listVersions Nothing [] False True (Nothing, Nothing) lV <- listVersions Nothing [] False True (Nothing, Nothing)
pure $ BrickData (reverse lV) pure $ BrickData (reverse lV)
-- --
keyHandlers :: KeyBindings keyHandlers :: KeyBindings
-> [ ( KeyCombination -> [ ( KeyCombination
@ -454,23 +700,25 @@ keyHandlers KeyBindings {..} =
, (KeyCombination Vty.KEnter [], const "advance options", createMenuforTool ) , (KeyCombination Vty.KEnter [], const "advance options", createMenuforTool )
] ]
where where
createMenuforTool = do createMenuforTool = do
e <- use (appState % to sectionListSelectedElement) e <- use (appState % to sectionListSelectedElement)
let exitKey = KeyCombination (Vty.KChar 'c') [Vty.MCtrl]
case e of case e of
Nothing -> pure () Nothing -> pure ()
Just (_, r) -> do Just (_, r) -> do
-- Create new menus -- Create new menus
contextMenu .= ContextMenu.create r bQuit contextMenu .= ContextMenu.create r exitKey
advanceInstallMenu .= AdvanceInstall.create bQuit advanceInstallMenu .= AdvanceInstall.create exitKey
compileGHCMenu .= CompileGHC.create bQuit compileGHCMenu .= CompileGHC.create exitKey
compileHLSMenu .= CompileHLS.create exitKey
-- Set mode to context -- Set mode to context
mode .= ContextPanel mode .= ContextPanel
pure () pure ()
--hideShowHandler' :: (BrickSettings -> Bool) -> (BrickSettings -> Bool) -> m () --hideShowHandler' :: (BrickSettings -> Bool) -> (BrickSettings -> Bool) -> m ()
hideShowHandler' f = do hideShowHandler' f = do
app_settings <- use appSettings app_settings <- use appSettings
let let
vers = f app_settings vers = f app_settings
newAppSettings = app_settings & Common.showAllVersions .~ vers newAppSettings = app_settings & Common.showAllVersions .~ vers
ad <- use appData ad <- use appData

View File

@ -25,7 +25,7 @@ module GHCup.Brick.App where
import qualified GHCup.Brick.Actions as Actions import qualified GHCup.Brick.Actions as Actions
import qualified GHCup.Brick.Attributes as Attributes import qualified GHCup.Brick.Attributes as Attributes
import GHCup.Brick.BrickState (BrickState (..), advanceInstallMenu, appKeys, appSettings, appState, contextMenu, mode, compileGHCMenu) import GHCup.Brick.BrickState (BrickState (..), advanceInstallMenu, appKeys, appSettings, appState, contextMenu, mode, compileGHCMenu, compileHLSMenu)
import GHCup.Brick.Common (Mode (..), Name (..)) import GHCup.Brick.Common (Mode (..), Name (..))
import qualified GHCup.Brick.Common as Common import qualified GHCup.Brick.Common as Common
import qualified GHCup.Brick.Widgets.KeyInfo as KeyInfo import qualified GHCup.Brick.Widgets.KeyInfo as KeyInfo
@ -65,6 +65,8 @@ import Optics.Optic ((%))
import Optics.State (use) import Optics.State (use)
import Optics.State.Operators ((.=)) import Optics.State.Operators ((.=))
import qualified GHCup.Brick.Widgets.Menus.CompileGHC as CompileGHC import qualified GHCup.Brick.Widgets.Menus.CompileGHC as CompileGHC
import qualified GHCup.Brick.Widgets.Menus.CompileHLS as CompileHLS
import Control.Monad (when)
app :: AttrMap -> AttrMap -> App BrickState () Name app :: AttrMap -> AttrMap -> App BrickState () Name
app attrs dimAttrs = app attrs dimAttrs =
@ -77,12 +79,12 @@ app attrs dimAttrs =
drawUI :: AttrMap -> BrickState -> [Widget Name] drawUI :: AttrMap -> BrickState -> [Widget Name]
drawUI dimAttrs st = drawUI dimAttrs st =
let let
footer = Brick.withAttr Attributes.helpAttr footer = Brick.withAttr Attributes.helpAttr
. Brick.txtWrap . Brick.txtWrap
. T.pack . T.pack
. foldr1 (\x y -> x <> " " <> y) . foldr1 (\x y -> x <> " " <> y)
. fmap (\(KeyCombination key mods, pretty_setting, _) . fmap (\(KeyCombination key mods, pretty_setting, _)
-> intercalate "+" (Common.showKey key : (Common.showMod <$> mods)) <> ":" <> pretty_setting (st ^. appSettings) -> intercalate "+" (Common.showKey key : (Common.showMod <$> mods)) <> ":" <> pretty_setting (st ^. appSettings)
) )
$ Actions.keyHandlers (st ^. appKeys) $ Actions.keyHandlers (st ^. appKeys)
@ -94,13 +96,13 @@ drawUI dimAttrs st =
ContextPanel -> [ContextMenu.draw (st ^. contextMenu), navg] ContextPanel -> [ContextMenu.draw (st ^. contextMenu), navg]
AdvanceInstallPanel -> [AdvanceInstall.draw (st ^. advanceInstallMenu), navg] AdvanceInstallPanel -> [AdvanceInstall.draw (st ^. advanceInstallMenu), navg]
CompileGHCPanel -> [CompileGHC.draw (st ^. compileGHCMenu), navg] CompileGHCPanel -> [CompileGHC.draw (st ^. compileGHCMenu), navg]
CompileHLSPanel -> [CompileHLS.draw (st ^. compileHLSMenu), navg]
-- | On q, go back to navigation.
-- | On q, go back to navigation.
-- On Enter, to go to tutorial -- On Enter, to go to tutorial
keyInfoHandler :: BrickEvent Name e -> EventM Name BrickState () keyInfoHandler :: BrickEvent Name e -> EventM Name BrickState ()
keyInfoHandler ev = case ev of keyInfoHandler ev = case ev of
VtyEvent (Vty.EvKey (Vty.KChar 'q') _ ) -> mode .= Navigation VtyEvent (Vty.EvKey (Vty.KChar 'c') [Vty.MCtrl]) -> mode .= Navigation
VtyEvent (Vty.EvKey Vty.KEnter _ ) -> mode .= Tutorial VtyEvent (Vty.EvKey Vty.KEnter _ ) -> mode .= Tutorial
_ -> pure () _ -> pure ()
@ -108,67 +110,75 @@ keyInfoHandler ev = case ev of
tutorialHandler :: BrickEvent Name e -> EventM Name BrickState () tutorialHandler :: BrickEvent Name e -> EventM Name BrickState ()
tutorialHandler ev = tutorialHandler ev =
case ev of case ev of
VtyEvent (Vty.EvKey (Vty.KChar 'q') _ ) -> mode .= Navigation VtyEvent (Vty.EvKey (Vty.KChar 'c') [Vty.MCtrl]) -> mode .= Navigation
_ -> pure () _ -> pure ()
-- | Tab/Arrows to navigate. -- | Tab/Arrows to navigate.
navigationHandler :: BrickEvent Name e -> EventM Name BrickState () navigationHandler :: BrickEvent Name e -> EventM Name BrickState ()
navigationHandler ev = do navigationHandler ev = do
AppState { keyBindings = kb } <- liftIO $ readIORef Actions.settings' AppState { keyBindings = kb } <- liftIO $ readIORef Actions.settings'
case ev of case ev of
inner_event@(VtyEvent (Vty.EvKey key _)) -> inner_event@(VtyEvent (Vty.EvKey key mods)) ->
case find (\(key', _, _) -> key' == KeyCombination key []) (Actions.keyHandlers kb) of case find (\(key', _, _) -> key' == KeyCombination key mods) (Actions.keyHandlers kb) of
Just (_, _, handler) -> handler Just (_, _, handler) -> handler
Nothing -> void $ Common.zoom appState $ Navigation.handler inner_event Nothing -> void $ Common.zoom appState $ Navigation.handler inner_event
inner_event -> Common.zoom appState $ Navigation.handler inner_event inner_event -> Common.zoom appState $ Navigation.handler inner_event
contextMenuHandler :: BrickEvent Name e -> EventM Name BrickState () contextMenuHandler :: BrickEvent Name e -> EventM Name BrickState ()
contextMenuHandler ev = do contextMenuHandler ev = do
ctx <- use contextMenu ctx <- use contextMenu
let focusedElement = ctx ^. Menu.menuFocusRingL % to F.focusGetCurrent let focusedElement = ctx ^. Menu.menuFocusRingL % to F.focusGetCurrent
buttons = ctx ^. Menu.menuButtonsL
(KeyCombination exitKey mods) = ctx ^. Menu.menuExitKeyL (KeyCombination exitKey mods) = ctx ^. Menu.menuExitKeyL
case (ev, focusedElement) of case (ev, focusedElement) of
(_ , Nothing) -> pure () (_ , Nothing) -> pure ()
(VtyEvent (Vty.EvKey k m), Just n) (VtyEvent (Vty.EvKey k m), Just n) | k == exitKey && m == mods -> mode .= Navigation
| k == exitKey
&& m == mods
&& n `elem` [Menu.fieldName button | button <- buttons]
-> mode .= Navigation
(VtyEvent (Vty.EvKey Vty.KEnter []), Just (Common.MenuElement Common.AdvanceInstallButton) ) -> mode .= Common.AdvanceInstallPanel (VtyEvent (Vty.EvKey Vty.KEnter []), Just (Common.MenuElement Common.AdvanceInstallButton) ) -> mode .= Common.AdvanceInstallPanel
(VtyEvent (Vty.EvKey Vty.KEnter []), Just (Common.MenuElement Common.CompilieButton) ) -> mode .= Common.CompileGHCPanel (VtyEvent (Vty.EvKey Vty.KEnter []), Just (Common.MenuElement Common.CompileGHCButton) ) -> mode .= Common.CompileGHCPanel
(VtyEvent (Vty.EvKey Vty.KEnter []), Just (Common.MenuElement Common.CompileHLSButton) ) -> mode .= Common.CompileHLSPanel
_ -> Common.zoom contextMenu $ ContextMenu.handler ev _ -> Common.zoom contextMenu $ ContextMenu.handler ev
-- --
advanceInstallHandler :: BrickEvent Name e -> EventM Name BrickState () advanceInstallHandler :: BrickEvent Name e -> EventM Name BrickState ()
advanceInstallHandler ev = do advanceInstallHandler ev = do
ctx <- use advanceInstallMenu ctx <- use advanceInstallMenu
let focusedElement = ctx ^. Menu.menuFocusRingL % to F.focusGetCurrent let focusedElement = ctx ^. Menu.menuFocusRingL % to F.focusGetCurrent
buttons = ctx ^. Menu.menuButtonsL
(KeyCombination exitKey mods) = ctx ^. Menu.menuExitKeyL (KeyCombination exitKey mods) = ctx ^. Menu.menuExitKeyL
case (ev, focusedElement) of case (ev, focusedElement) of
(_ , Nothing) -> pure () (_ , Nothing) -> pure ()
(VtyEvent (Vty.EvKey k m), Just n) (VtyEvent (Vty.EvKey k m), Just n) | k == exitKey && m == mods -> mode .= ContextPanel
| k == exitKey (VtyEvent (Vty.EvKey Vty.KEnter []), Just (MenuElement Common.OkButton)) -> do
&& m == mods let iopts = ctx ^. Menu.menuStateL
&& n `elem` [Menu.fieldName button | button <- buttons] Actions.withIOAction $ Actions.installWithOptions iopts
-> mode .= ContextPanel
_ -> Common.zoom advanceInstallMenu $ AdvanceInstall.handler ev _ -> Common.zoom advanceInstallMenu $ AdvanceInstall.handler ev
compileGHCHandler :: BrickEvent Name e -> EventM Name BrickState () compileGHCHandler :: BrickEvent Name e -> EventM Name BrickState ()
compileGHCHandler ev = do compileGHCHandler ev = do
ctx <- use compileGHCMenu ctx <- use compileGHCMenu
let focusedElement = ctx ^. Menu.menuFocusRingL % to F.focusGetCurrent let focusedElement = ctx ^. Menu.menuFocusRingL % to F.focusGetCurrent
buttons = ctx ^. Menu.menuButtonsL
(KeyCombination exitKey mods) = ctx ^. Menu.menuExitKeyL (KeyCombination exitKey mods) = ctx ^. Menu.menuExitKeyL
case (ev, focusedElement) of case (ev, focusedElement) of
(_ , Nothing) -> pure () (_ , Nothing) -> pure ()
(VtyEvent (Vty.EvKey k m), Just n) (VtyEvent (Vty.EvKey k m), Just n) | k == exitKey && m == mods -> mode .= ContextPanel
| k == exitKey (VtyEvent (Vty.EvKey Vty.KEnter []), Just (MenuElement Common.OkButton)) -> do
&& m == mods let iopts = ctx ^. Menu.menuStateL
&& n `elem` [Menu.fieldName button | button <- buttons] when (Menu.isValidMenu ctx)
-> mode .= ContextPanel (Actions.withIOAction $ Actions.compileGHC iopts)
_ -> Common.zoom compileGHCMenu $ CompileGHC.handler ev _ -> Common.zoom compileGHCMenu $ CompileGHC.handler ev
compileHLSHandler :: BrickEvent Name e -> EventM Name BrickState ()
compileHLSHandler ev = do
ctx <- use compileHLSMenu
let focusedElement = ctx ^. Menu.menuFocusRingL % to F.focusGetCurrent
(KeyCombination exitKey mods) = ctx ^. Menu.menuExitKeyL
case (ev, focusedElement) of
(_ , Nothing) -> pure ()
(VtyEvent (Vty.EvKey k m), Just n) | k == exitKey && m == mods -> mode .= ContextPanel
(VtyEvent (Vty.EvKey Vty.KEnter []), Just (MenuElement Common.OkButton)) -> do
let iopts = ctx ^. Menu.menuStateL
when (Menu.isValidMenu ctx)
(Actions.withIOAction $ Actions.compileHLS iopts)
_ -> Common.zoom compileHLSMenu $ CompileHLS.handler ev
eventHandler :: BrickEvent Name e -> EventM Name BrickState () eventHandler :: BrickEvent Name e -> EventM Name BrickState ()
eventHandler ev = do eventHandler ev = do
m <- use mode m <- use mode
@ -179,3 +189,4 @@ eventHandler ev = do
ContextPanel -> contextMenuHandler ev ContextPanel -> contextMenuHandler ev
AdvanceInstallPanel -> advanceInstallHandler ev AdvanceInstallPanel -> advanceInstallHandler ev
CompileGHCPanel -> compileGHCHandler ev CompileGHCPanel -> compileGHCHandler ev
CompileHLSPanel -> compileHLSHandler ev

View File

@ -46,10 +46,8 @@ defaultAttributes no_color = Brick.attrMap
where where
withForeColor | no_color = const withForeColor | no_color = const
| otherwise = Vty.withForeColor | otherwise = Vty.withForeColor
withBackColor | no_color = \attr _ -> attr `Vty.withStyle` Vty.reverseVideo withBackColor | no_color = \attr _ -> attr `Vty.withStyle` Vty.reverseVideo
| otherwise = Vty.withBackColor | otherwise = Vty.withBackColor
withStyle = Vty.withStyle withStyle = Vty.withStyle

View File

@ -14,15 +14,15 @@
{-# LANGUAGE InstanceSigs #-} {-# LANGUAGE InstanceSigs #-}
{- {-
This module contains the BrickState. One could be tempted to include this data structure in GHCup.Brick.Common, This module contains the BrickState. One could be tempted to include this data structure in GHCup.Brick.Common,
but it is better to make a separated module in order to avoid cyclic dependencies. but it is better to make a separated module in order to avoid cyclic dependencies.
This happens because the BrickState is sort of a container for all widgets, This happens because the BrickState is sort of a container for all widgets,
but widgets depends on common functionality, hence: but widgets depends on common functionality, hence:
BrickState `depends on` Widgets.XYZ `depends on` Common BrickState `depends on` Widgets.XYZ `depends on` Common
The linear relation above breaks if BrickState is defined in Common. The linear relation above breaks if BrickState is defined in Common.
-} -}
@ -35,6 +35,7 @@ import GHCup.Brick.Widgets.Menus.Context (ContextMenu)
import GHCup.Brick.Widgets.Menus.AdvanceInstall (AdvanceInstallMenu) import GHCup.Brick.Widgets.Menus.AdvanceInstall (AdvanceInstallMenu)
import GHCup.Brick.Widgets.Menus.CompileGHC (CompileGHCMenu) import GHCup.Brick.Widgets.Menus.CompileGHC (CompileGHCMenu)
import Optics.TH (makeLenses) import Optics.TH (makeLenses)
import GHCup.Brick.Widgets.Menus.CompileHLS (CompileHLSMenu)
data BrickState = BrickState data BrickState = BrickState
@ -44,6 +45,7 @@ data BrickState = BrickState
, _contextMenu :: ContextMenu , _contextMenu :: ContextMenu
, _advanceInstallMenu :: AdvanceInstallMenu , _advanceInstallMenu :: AdvanceInstallMenu
, _compileGHCMenu :: CompileGHCMenu , _compileGHCMenu :: CompileGHCMenu
, _compileHLSMenu :: CompileHLSMenu
, _appKeys :: KeyBindings , _appKeys :: KeyBindings
, _mode :: Mode , _mode :: Mode
} }

View File

@ -45,7 +45,8 @@ module GHCup.Brick.Common (
, TargetGhcEditBox, BootstrapGhcEditBox, JobsEditBox, BuildConfigEditBox , TargetGhcEditBox, BootstrapGhcEditBox, JobsEditBox, BuildConfigEditBox
, PatchesEditBox, CrossTargetEditBox, AddConfArgsEditBox, OvewrwiteVerEditBox , PatchesEditBox, CrossTargetEditBox, AddConfArgsEditBox, OvewrwiteVerEditBox
, BuildFlavourEditBox, BuildSystemEditBox, OkButton, AdvanceInstallButton , BuildFlavourEditBox, BuildSystemEditBox, OkButton, AdvanceInstallButton
, CompilieButton , CompileGHCButton, CompileHLSButton, CabalProjectEditBox
, CabalProjectLocalEditBox, UpdateCabalCheckBox
) ) where ) ) where
import GHCup.List ( ListResult ) import GHCup.List ( ListResult )
@ -75,8 +76,10 @@ pattern OkButton :: ResourceId
pattern OkButton = ResourceId 0 pattern OkButton = ResourceId 0
pattern AdvanceInstallButton :: ResourceId pattern AdvanceInstallButton :: ResourceId
pattern AdvanceInstallButton = ResourceId 100 pattern AdvanceInstallButton = ResourceId 100
pattern CompilieButton :: ResourceId pattern CompileGHCButton :: ResourceId
pattern CompilieButton = ResourceId 101 pattern CompileGHCButton = ResourceId 101
pattern CompileHLSButton :: ResourceId
pattern CompileHLSButton = ResourceId 102
pattern UrlEditBox :: ResourceId pattern UrlEditBox :: ResourceId
pattern UrlEditBox = ResourceId 1 pattern UrlEditBox = ResourceId 1
@ -110,7 +113,15 @@ pattern BuildFlavourEditBox = ResourceId 14
pattern BuildSystemEditBox :: ResourceId pattern BuildSystemEditBox :: ResourceId
pattern BuildSystemEditBox = ResourceId 15 pattern BuildSystemEditBox = ResourceId 15
-- | Name data type. Uniquely identifies each widget in the TUI. pattern CabalProjectEditBox :: ResourceId
pattern CabalProjectEditBox = ResourceId 16
pattern CabalProjectLocalEditBox :: ResourceId
pattern CabalProjectLocalEditBox = ResourceId 17
pattern UpdateCabalCheckBox :: ResourceId
pattern UpdateCabalCheckBox = ResourceId 18
-- | Name data type. Uniquely identifies each widget in the TUI.
-- some constructors might end up unused, but still is a good practise -- some constructors might end up unused, but still is a good practise
-- to have all of them defined, just in case -- to have all of them defined, just in case
data Name = AllTools -- ^ The main list widget data Name = AllTools -- ^ The main list widget
@ -118,8 +129,8 @@ data Name = AllTools -- ^ The main list widget
| KeyInfoBox -- ^ The text box widget with action informacion | KeyInfoBox -- ^ The text box widget with action informacion
| TutorialBox -- ^ The tutorial widget | TutorialBox -- ^ The tutorial widget
| ContextBox -- ^ The resource for Context Menu | ContextBox -- ^ The resource for Context Menu
| CompileGHCBox -- ^ The resource for CompileGHC Menu | CompileGHCBox -- ^ The resource for CompileGHC Menu
| AdvanceInstallBox -- ^ The resource for AdvanceInstall Menu | AdvanceInstallBox -- ^ The resource for AdvanceInstall Menu
| MenuElement ResourceId -- ^ Each element in a Menu. Resources must not be share for visible | MenuElement ResourceId -- ^ Each element in a Menu. Resources must not be share for visible
-- Menus, but MenuA and MenuB can share resources if they both are -- Menus, but MenuA and MenuB can share resources if they both are
-- invisible, or just one of them is visible. -- invisible, or just one of them is visible.
@ -131,8 +142,9 @@ data Mode = Navigation
| KeyInfo | KeyInfo
| Tutorial | Tutorial
| ContextPanel | ContextPanel
| AdvanceInstallPanel | AdvanceInstallPanel
| CompileGHCPanel | CompileGHCPanel
| CompileHLSPanel
deriving (Eq, Show, Ord) deriving (Eq, Show, Ord)
installedSign :: String installedSign :: String
@ -183,7 +195,7 @@ frontwardLayer layer_name =
. Brick.withBorderStyle Border.unicode . Brick.withBorderStyle Border.unicode
. Border.borderWithLabel (Brick.txt layer_name) . Border.borderWithLabel (Brick.txt layer_name)
-- I refuse to give this a type signature. -- I refuse to give this a type signature.
-- | Given a lens, zoom on it. It is needed because Brick uses microlens but GHCup uses optics. -- | Given a lens, zoom on it. It is needed because Brick uses microlens but GHCup uses optics.
zoom l = Brick.zoom (toLensVL l) zoom l = Brick.zoom (toLensVL l)

View File

@ -9,7 +9,7 @@
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
{- {-
A very simple information-only widget with no handler. A very simple information-only widget with no handler.
-} -}
module GHCup.Brick.Widgets.KeyInfo where module GHCup.Brick.Widgets.KeyInfo where
@ -20,7 +20,7 @@ import qualified GHCup.Brick.Common as Common
import Brick import Brick
( Padding(Max), ( Padding(Max),
Widget(..), Widget(..),
(<+>), (<+>),
(<=>)) (<=>))
import qualified Brick import qualified Brick
@ -69,4 +69,4 @@ draw KeyBindings {..} =
] ]
] ]
] ]
<=> Brick.hBox [Brick.txt "Press q to return to Navigation" <+> Brick.padRight Brick.Max (Brick.txt " ") <+> Brick.txt "Press Enter to go to the Tutorial"] <=> Brick.hBox [Brick.txt "Press c+ctrl to return to Navigation" <+> Brick.padRight Brick.Max (Brick.txt " ") <+> Brick.txt "Press Enter to go to the Tutorial"]

View File

@ -34,9 +34,9 @@ An input (type FieldInput) consist in
b) a validator function b) a validator function
c) a handler and a renderer c) a handler and a renderer
We have to use existential types to achive a composable API since every FieldInput has a different We have to use existential types to achive a composable API since every FieldInput has a different
internal type, and every MenuField has a different Lens. For example: internal type, and every MenuField has a different Lens. For example:
- The menu state is a record (MyRecord {uri: URI, flag : Bool}) - The menu state is a record (MyRecord {uri: URI, flag : Bool})
- Then, there are two MenuField: - Then, there are two MenuField:
- One MenuField has (Lens' MyRecord URI) and the other has (Lens' MyRecord Bool) - One MenuField has (Lens' MyRecord URI) and the other has (Lens' MyRecord Bool)
- The MenuFields has FieldInputs with internal state Text and Bool, respectively - The MenuFields has FieldInputs with internal state Text and Bool, respectively
@ -93,7 +93,7 @@ idFormatter = const id
-- | An error message -- | An error message
type ErrorMessage = T.Text type ErrorMessage = T.Text
data ErrorStatus = Valid | Invalid ErrorMessage data ErrorStatus = Valid | Invalid ErrorMessage deriving (Eq)
-- | A lens which does nothing. Usefull to defined no-op fields -- | A lens which does nothing. Usefull to defined no-op fields
emptyLens :: Lens' s () emptyLens :: Lens' s ()
@ -113,7 +113,7 @@ data FieldInput a b n =
-> HelpMessage -> HelpMessage
-> b -> b
-> (Widget n -> Widget n) -> (Widget n -> Widget n)
-> Widget n -- ^ How to draw the input, with focus a help message and input. -> Widget n -- ^ How to draw the input, with focus a help message and input.
-- A extension function can be applied too -- A extension function can be applied too
, inputHandler :: BrickEvent n () -> EventM n b () -- ^ The handler , inputHandler :: BrickEvent n () -> EventM n b () -- ^ The handler
} }
@ -137,6 +137,8 @@ data MenuField s n where
, fieldName :: n , fieldName :: n
} -> MenuField s n } -> MenuField s n
isValidField :: MenuField s n -> Bool
isValidField = (== Valid) . fieldStatus
makeLensesFor makeLensesFor
[ ("fieldLabel", "fieldLabelL") [ ("fieldLabel", "fieldLabelL")
@ -150,6 +152,14 @@ fieldHelpMsgL = lens g s
where g (MenuField {..})= fieldInput ^. inputHelpL where g (MenuField {..})= fieldInput ^. inputHelpL
s (MenuField{..}) msg = MenuField {fieldInput = fieldInput & inputHelpL .~ msg , ..} s (MenuField{..}) msg = MenuField {fieldInput = fieldInput & inputHelpL .~ msg , ..}
-- | How to draw a field given a formater
drawField :: Formatter n -> Bool -> MenuField s n -> Widget n
drawField amp focus (MenuField { fieldInput = FieldInput {..}, ..}) =
let input = inputRender focus fieldStatus inputHelp inputState (amp focus)
in if focus
then Brick.visible input
else input
instance Brick.Named (MenuField s n) n where instance Brick.Named (MenuField s n) n where
getName :: MenuField s n -> n getName :: MenuField s n -> n
getName entry = entry & fieldName getName entry = entry & fieldName
@ -171,7 +181,7 @@ createCheckBoxInput = FieldInput False Right "" checkBoxRender checkBoxHandler
else border . Brick.withAttr Attributes.notInstalledAttr $ Brick.str Common.notInstalledSign else border . Brick.withAttr Attributes.notInstalledAttr $ Brick.str Common.notInstalledSign
checkBoxRender focus _ help check f = checkBoxRender focus _ help check f =
let core = f $ drawBool check let core = f $ drawBool check
in if focus in if focus
then core then core
else core <+> (Brick.padLeft (Brick.Pad 1) . centerV . renderAsHelpMsg $ help) else core <+> (Brick.padLeft (Brick.Pad 1) . centerV . renderAsHelpMsg $ help)
checkBoxHandler = \case checkBoxHandler = \case
@ -191,18 +201,18 @@ createEditableInput :: (Ord n, Show n) => n -> (T.Text -> Either ErrorMessage a)
createEditableInput name validator = FieldInput initEdit validateEditContent "" drawEdit Edit.handleEditorEvent createEditableInput name validator = FieldInput initEdit validateEditContent "" drawEdit Edit.handleEditorEvent
where where
drawEdit focus errMsg help edi amp = drawEdit focus errMsg help edi amp =
let let
borderBox = amp . Border.border . Brick.padRight Brick.Max borderBox = amp . Border.border . Brick.padRight Brick.Max
editorRender = Edit.renderEditor (Brick.txt . T.unlines) focus edi editorRender = Edit.renderEditor (Brick.txt . T.unlines) focus edi
isEditorEmpty = Edit.getEditContents edi == [mempty] isEditorEmpty = Edit.getEditContents edi == [mempty]
in case errMsg of in case errMsg of
Valid | isEditorEmpty -> borderBox $ renderAsHelpMsg help Valid | isEditorEmpty -> borderBox $ renderAsHelpMsg help
| otherwise -> borderBox editorRender | otherwise -> borderBox editorRender
Invalid msg Invalid msg
| focus && isEditorEmpty -> borderBox $ renderAsHelpMsg help | focus && isEditorEmpty -> borderBox $ renderAsHelpMsg help
| focus -> borderBox editorRender | focus -> borderBox editorRender
| otherwise -> borderBox $ renderAsErrMsg msg | otherwise -> borderBox $ renderAsErrMsg msg
validateEditContent = validator . T.unlines . Edit.getEditContents validateEditContent = validator . T.init . T.unlines . Edit.getEditContents
initEdit = Edit.editorText name (Just 1) "" initEdit = Edit.editorText name (Just 1) ""
createEditableField :: (Eq n, Ord n, Show n) => n -> (T.Text -> Either ErrorMessage a) -> Lens' s a -> EditableField s n createEditableField :: (Eq n, Ord n, Show n) => n -> (T.Text -> Either ErrorMessage a) -> Lens' s a -> EditableField s n
@ -218,7 +228,9 @@ type Button = MenuField
createButtonInput :: FieldInput () () n createButtonInput :: FieldInput () () n
createButtonInput = FieldInput () Right "" drawButton (const $ pure ()) createButtonInput = FieldInput () Right "" drawButton (const $ pure ())
where drawButton _ _ help _ amp = amp . centerV . renderAsHelpMsg $ help where
drawButton True (Invalid err) _ _ amp = amp . centerV . renderAsErrMsg $ err
drawButton _ _ help _ amp = amp . centerV . renderAsHelpMsg $ help
createButtonField :: n -> Button s n createButtonField :: n -> Button s n
createButtonField = MenuField emptyLens createButtonInput "" Valid createButtonField = MenuField emptyLens createButtonInput "" Valid
@ -238,14 +250,14 @@ renderAslabel t focus =
then highlighted $ Brick.txt t then highlighted $ Brick.txt t
else Brick.txt t else Brick.txt t
-- | Creates a left align column. -- | Creates a left align column.
-- Example: |- col2 is align dispite the length of col1 -- Example: |- col2 is align dispite the length of col1
-- row1_col1 row1_col2 -- row1_col1 row1_col2
-- row2_col1_large row2_col2 -- row2_col1_large row2_col2
leftify :: Int -> Brick.Widget n -> Brick.Widget n leftify :: Int -> Brick.Widget n -> Brick.Widget n
leftify i = Brick.hLimit i . Brick.padRight Brick.Max leftify i = Brick.hLimit i . Brick.padRight Brick.Max
-- | center a line in three rows. -- | center a line in three rows.
centerV :: Widget n -> Widget n centerV :: Widget n -> Widget n
centerV = Brick.padTopBottom 1 centerV = Brick.padTopBottom 1
@ -261,8 +273,8 @@ renderAsErrMsg = Brick.withAttr Attributes.errMsgAttr . Brick.txt
Menu widget Menu widget
***************** -} ***************** -}
-- | A menu is a list of Fields and a state. Informally we can think about s in terms of the record type returned by -- | A menu is a list of Fields and a state. Informally we can think about s in terms of the record type returned by
-- a form. -- a form.
data Menu s n data Menu s n
= Menu = Menu
{ menuFields :: [MenuField s n] -- ^ The datatype representing the list of entries. Precisely, any array-like data type is highly unconvinient. { menuFields :: [MenuField s n] -- ^ The datatype representing the list of entries. Precisely, any array-like data type is highly unconvinient.
@ -273,7 +285,6 @@ data Menu s n
, menuName :: n -- ^ The resource Name. , menuName :: n -- ^ The resource Name.
} }
makeLensesFor makeLensesFor
[ ("menuFields", "menuFieldsL"), ("menuState", "menuStateL") [ ("menuFields", "menuFieldsL"), ("menuState", "menuStateL")
, ("menuButtons", "menuButtonsL"), ("menuFocusRing", "menuFocusRingL") , ("menuButtons", "menuButtonsL"), ("menuFocusRing", "menuFocusRingL")
@ -281,6 +292,9 @@ makeLensesFor
] ]
''Menu ''Menu
isValidMenu :: Menu s n -> Bool
isValidMenu = all isValidField . menuFields
createMenu :: n -> s -> KeyCombination -> [Button s n] -> [MenuField s n] -> Menu s n createMenu :: n -> s -> KeyCombination -> [Button s n] -> [MenuField s n] -> Menu s n
createMenu n initial exitK buttons fields = Menu fields initial buttons ring exitK n createMenu n initial exitK buttons fields = Menu fields initial buttons ring exitK n
where ring = F.focusRing $ [field & fieldName | field <- fields] ++ [button & fieldName | button <- buttons] where ring = F.focusRing $ [field & fieldName | field <- fields] ++ [button & fieldName | button <- buttons]
@ -297,11 +311,15 @@ handlerMenu ev =
fields <- use menuFieldsL fields <- use menuFieldsL
case focused of case focused of
Nothing -> pure () Nothing -> pure ()
Just n -> do Just n -> do
updated_fields <- updateFields n (VtyEvent e) fields updated_fields <- updateFields n (VtyEvent e) fields
if all isValidField updated_fields
then menuButtonsL %= fmap (fieldStatusL .~ Valid)
else menuButtonsL %= fmap (fieldStatusL .~ Invalid "Some fields are invalid")
menuFieldsL .= updated_fields menuFieldsL .= updated_fields
_ -> pure () _ -> pure ()
where where
-- runs the Event with the inner handler of MenuField.
updateFields :: n -> BrickEvent n () -> [MenuField s n] -> EventM n (Menu s n) [MenuField s n] updateFields :: n -> BrickEvent n () -> [MenuField s n] -> EventM n (Menu s n) [MenuField s n]
updateFields n e [] = pure [] updateFields n e [] = pure []
updateFields n e (x@(MenuField {fieldInput = i@(FieldInput {..}) , ..}):xs) = updateFields n e (x@(MenuField {fieldInput = i@(FieldInput {..}) , ..}):xs) =
@ -316,7 +334,7 @@ handlerMenu ev =
drawMenu :: (Eq n, Ord n, Show n, Brick.Named (MenuField s n) n) => Menu s n -> Widget n drawMenu :: (Eq n, Ord n, Show n, Brick.Named (MenuField s n) n) => Menu s n -> Widget n
drawMenu menu = drawMenu menu =
Brick.vBox Brick.vBox
[ Brick.vBox buttonWidgets [ Brick.vBox buttonWidgets
, Common.separator , Common.separator
@ -324,25 +342,19 @@ drawMenu menu =
$ Brick.viewport (menu ^. menuNameL) Brick.Vertical $ Brick.viewport (menu ^. menuNameL) Brick.Vertical
$ Brick.vBox fieldWidgets $ Brick.vBox fieldWidgets
, Brick.txt " " , Brick.txt " "
, Brick.padRight Brick.Max $ , Brick.padRight Brick.Max $
Brick.txt "Press " Brick.txt "Press "
<+> Common.keyToWidget (menu ^. menuExitKeyL) <+> Common.keyToWidget (menu ^. menuExitKeyL)
<+> Brick.txt " to go back" <+> Brick.txt " to go back"
] ]
where where
drawField amp focus (MenuField { fieldInput = FieldInput {..}, ..}) =
let input = inputRender focus fieldStatus inputHelp inputState (amp focus)
in if focus
then Brick.visible input
else input
fieldLabels = [field & fieldLabel | field <- menu ^. menuFieldsL] fieldLabels = [field & fieldLabel | field <- menu ^. menuFieldsL]
buttonLabels = [button & fieldLabel | button <- menu ^. menuButtonsL] buttonLabels = [button & fieldLabel | button <- menu ^. menuButtonsL]
allLabels = fieldLabels ++ buttonLabels allLabels = fieldLabels ++ buttonLabels
maxWidth = foldl' max 5 (fmap Brick.textWidth allLabels) maxWidth = foldl' max 5 (fmap Brick.textWidth allLabels)
-- A list of functions which draw a highlighted label with right padding at the left of a widget. -- A list of functions which draw a highlighted label with right padding at the left of a widget.
amplifiers = amplifiers =
let labelsWidgets = fmap renderAslabel fieldLabels let labelsWidgets = fmap renderAslabel fieldLabels
in fmap (\f b -> ((centerV . leftify (maxWidth + 10) $ f b) <+>) ) labelsWidgets in fmap (\f b -> ((centerV . leftify (maxWidth + 10) $ f b) <+>) ) labelsWidgets

View File

@ -14,7 +14,18 @@
{-# LANGUAGE InstanceSigs #-} {-# LANGUAGE InstanceSigs #-}
{-# OPTIONS_GHC -Wno-incomplete-patterns #-} {-# OPTIONS_GHC -Wno-incomplete-patterns #-}
module GHCup.Brick.Widgets.Menus.AdvanceInstall (InstallOptions, AdvanceInstallMenu, create, handler, draw) where module GHCup.Brick.Widgets.Menus.AdvanceInstall (
InstallOptions (..),
AdvanceInstallMenu,
create,
handler,
draw,
instBindistL,
instSetL,
isolateDirL,
forceInstallL,
addConfArgsL,
) where
import GHCup.Brick.Widgets.Menu (Menu) import GHCup.Brick.Widgets.Menu (Menu)
import qualified GHCup.Brick.Widgets.Menu as Menu import qualified GHCup.Brick.Widgets.Menu as Menu
@ -35,6 +46,8 @@ import Data.Bifunctor (Bifunctor(..))
import Data.Function ((&)) import Data.Function ((&))
import Optics ((.~)) import Optics ((.~))
import Data.Char (isSpace) import Data.Char (isSpace)
import System.FilePath (isValid, isAbsolute, normalise)
import GHCup.Prelude (stripNewlineEnd)
data InstallOptions = InstallOptions data InstallOptions = InstallOptions
{ instBindist :: Maybe URI { instBindist :: Maybe URI
@ -61,23 +74,28 @@ create k = Menu.createMenu AdvanceInstallBox initialState k [ok] fields
initialState = InstallOptions Nothing False Nothing False [] initialState = InstallOptions Nothing False Nothing False []
-- Brick's internal editor representation is [mempty]. -- Brick's internal editor representation is [mempty].
emptyEditor i = T.null i || (i == "\n") emptyEditor i = T.null i || (i == "\n")
uriValidator :: T.Text -> Either Menu.ErrorMessage (Maybe URI) uriValidator :: T.Text -> Either Menu.ErrorMessage (Maybe URI)
uriValidator i = uriValidator i =
case not $ emptyEditor i of case not $ emptyEditor i of
True -> bimap (T.pack . show) Just . parseURI . UTF8.fromString . T.unpack $ i True -> bimap (T.pack . show) Just . parseURI . UTF8.fromString . T.unpack $ i
False -> Right Nothing False -> Right Nothing
filepathValidator :: T.Text -> Either Menu.ErrorMessage (Maybe FilePath) filepathValidator :: T.Text -> Either Menu.ErrorMessage (Maybe FilePath)
filepathValidator i = filepathValidator i =
case not $ emptyEditor i of case not $ emptyEditor i of
True -> Right . Just . T.unpack $ i True -> absolutePathParser (T.unpack i)
False -> Right Nothing False -> Right Nothing
absolutePathParser :: FilePath -> Either Menu.ErrorMessage (Maybe FilePath)
absolutePathParser f = case isValid f && isAbsolute f of
True -> Right . Just . stripNewlineEnd . normalise $ f
False -> Left "Please enter a valid absolute filepath."
additionalValidator :: T.Text -> Either Menu.ErrorMessage [T.Text] additionalValidator :: T.Text -> Either Menu.ErrorMessage [T.Text]
additionalValidator = Right . T.split isSpace additionalValidator = Right . T.split isSpace
fields = fields =
[ Menu.createEditableField (Common.MenuElement Common.UrlEditBox) uriValidator instBindistL [ Menu.createEditableField (Common.MenuElement Common.UrlEditBox) uriValidator instBindistL
& Menu.fieldLabelL .~ "url" & Menu.fieldLabelL .~ "url"
& Menu.fieldHelpMsgL .~ "Install the specified version from this bindist" & Menu.fieldHelpMsgL .~ "Install the specified version from this bindist"
@ -94,7 +112,7 @@ create k = Menu.createMenu AdvanceInstallBox initialState k [ok] fields
& Menu.fieldLabelL .~ "CONFIGURE_ARGS" & Menu.fieldLabelL .~ "CONFIGURE_ARGS"
& Menu.fieldHelpMsgL .~ "Additional arguments to bindist configure, prefix with '-- ' (longopts)" & Menu.fieldHelpMsgL .~ "Additional arguments to bindist configure, prefix with '-- ' (longopts)"
] ]
ok = Menu.createButtonField (Common.MenuElement Common.OkButton) ok = Menu.createButtonField (Common.MenuElement Common.OkButton)
& Menu.fieldLabelL .~ "Advance Install" & Menu.fieldLabelL .~ "Advance Install"
& Menu.fieldHelpMsgL .~ "Install with options below" & Menu.fieldHelpMsgL .~ "Install with options below"

View File

@ -14,7 +14,24 @@
{-# LANGUAGE InstanceSigs #-} {-# LANGUAGE InstanceSigs #-}
{-# OPTIONS_GHC -Wno-incomplete-patterns #-} {-# OPTIONS_GHC -Wno-incomplete-patterns #-}
module GHCup.Brick.Widgets.Menus.CompileGHC (CompileGHCOptions, CompileGHCMenu, create, handler, draw) where module GHCup.Brick.Widgets.Menus.CompileGHC (
CompileGHCOptions,
CompileGHCMenu,
create,
handler,
draw,
bootstrapGhc,
jobs,
buildConfig,
patches,
crossTarget,
addConfArgs,
setCompile,
overwriteVer,
buildFlavour,
buildSystem,
isolateDir,
) where
import GHCup.Brick.Widgets.Menu (Menu) import GHCup.Brick.Widgets.Menu (Menu)
import qualified GHCup.Brick.Widgets.Menu as Menu import qualified GHCup.Brick.Widgets.Menu as Menu
@ -26,7 +43,8 @@ import Brick
import Prelude hiding ( appendFile ) import Prelude hiding ( appendFile )
import Optics.TH (makeLenses) import Optics.TH (makeLenses)
import qualified GHCup.Brick.Common as Common import qualified GHCup.Brick.Common as Common
import GHCup.Types (KeyCombination, BuildSystem (Hadrian)) import GHCup.Types
( KeyCombination, BuildSystem(..), VersionPattern )
import URI.ByteString (URI) import URI.ByteString (URI)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.ByteString.UTF8 as UTF8 import qualified Data.ByteString.UTF8 as UTF8
@ -36,9 +54,11 @@ import Data.Function ((&))
import Optics ((.~)) import Optics ((.~))
import Data.Char (isSpace) import Data.Char (isSpace)
import Data.Versions (Version, version) import Data.Versions (Version, version)
import System.FilePath (isPathSeparator) import System.FilePath (isPathSeparator, isValid, isAbsolute, normalise)
import Control.Applicative (Alternative((<|>))) import Control.Applicative (Alternative((<|>)))
import Text.Read (readEither) import Text.Read (readEither)
import GHCup.Prelude (stripNewlineEnd)
import qualified GHCup.OptParse.Common as OptParse
data CompileGHCOptions = CompileGHCOptions data CompileGHCOptions = CompileGHCOptions
{ _bootstrapGhc :: Either Version FilePath { _bootstrapGhc :: Either Version FilePath
@ -48,7 +68,7 @@ data CompileGHCOptions = CompileGHCOptions
, _crossTarget :: Maybe T.Text , _crossTarget :: Maybe T.Text
, _addConfArgs :: [T.Text] , _addConfArgs :: [T.Text]
, _setCompile :: Bool , _setCompile :: Bool
, _ovewrwiteVer :: Maybe Version , _overwriteVer :: Maybe [VersionPattern]
, _buildFlavour :: Maybe String , _buildFlavour :: Maybe String
, _buildSystem :: Maybe BuildSystem , _buildSystem :: Maybe BuildSystem
, _isolateDir :: Maybe FilePath , _isolateDir :: Maybe FilePath
@ -61,8 +81,8 @@ type CompileGHCMenu = Menu CompileGHCOptions Name
create :: KeyCombination -> CompileGHCMenu create :: KeyCombination -> CompileGHCMenu
create k = Menu.createMenu CompileGHCBox initialState k buttons fields create k = Menu.createMenu CompileGHCBox initialState k buttons fields
where where
initialState = initialState =
CompileGHCOptions CompileGHCOptions
(Right "") (Right "")
Nothing Nothing
Nothing Nothing
@ -82,51 +102,60 @@ create k = Menu.createMenu CompileGHCBox initialState k buttons fields
bootstrapV :: T.Text -> Either Menu.ErrorMessage (Either Version FilePath) bootstrapV :: T.Text -> Either Menu.ErrorMessage (Either Version FilePath)
bootstrapV i = bootstrapV i =
case not $ emptyEditor i of case not $ emptyEditor i of
True -> True ->
let readVersion = bimap (const "Not a valid version") Left (version (T.init i)) -- Brick adds \n at the end, hence T.init let readVersion = bimap (const "Not a valid version") Left (version i)
readPath readPath = do
= if isPathSeparator (T.head i) mfilepath <- filepathV i
then pure $ Right (T.unpack i) case mfilepath of
else Left "Not an absolute Path" Nothing -> Left "Invalid Empty value"
in if T.any isPathSeparator i Just f -> Right (Right f)
in if T.any isPathSeparator i
then readPath then readPath
else readVersion else readVersion
False -> Left "Invalid Empty value" False -> Left "Invalid Empty value"
versionV :: T.Text -> Either Menu.ErrorMessage (Maybe Version) versionV :: T.Text -> Either Menu.ErrorMessage (Maybe [VersionPattern])
versionV = bimap (const "Not a valid version") Just . version . T.init -- Brick adds \n at the end, hence T.init versionV = whenEmpty Nothing (bimap T.pack Just . OptParse.overWriteVersionParser . T.unpack)
jobsV :: T.Text -> Either Menu.ErrorMessage (Maybe Int) jobsV :: T.Text -> Either Menu.ErrorMessage (Maybe Int)
jobsV = jobsV =
let parseInt = bimap (const "Invalid value. Must be an integer") Just . readEither @Int . T.unpack let parseInt = bimap (const "Invalid value. Must be an integer") Just . readEither @Int . T.unpack
in whenEmpty Nothing parseInt in whenEmpty Nothing parseInt
patchesV :: T.Text -> Either Menu.ErrorMessage (Maybe (Either FilePath [URI])) patchesV :: T.Text -> Either Menu.ErrorMessage (Maybe (Either FilePath [URI]))
patchesV = whenEmpty Nothing readPatches patchesV = whenEmpty Nothing readPatches
where where
readUri :: T.Text -> Either String URI readUri :: T.Text -> Either String URI
readUri = first show . parseURI . UTF8.fromString . T.unpack readUri = first show . parseURI . UTF8.fromString . T.unpack
readPatches j = readPatches j =
let let
x = (bimap T.unpack (fmap Left) $ filepathV j) x = (bimap T.unpack (fmap Left) $ filepathV j)
y = second (Just . Right) $ traverse readUri (T.split isSpace j) y = second (Just . Right) $ traverse readUri (T.split isSpace j)
in first T.pack $ x <|> y in first T.pack $ x <|> y
filepathV :: T.Text -> Either Menu.ErrorMessage (Maybe FilePath) filepathV :: T.Text -> Either Menu.ErrorMessage (Maybe FilePath)
filepathV = whenEmpty Nothing (Right . Just . T.unpack) filepathV i =
case not $ emptyEditor i of
True -> absolutePathParser (T.unpack i)
False -> Right Nothing
absolutePathParser :: FilePath -> Either Menu.ErrorMessage (Maybe FilePath)
absolutePathParser f = case isValid f && isAbsolute f of
True -> Right . Just . stripNewlineEnd . normalise $ f
False -> Left "Please enter a valid absolute filepath."
additionalValidator :: T.Text -> Either Menu.ErrorMessage [T.Text] additionalValidator :: T.Text -> Either Menu.ErrorMessage [T.Text]
additionalValidator = Right . T.split isSpace additionalValidator = Right . T.split isSpace
systemV :: T.Text -> Either Menu.ErrorMessage (Maybe BuildSystem) systemV :: T.Text -> Either Menu.ErrorMessage (Maybe BuildSystem)
systemV = whenEmpty Nothing readSys systemV = whenEmpty Nothing readSys
where where
readSys i readSys i
| T.toLower i == "hadrian" = Right $ Just Hadrian | T.toLower i == "hadrian" = Right $ Just Hadrian
| T.toLower i == "make" = Right $ Just Hadrian | T.toLower i == "make" = Right $ Just Make
| otherwise = Left "Not a valid Build System" | otherwise = Left "Not a valid Build System"
fields = fields =
[ Menu.createEditableField (Common.MenuElement Common.BootstrapGhcEditBox) bootstrapV bootstrapGhc [ Menu.createEditableField (Common.MenuElement Common.BootstrapGhcEditBox) bootstrapV bootstrapGhc
& Menu.fieldLabelL .~ "bootstrap-ghc" & Menu.fieldLabelL .~ "bootstrap-ghc"
& Menu.fieldHelpMsgL .~ "The GHC version (or full path) to bootstrap with (must be installed)" & Menu.fieldHelpMsgL .~ "The GHC version (or full path) to bootstrap with (must be installed)"
@ -149,14 +178,14 @@ create k = Menu.createMenu CompileGHCBox initialState k buttons fields
, Menu.createCheckBoxField (Common.MenuElement Common.SetCheckBox) setCompile , Menu.createCheckBoxField (Common.MenuElement Common.SetCheckBox) setCompile
& Menu.fieldLabelL .~ "set" & Menu.fieldLabelL .~ "set"
& Menu.fieldHelpMsgL .~ "Set as active version after install" & Menu.fieldHelpMsgL .~ "Set as active version after install"
, Menu.createEditableField (Common.MenuElement Common.OvewrwiteVerEditBox) versionV ovewrwiteVer , Menu.createEditableField (Common.MenuElement Common.OvewrwiteVerEditBox) versionV overwriteVer
& Menu.fieldLabelL .~ "overwrite-version" & Menu.fieldLabelL .~ "overwrite-version"
& Menu.fieldHelpMsgL .~ "Allows to overwrite the finally installed VERSION with a different one" & Menu.fieldHelpMsgL .~ "Allows to overwrite the finally installed VERSION with a different one"
, Menu.createEditableField (Common.MenuElement Common.BuildFlavourEditBox) (Right . Just . T.unpack) buildFlavour
& Menu.fieldLabelL .~ "flavour"
& Menu.fieldHelpMsgL .~ "Set the compile build flavour (this value depends on the build system type: 'make' vs 'hadrian')"
, Menu.createEditableField (Common.MenuElement Common.BuildSystemEditBox) systemV buildSystem , Menu.createEditableField (Common.MenuElement Common.BuildSystemEditBox) systemV buildSystem
& Menu.fieldLabelL .~ "build system" & Menu.fieldLabelL .~ "build system"
& Menu.fieldHelpMsgL .~ "either 'make' or 'hadrian'"
, Menu.createEditableField (Common.MenuElement Common.BuildFlavourEditBox) (Right . Just . T.unpack) buildFlavour
& Menu.fieldLabelL .~ "flavour"
& Menu.fieldHelpMsgL .~ "Set the compile build flavour (this value depends on the build system type: 'make' vs 'hadrian')" & Menu.fieldHelpMsgL .~ "Set the compile build flavour (this value depends on the build system type: 'make' vs 'hadrian')"
, Menu.createEditableField (Common.MenuElement Common.IsolateEditBox) filepathV isolateDir , Menu.createEditableField (Common.MenuElement Common.IsolateEditBox) filepathV isolateDir
& Menu.fieldLabelL .~ "isolated" & Menu.fieldLabelL .~ "isolated"
@ -167,6 +196,7 @@ create k = Menu.createMenu CompileGHCBox initialState k buttons fields
Menu.createButtonField (Common.MenuElement Common.OkButton) Menu.createButtonField (Common.MenuElement Common.OkButton)
& Menu.fieldLabelL .~ "Compile" & Menu.fieldLabelL .~ "Compile"
& Menu.fieldHelpMsgL .~ "Compile GHC from source with options below" & Menu.fieldHelpMsgL .~ "Compile GHC from source with options below"
& Menu.fieldStatusL .~ Menu.Invalid "bootstrap GHC is mandatory"
] ]
handler :: BrickEvent Name e -> EventM Name CompileGHCMenu () handler :: BrickEvent Name e -> EventM Name CompileGHCMenu ()

View File

@ -0,0 +1,191 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-unused-record-wildcards #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE InstanceSigs #-}
{-# OPTIONS_GHC -Wno-incomplete-patterns #-}
module GHCup.Brick.Widgets.Menus.CompileHLS (
CompileHLSOptions,
CompileHLSMenu,
create,
handler,
draw,
jobs,
setCompile,
updateCabal,
overwriteVer,
isolateDir,
cabalProject,
cabalProjectLocal,
patches,
targetGHCs,
cabalArgs,
)
where
import GHCup.Brick.Widgets.Menu (Menu)
import qualified GHCup.Brick.Widgets.Menu as Menu
import GHCup.Brick.Common(Name(..))
import Brick
( BrickEvent(..),
EventM,
Widget(..))
import Prelude hiding ( appendFile )
import Optics.TH (makeLenses)
import qualified GHCup.Brick.Common as Common
import GHCup.Types (KeyCombination, VersionPattern, ToolVersion)
import URI.ByteString (URI)
import qualified Data.Text as T
import qualified Data.ByteString.UTF8 as UTF8
import GHCup.Utils (parseURI)
import Data.Bifunctor (Bifunctor(..))
import Data.Function ((&))
import Optics ((.~))
import Data.Char (isSpace)
import System.FilePath (isValid, isAbsolute, normalise)
import Control.Applicative (Alternative((<|>)))
import Text.Read (readEither)
import GHCup.Prelude (stripNewlineEnd)
import qualified GHCup.OptParse.Common as OptParse
data CompileHLSOptions = CompileHLSOptions
{ _jobs :: Maybe Int
, _setCompile :: Bool
, _updateCabal :: Bool
, _overwriteVer :: Maybe [VersionPattern]
, _isolateDir :: Maybe FilePath
, _cabalProject :: Maybe (Either FilePath URI)
, _cabalProjectLocal :: Maybe URI
, _patches :: Maybe (Either FilePath [URI])
, _targetGHCs :: [ToolVersion]
, _cabalArgs :: [T.Text]
} deriving (Eq, Show)
makeLenses ''CompileHLSOptions
type CompileHLSMenu = Menu CompileHLSOptions Name
create :: KeyCombination -> CompileHLSMenu
create k = Menu.createMenu CompileGHCBox initialState k buttons fields
where
initialState =
CompileHLSOptions
Nothing
False
False
Nothing
Nothing
Nothing
Nothing
Nothing
[]
[]
-- Brick's internal editor representation is [mempty].
emptyEditor i = T.null i || (i == "\n")
whenEmpty :: a -> (T.Text -> Either Menu.ErrorMessage a) -> T.Text -> Either Menu.ErrorMessage a
whenEmpty emptyval f i = if not (emptyEditor i) then f i else Right emptyval
cabalProjectV :: T.Text -> Either Menu.ErrorMessage (Maybe (Either FilePath URI))
cabalProjectV i =
case not $ emptyEditor i of
True ->
let readPath = Right . Left . stripNewlineEnd . T.unpack $ i
in bimap T.pack Just $ second Right (readUri i) <|> readPath
False -> Right Nothing
{- There is an unwanted dependency to ghcup-opt... Alternatives are
- copy-paste a bunch of code
- define a new common library
-}
ghcVersionTagEither :: T.Text -> Either Menu.ErrorMessage [ToolVersion]
ghcVersionTagEither = first T.pack . traverse (OptParse.ghcVersionTagEither . T.unpack) . T.split isSpace
overWriteVersionParser :: T.Text -> Either Menu.ErrorMessage (Maybe [VersionPattern])
overWriteVersionParser = bimap T.pack Just . OptParse.overWriteVersionParser . T.unpack
jobsV :: T.Text -> Either Menu.ErrorMessage (Maybe Int)
jobsV =
let parseInt = bimap (const "Invalid value. Must be an integer") Just . readEither @Int . T.unpack
in whenEmpty Nothing parseInt
readUri :: T.Text -> Either String URI
readUri = first show . parseURI . UTF8.fromString . T.unpack
patchesV :: T.Text -> Either Menu.ErrorMessage (Maybe (Either FilePath [URI]))
patchesV = whenEmpty Nothing readPatches
where
readPatches j =
let
x = (bimap T.unpack (fmap Left) $ filepathV j)
y = second (Just . Right) $ traverse readUri (T.split isSpace j)
in first T.pack $ x <|> y
filepathV :: T.Text -> Either Menu.ErrorMessage (Maybe FilePath)
filepathV i =
case not $ emptyEditor i of
True -> absolutePathParser (T.unpack i)
False -> Right Nothing
absolutePathParser :: FilePath -> Either Menu.ErrorMessage (Maybe FilePath)
absolutePathParser f = case isValid f && isAbsolute f of
True -> Right . Just . stripNewlineEnd . normalise $ f
False -> Left "Please enter a valid absolute filepath."
additionalValidator :: T.Text -> Either Menu.ErrorMessage [T.Text]
additionalValidator = Right . T.split isSpace
fields =
[ Menu.createEditableField (Common.MenuElement Common.CabalProjectEditBox) cabalProjectV cabalProject
& Menu.fieldLabelL .~ "cabal project"
& Menu.fieldHelpMsgL .~ "If relative filepath, specifies the path to cabal.project inside the unpacked HLS tarball/checkout. Otherwise expects a full URI with https/http/file scheme."
, Menu.createEditableField (Common.MenuElement Common.CabalProjectLocalEditBox) (bimap T.pack Just . readUri) cabalProjectLocal
& Menu.fieldLabelL .~ "cabal project local"
& Menu.fieldHelpMsgL .~ "URI (https/http/file) to a cabal.project.local to be used for the build. Will be copied over."
, Menu.createCheckBoxField (Common.MenuElement Common.UpdateCabalCheckBox) updateCabal
& Menu.fieldLabelL .~ "cabal update"
& Menu.fieldHelpMsgL .~ "Run 'cabal update' before the build"
, Menu.createEditableField (Common.MenuElement Common.JobsEditBox) jobsV jobs
& Menu.fieldLabelL .~ "jobs"
& Menu.fieldHelpMsgL .~ "How many jobs to use for make"
, Menu.createEditableField (Common.MenuElement Common.TargetGhcEditBox) ghcVersionTagEither targetGHCs
& Menu.fieldLabelL .~ "target GHC"
& Menu.fieldHelpMsgL .~ "For which GHC version to compile for (can be specified multiple times)"
, Menu.createEditableField (Common.MenuElement Common.PatchesEditBox) patchesV patches
& Menu.fieldLabelL .~ "patches"
& Menu.fieldHelpMsgL .~ "Either a URI to a patch (https/http/file) or Absolute path to patch directory"
, Menu.createCheckBoxField (Common.MenuElement Common.SetCheckBox) setCompile
& Menu.fieldLabelL .~ "set"
& Menu.fieldHelpMsgL .~ "Set as active version after install"
, Menu.createEditableField (Common.MenuElement Common.AdditionalEditBox) additionalValidator cabalArgs
& Menu.fieldLabelL .~ "CONFIGURE_ARGS"
& Menu.fieldHelpMsgL .~ "Additional arguments to cabal install, prefix with '-- ' (longopts)"
, Menu.createEditableField (Common.MenuElement Common.IsolateEditBox) filepathV isolateDir
& Menu.fieldLabelL .~ "isolated"
& Menu.fieldHelpMsgL .~ "install in an isolated absolute directory instead of the default one"
, Menu.createEditableField (Common.MenuElement Common.OvewrwiteVerEditBox) overWriteVersionParser overwriteVer
& Menu.fieldLabelL .~ "overwrite version"
& Menu.fieldHelpMsgL .~ "Allows to overwrite the finally installed VERSION with a different one"
]
buttons = [
Menu.createButtonField (Common.MenuElement Common.OkButton)
& Menu.fieldLabelL .~ "Compile"
& Menu.fieldHelpMsgL .~ "Compile HLS from source with options below"
]
handler :: BrickEvent Name e -> EventM Name CompileHLSMenu ()
handler = Menu.handlerMenu
draw :: CompileHLSMenu -> Widget Name
draw = Common.frontwardLayer "Compile HLS" . Menu.drawMenu

View File

@ -6,20 +6,25 @@ import Brick (
Widget (..), BrickEvent, EventM, Widget (..), BrickEvent, EventM,
) )
import Data.Function ((&)) import Data.Function ((&))
import qualified GHCup.Brick.Common as Common
import qualified GHCup.Brick.Widgets.Menu as Menu
import Prelude hiding (appendFile) import Prelude hiding (appendFile)
import qualified Data.Text as T
import Data.Versions (prettyVer) import Data.Versions (prettyVer)
import GHCup (ListResult (..)) import GHCup.List ( ListResult(..) )
import GHCup.Types (KeyCombination, Tool (..))
import qualified GHCup.Brick.Common as Common
import qualified GHCup.Brick.Widgets.Menu as Menu
import GHCup.Brick.Common (Name (..)) import GHCup.Brick.Common (Name (..))
import GHCup.Brick.Widgets.Menu (Menu) import GHCup.Brick.Widgets.Menu (Menu)
import GHCup.Types (KeyCombination, Tool (..)) import qualified Brick.Widgets.Core as Brick
import qualified Brick.Widgets.Border as Border
import qualified Brick.Focus as F
import Brick.Widgets.Core ((<+>))
import Optics (to) import Optics (to)
import Optics.Operators ((.~), (^.)) import Optics.Operators ((.~), (^.))
import Optics.Optic ((%)) import Optics.Optic ((%))
import Data.Foldable (foldl')
type ContextMenu = Menu ListResult Name type ContextMenu = Menu ListResult Name
@ -30,30 +35,48 @@ create lr exit_key = Menu.createMenu Common.ContextBox lr exit_key buttons []
Menu.createButtonField (MenuElement Common.AdvanceInstallButton) Menu.createButtonField (MenuElement Common.AdvanceInstallButton)
& Menu.fieldLabelL .~ "Install" & Menu.fieldLabelL .~ "Install"
& Menu.fieldHelpMsgL .~ "Advance Installation Settings" & Menu.fieldHelpMsgL .~ "Advance Installation Settings"
compileButton = compileGhcButton =
Menu.createButtonField (MenuElement Common.CompilieButton) Menu.createButtonField (MenuElement Common.CompileGHCButton)
& Menu.fieldLabelL .~ "Compile" & Menu.fieldLabelL .~ "Compile"
& Menu.fieldHelpMsgL .~ "Compile tool from source (to be implemented)" & Menu.fieldHelpMsgL .~ "Compile GHC from source"
compileHLSButton =
Menu.createButtonField (MenuElement Common.CompileHLSButton)
& Menu.fieldLabelL .~ "Compile"
& Menu.fieldHelpMsgL .~ "Compile HLS from source"
buttons = buttons =
case lTool lr of case lTool lr of
GHC -> [advInstallButton, compileButton] GHC -> [advInstallButton, compileGhcButton]
HLS -> [advInstallButton, compileButton] HLS -> [advInstallButton, compileHLSButton]
_ -> [advInstallButton] _ -> [advInstallButton]
draw :: ContextMenu -> Widget Name draw :: ContextMenu -> Widget Name
draw ctx = draw menu =
Common.frontwardLayer Common.frontwardLayer
("Context Menu for " <> tool_str <> " " <> prettyVer (lVer $ ctx ^. Menu.menuStateL)) ("Context Menu for " <> tool_str <> " " <> prettyVer (lVer $ menu ^. Menu.menuStateL))
(Menu.drawMenu ctx) $ Brick.vBox
where [ Brick.vBox buttonWidgets
tool_str :: T.Text , Brick.txt " "
tool_str = , Brick.padRight Brick.Max $
case ctx ^. Menu.menuStateL % to lTool of Brick.txt "Press "
GHC -> "GHC" <+> Common.keyToWidget (menu ^. Menu.menuExitKeyL)
GHCup -> "GHCup" <+> Brick.txt " to go back"
Cabal -> "Cabal" ]
HLS -> "HLS" where
Stack -> "Stack" buttonLabels = [button & Menu.fieldLabel | button <- menu ^. Menu.menuButtonsL]
maxWidth = foldl' max 5 (fmap Brick.textWidth buttonLabels)
buttonAmplifiers =
let buttonAsWidgets = fmap Menu.renderAslabel buttonLabels
in fmap (\f b -> ((Menu.leftify (maxWidth + 10) . Border.border $ f b) <+>) ) buttonAsWidgets
drawButtons = fmap Menu.drawField buttonAmplifiers
buttonWidgets = zipWith (F.withFocusRing (menu ^. Menu.menuFocusRingL)) drawButtons (menu ^. Menu.menuButtonsL)
tool_str =
case menu ^. Menu.menuStateL % to lTool of
GHC -> "GHC"
GHCup -> "GHCup"
Cabal -> "Cabal"
HLS -> "HLS"
Stack -> "Stack"
handler :: BrickEvent Name e -> EventM Name ContextMenu () handler :: BrickEvent Name e -> EventM Name ContextMenu ()
handler = Menu.handlerMenu handler = Menu.handlerMenu

View File

@ -36,6 +36,8 @@ import Brick
(<+>), (<+>),
(<=>)) (<=>))
import qualified Brick import qualified Brick
import Brick.Widgets.Core ( putCursor )
import Brick.Types ( Location(..) )
import Brick.Widgets.Border ( hBorder, borderWithLabel) import Brick.Widgets.Border ( hBorder, borderWithLabel)
import Brick.Widgets.Border.Style ( unicode ) import Brick.Widgets.Border.Style ( unicode )
import Brick.Widgets.Center ( center ) import Brick.Widgets.Center ( center )
@ -54,7 +56,7 @@ type BrickInternalState = SectionList.SectionList Common.Name ListResult
-- | How to create a navigation widget -- | How to create a navigation widget
create :: Common.Name -- The name of the section list create :: Common.Name -- The name of the section list
-> [(Common.Name, Vector ListResult)] -- a list of tuples (section name, collection of elements) -> [(Common.Name, Vector ListResult)] -- a list of tuples (section name, collection of elements)
-> Int -- The height of each item in a list. Commonly 1 -> Int -- The height of each item in a list. Commonly 1
-> BrickInternalState -> BrickInternalState
create = SectionList.sectionList create = SectionList.sectionList
@ -100,7 +102,8 @@ draw dimAttrs section_list
| elem Latest lTag' && not lInstalled = | elem Latest lTag' && not lInstalled =
Brick.withAttr Attributes.hoorayAttr Brick.withAttr Attributes.hoorayAttr
| otherwise = id | otherwise = id
in hooray $ dim active = if b then putCursor Common.AllTools (Location (0,0)) else id
in hooray $ active $ dim
( marks ( marks
<+> Brick.padLeft (Pad 2) <+> Brick.padLeft (Pad 2)
( minHSize 6 ( minHSize 6
@ -145,4 +148,4 @@ draw dimAttrs section_list
Nothing -> mempty Nothing -> mempty
Just d -> [Brick.withAttr Attributes.dayAttr $ Brick.str (show d)]) Just d -> [Brick.withAttr Attributes.dayAttr $ Brick.str (show d)])
minHSize s' = Brick.hLimit s' . Brick.vLimit 1 . (<+> Brick.fill ' ') minHSize s' = Brick.hLimit s' . Brick.vLimit 1 . (<+> Brick.fill ' ')

View File

@ -15,8 +15,8 @@
{- A general system for lists with sections {- A general system for lists with sections
Consider this code as private. GenericSectionList should not be used directly as the FocusRing should be align with the Vector containing Consider this code as private. GenericSectionList should not be used directly as the FocusRing should be align with the Vector containing
the elements, otherwise you'd be focusing on a non-existent widget with unknown result (In theory the code is safe unless you have an empty section list). the elements, otherwise you'd be focusing on a non-existent widget with unknown result (In theory the code is safe unless you have an empty section list).
- To build a SectionList use the safe constructor sectionList - To build a SectionList use the safe constructor sectionList
- To access sections use the lens provider sectionL and the name of the section you'd like to access - To access sections use the lens provider sectionL and the name of the section you'd like to access
@ -33,7 +33,7 @@ import Brick
( BrickEvent(VtyEvent, MouseDown), ( BrickEvent(VtyEvent, MouseDown),
EventM, EventM,
Size(..), Size(..),
Widget(..), Widget(..),
ViewportType (Vertical), ViewportType (Vertical),
(<=>)) (<=>))
import qualified Brick import qualified Brick
@ -68,8 +68,8 @@ makeLensesFor [("sectionListFocusRing", "sectionListFocusRingL"), ("sectionListE
type SectionList n e = GenericSectionList n V.Vector e type SectionList n e = GenericSectionList n V.Vector e
-- | Build a SectionList from nonempty list. If empty we could not defined sectionL lenses. -- | Build a SectionList from nonempty list. If empty we could not defined sectionL lenses.
sectionList :: Foldable t sectionList :: Foldable t
=> n -- The name of the section list => n -- The name of the section list
-> [(n, t e)] -- a list of tuples (section name, collection of elements) -> [(n, t e)] -- a list of tuples (section name, collection of elements)
-> Int -> Int
@ -81,14 +81,14 @@ sectionList name elements height
, sectionListName = name , sectionListName = name
} }
-- | This lens constructor, takes a name and looks if a section has such a name. -- | This lens constructor, takes a name and looks if a section has such a name.
-- Used to dispatch events to sections. It is a partial function only meant to -- Used to dispatch events to sections. It is a partial function only meant to
-- be used with the FocusRing inside GenericSectionList -- be used with the FocusRing inside GenericSectionList
sectionL :: Eq n => n -> Lens' (GenericSectionList n t e) (L.GenericList n t e) sectionL :: Eq n => n -> Lens' (GenericSectionList n t e) (L.GenericList n t e)
sectionL section_name = lens g s sectionL section_name = lens g s
where is_section_name = (== section_name) . L.listName where is_section_name = (== section_name) . L.listName
g section_list = g section_list =
let elms = section_list ^. sectionListElementsL let elms = section_list ^. sectionListElementsL
zeroth = elms V.! 0 -- TODO: This crashes for empty vectors. zeroth = elms V.! 0 -- TODO: This crashes for empty vectors.
in fromMaybe zeroth (V.find is_section_name elms) in fromMaybe zeroth (V.find is_section_name elms)
s gl@(GenericSectionList _ elms _) list = s gl@(GenericSectionList _ elms _) list =
case V.findIndex is_section_name elms of case V.findIndex is_section_name elms of
@ -97,16 +97,16 @@ sectionL section_name = lens g s
in gl & sectionListElementsL .~ new_elms in gl & sectionListElementsL .~ new_elms
moveDown :: (L.Splittable t, Ord n, Foldable t) => EventM n (GenericSectionList n t e) () moveDown :: (L.Splittable t, Ord n, Foldable t) => EventM n (GenericSectionList n t e) ()
moveDown = do moveDown = do
ring <- use sectionListFocusRingL ring <- use sectionListFocusRingL
case F.focusGetCurrent ring of case F.focusGetCurrent ring of
Nothing -> pure () Nothing -> pure ()
Just l -> do -- If it is the last element, move to the first element of the next focus; else, just handle regular list event. Just l -> do -- If it is the last element, move to the first element of the next focus; else, just handle regular list event.
current_list <- use (sectionL l) current_list <- use (sectionL l)
let current_idx = L.listSelected current_list let current_idx = L.listSelected current_list
list_length = current_list & length list_length = current_list & length
if current_idx == Just (list_length - 1) if current_idx == Just (list_length - 1)
then do then do
new_focus <- sectionListFocusRingL <%= F.focusNext new_focus <- sectionListFocusRingL <%= F.focusNext
case F.focusGetCurrent new_focus of case F.focusGetCurrent new_focus of
Nothing -> pure () -- |- Optic.Zoom.zoom doesn't typecheck but Lens.Micro.Mtl.zoom does. It is re-exported by Brick Nothing -> pure () -- |- Optic.Zoom.zoom doesn't typecheck but Lens.Micro.Mtl.zoom does. It is re-exported by Brick
@ -122,10 +122,10 @@ moveUp = do
current_list <- use (sectionL l) current_list <- use (sectionL l)
let current_idx = L.listSelected current_list let current_idx = L.listSelected current_list
if current_idx == Just 0 if current_idx == Just 0
then do then do
new_focus <- sectionListFocusRingL <%= F.focusPrev new_focus <- sectionListFocusRingL <%= F.focusPrev
case F.focusGetCurrent new_focus of case F.focusGetCurrent new_focus of
Nothing -> pure () Nothing -> pure ()
Just new_l -> Common.zoom (sectionL new_l) (Brick.modify L.listMoveToEnd) Just new_l -> Common.zoom (sectionL new_l) (Brick.modify L.listMoveToEnd)
else Common.zoom (sectionL l) $ Brick.modify L.listMoveUp else Common.zoom (sectionL l) $ Brick.modify L.listMoveUp
@ -188,6 +188,6 @@ renderSectionList renderElem sectionFocus ge@(GenericSectionList focus elms slNa
-- | Equivalent to listSelectedElement -- | Equivalent to listSelectedElement
sectionListSelectedElement :: (Eq n, L.Splittable t, Traversable t, Semigroup (t e)) => GenericSectionList n t e -> Maybe (Int, e) sectionListSelectedElement :: (Eq n, L.Splittable t, Traversable t, Semigroup (t e)) => GenericSectionList n t e -> Maybe (Int, e)
sectionListSelectedElement generic_section_list = do sectionListSelectedElement generic_section_list = do
current_focus <- generic_section_list ^. sectionListFocusRingL & F.focusGetCurrent current_focus <- generic_section_list ^. sectionListFocusRingL & F.focusGetCurrent
let current_section = generic_section_list ^. sectionL current_focus let current_section = generic_section_list ^. sectionL current_focus
L.listSelectedElement current_section L.listSelectedElement current_section

View File

@ -9,7 +9,7 @@
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
{- {-
A very simple information-only widget with no handler. A very simple information-only widget with no handler.
-} -}
module GHCup.Brick.Widgets.Tutorial (draw) where module GHCup.Brick.Widgets.Tutorial (draw) where
@ -74,4 +74,4 @@ draw =
] ]
, Brick.txt " " , Brick.txt " "
]) ])
<=> Brick.padRight Brick.Max (Brick.txt "Press q to exit the tutorial") <=> Brick.padRight Brick.Max (Brick.txt "Press c+ctrl to exit the tutorial")

View File

@ -17,7 +17,7 @@ module GHCup.BrickMain where
import GHCup.Types import GHCup.Types
( Settings(noColor), ( Settings(noColor),
AppState(ghcupInfo, settings, keyBindings, loggerConfig), KeyBindings (..) ) AppState(ghcupInfo, settings, keyBindings, loggerConfig), KeyBindings (..), KeyCombination (KeyCombination) )
import GHCup.Prelude.Logger ( logError ) import GHCup.Prelude.Logger ( logError )
import qualified GHCup.Brick.Actions as Actions import qualified GHCup.Brick.Actions as Actions
import qualified GHCup.Brick.Common as Common import qualified GHCup.Brick.Common as Common
@ -29,6 +29,7 @@ import qualified GHCup.Brick.Widgets.SectionList as Navigation
import qualified GHCup.Brick.Widgets.Menus.AdvanceInstall as AdvanceInstall import qualified GHCup.Brick.Widgets.Menus.AdvanceInstall as AdvanceInstall
import qualified GHCup.Brick.Widgets.Menus.CompileGHC as CompileGHC import qualified GHCup.Brick.Widgets.Menus.CompileGHC as CompileGHC
import qualified Brick import qualified Brick
import qualified Graphics.Vty as Vty
import Control.Monad.Reader ( ReaderT(runReaderT) ) import Control.Monad.Reader ( ReaderT(runReaderT) )
import Data.Functor ( ($>) ) import Data.Functor ( ($>) )
@ -37,6 +38,7 @@ import Prelude hiding ( appendFile )
import System.Exit ( ExitCode(ExitFailure), exitWith ) import System.Exit ( ExitCode(ExitFailure), exitWith )
import qualified Data.Text as T import qualified Data.Text as T
import qualified GHCup.Brick.Widgets.Menus.CompileHLS as CompileHLS
@ -50,14 +52,14 @@ brickMain s = do
Right ad -> do Right ad -> do
let initial_list = Actions.constructList ad Common.defaultAppSettings Nothing let initial_list = Actions.constructList ad Common.defaultAppSettings Nothing
current_element = Navigation.sectionListSelectedElement initial_list current_element = Navigation.sectionListSelectedElement initial_list
exit_key = bQuit . keyBindings $ s exit_key = KeyCombination (Vty.KChar 'c') [Vty.MCtrl] -- bQuit . keyBindings $ s
case current_element of case current_element of
Nothing -> do Nothing -> do
flip runReaderT s $ logError "Error building app state: empty ResultList" flip runReaderT s $ logError "Error building app state: empty ResultList"
exitWith $ ExitFailure 2 exitWith $ ExitFailure 2
Just (_, e) -> Just (_, e) ->
let initapp = let initapp =
BrickApp.app BrickApp.app
(Attributes.defaultAttributes $ noColor $ settings s) (Attributes.defaultAttributes $ noColor $ settings s)
(Attributes.dimAttributes $ noColor $ settings s) (Attributes.dimAttributes $ noColor $ settings s)
initstate = initstate =
@ -65,11 +67,12 @@ brickMain s = do
Common.defaultAppSettings Common.defaultAppSettings
initial_list initial_list
(ContextMenu.create e exit_key) (ContextMenu.create e exit_key)
(AdvanceInstall.create (bQuit . keyBindings $ s )) (AdvanceInstall.create exit_key)
(CompileGHC.create exit_key) (CompileGHC.create exit_key)
(CompileHLS.create exit_key)
(keyBindings s) (keyBindings s)
Common.Navigation Common.Navigation
in Brick.defaultMain initapp initstate in Brick.defaultMain initapp initstate
$> () $> ()
Left e -> do Left e -> do
flip runReaderT s $ logError $ "Error building app state: " <> T.pack (show e) flip runReaderT s $ logError $ "Error building app state: " <> T.pack (show e)