Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion ghcup.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -377,7 +377,7 @@ library ghcup-tui
GHCup.Brick.Widgets.SectionList
GHCup.Brick.Widgets.Menu
GHCup.Brick.Widgets.Menus.Context
GHCup.Brick.Widgets.Menus.AdvanceInstall
GHCup.Brick.Widgets.Menus.AdvancedInstall
GHCup.Brick.Widgets.Menus.CompileGHC
GHCup.Brick.Widgets.Menus.CompileHLS
GHCup.Brick.Actions
Expand Down
30 changes: 15 additions & 15 deletions lib-tui/GHCup/Brick/Actions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import GHCup.Brick.BrickState
import GHCup.Brick.Widgets.SectionList
import qualified GHCup.Brick.Widgets.Menus.Context as ContextMenu
import GHCup.Brick.Widgets.Navigation (BrickInternalState)
import qualified GHCup.Brick.Widgets.Menus.AdvanceInstall as AdvanceInstall
import qualified GHCup.Brick.Widgets.Menus.AdvancedInstall as AdvancedInstall
import qualified GHCup.Brick.Widgets.Menus.CompileGHC as CompileGHC
import GHCup.Brick.Widgets.Menu (MenuKeyBindings(..))

Expand Down Expand Up @@ -182,19 +182,19 @@ withIOAction action = do
Left err -> throwIO $ userError err

installWithOptions :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> AdvanceInstall.InstallOptions
=> AdvancedInstall.InstallOptions
-> (Int, ListResult)
-> m (Either String ())
installWithOptions opts (_, ListResult {..}) = do
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
installTargets = opts ^. AdvanceInstall.installTargetsL
v = fromMaybe (GHCTargetVersion lCross lVer) (opts ^. AdvanceInstall.instVersionL)
misolated = opts ^. AdvancedInstall.isolateDirL
shouldIsolate = maybe GHCupInternal IsolateDir (opts ^. AdvancedInstall.isolateDirL)
shouldForce = opts ^. AdvancedInstall.forceInstallL
shouldSet = opts ^. AdvancedInstall.instSetL
extraArgs = opts ^. AdvancedInstall.addConfArgsL
installTargets = opts ^. AdvancedInstall.installTargetsL
v = fromMaybe (GHCTargetVersion lCross lVer) (opts ^. AdvancedInstall.instVersionL)
toolV = _tvVersion v
let run =
runResourceT
Expand Down Expand Up @@ -244,7 +244,7 @@ installWithOptions opts (_, ListResult {..}) = do
lift $ logWarn
"...waiting for 5 seconds, you can still abort..."
liftIO $ threadDelay 5000000 -- give the user a sec to intervene
case opts ^. AdvanceInstall.instBindistL of
case opts ^. AdvancedInstall.instBindistL of
Nothing -> do
liftE $
runBothE'
Expand Down Expand Up @@ -272,7 +272,7 @@ installWithOptions opts (_, ListResult {..}) = do
lift $ logWarn
"...waiting for 5 seconds, you can still abort..."
liftIO $ threadDelay 5000000 -- give the user a sec to intervene
case opts ^. AdvanceInstall.instBindistL of
case opts ^. AdvancedInstall.instBindistL of
Nothing -> do
liftE $
runBothE'
Expand Down Expand Up @@ -301,7 +301,7 @@ installWithOptions opts (_, ListResult {..}) = do
lift $ logWarn
"...waiting for 5 seconds, you can still abort..."
liftIO $ threadDelay 5000000 -- give the user a sec to intervene
case opts ^. AdvanceInstall.instBindistL of
case opts ^. AdvancedInstall.instBindistL of
Nothing -> do
liftE $
runBothE'
Expand All @@ -321,7 +321,7 @@ installWithOptions opts (_, ListResult {..}) = do

Stack -> do
let vi = getVersionInfo v Stack dls
case opts ^. AdvanceInstall.instBindistL of
case opts ^. AdvancedInstall.instBindistL of
Nothing -> do
liftE $
runBothE'
Expand Down Expand Up @@ -363,7 +363,7 @@ installWithOptions opts (_, ListResult {..}) = do

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 Nothing False [] "install")
install' = installWithOptions (AdvancedInstall.InstallOptions Nothing False Nothing Nothing False [] "install")

set' :: (MonadReader AppState m, MonadIO m, MonadThrow m, MonadFail m, MonadMask m, MonadUnliftIO m, Alternative m)
=> (Int, ListResult)
Expand Down Expand Up @@ -759,7 +759,7 @@ keyHandlers KeyBindings {..} =
, (bUp, const "Up", Common.zoom appState moveUp)
, (bDown, const "Down", Common.zoom appState moveDown)
, (KeyCombination (Vty.KChar 'h') [], const "help", mode .= KeyInfo)
, (KeyCombination Vty.KEnter [], const "advance options", createMenuforTool )
, (KeyCombination Vty.KEnter [], const "advanced options", createMenuforTool )
]
where
createMenuforTool = do
Expand Down
14 changes: 7 additions & 7 deletions lib-tui/GHCup/Brick/App.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,15 +25,15 @@ module GHCup.Brick.App where

import qualified GHCup.Brick.Actions as Actions
import qualified GHCup.Brick.Attributes as Attributes
import GHCup.Brick.BrickState (BrickState (..), advanceInstallMenu, appKeys, appSettings, appState, contextMenu, mode, compileGHCMenu, compileHLSMenu)
import GHCup.Brick.BrickState (BrickState (..), advancedInstallMenu, appKeys, appSettings, appState, contextMenu, mode, compileGHCMenu, compileHLSMenu)
import GHCup.Brick.Common (Mode (..), Name (..))
import qualified GHCup.Brick.Common as Common
import qualified GHCup.Brick.Widgets.KeyInfo as KeyInfo
import qualified GHCup.Brick.Widgets.Menus.Context as ContextMenu
import qualified GHCup.Brick.Widgets.Navigation as Navigation
import qualified GHCup.Brick.Widgets.Tutorial as Tutorial
import qualified GHCup.Brick.Widgets.Menu as Menu
import qualified GHCup.Brick.Widgets.Menus.AdvanceInstall as AdvanceInstall
import qualified GHCup.Brick.Widgets.Menus.AdvancedInstall as AdvancedInstall

import GHCup.List (ListResult)
import GHCup.Types (AppState (AppState, keyBindings), KeyCombination (KeyCombination), KeyBindings (..))
Expand Down Expand Up @@ -103,7 +103,7 @@ drawUI dimAttrs st =
Tutorial -> [Tutorial.draw (bQuit $ st ^. appKeys), navg]
KeyInfo -> [KeyInfo.draw (st ^. appKeys), navg]
ContextPanel -> [ContextMenu.draw (st ^. contextMenu), navg]
AdvanceInstallPanel -> AdvanceInstall.draw (st ^. advanceInstallMenu) ++ [navg]
AdvancedInstallPanel -> AdvancedInstall.draw (st ^. advancedInstallMenu) ++ [navg]
CompileGHCPanel -> CompileGHC.draw (st ^. compileGHCMenu) ++ [navg]
CompileHLSPanel -> CompileHLS.draw (st ^. compileHLSMenu) ++ [navg]

Expand Down Expand Up @@ -146,13 +146,13 @@ contextMenuHandler ev = do
case (ev, focusedElement) of
(_ , Nothing) -> pure ()
(VtyEvent (Vty.EvKey k m), Just n) | k == exitKey && m == mods -> mode .= Navigation
(VtyEvent (Vty.EvKey Vty.KEnter []), Just (Common.MenuElement Common.AdvanceInstallButton) ) -> mode .= Common.AdvanceInstallPanel
(VtyEvent (Vty.EvKey Vty.KEnter []), Just (Common.MenuElement Common.AdvancedInstallButton) ) -> mode .= Common.AdvancedInstallPanel
(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
--
advanceInstallHandler :: BrickEvent Name e -> EventM Name BrickState ()
advanceInstallHandler = menuWithOverlayHandler advanceInstallMenu Actions.installWithOptions AdvanceInstall.handler
advancedInstallHandler :: BrickEvent Name e -> EventM Name BrickState ()
advancedInstallHandler = menuWithOverlayHandler advancedInstallMenu Actions.installWithOptions AdvancedInstall.handler

compileGHCHandler :: BrickEvent Name e -> EventM Name BrickState ()
compileGHCHandler = menuWithOverlayHandler compileGHCMenu Actions.compileGHC CompileGHC.handler
Expand Down Expand Up @@ -190,6 +190,6 @@ eventHandler ev = do
Tutorial -> tutorialHandler ev
Navigation -> navigationHandler ev
ContextPanel -> contextMenuHandler ev
AdvanceInstallPanel -> advanceInstallHandler ev
AdvancedInstallPanel -> advancedInstallHandler ev
CompileGHCPanel -> compileGHCHandler ev
CompileHLSPanel -> compileHLSHandler ev
20 changes: 10 additions & 10 deletions lib-tui/GHCup/Brick/BrickState.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,22 +32,22 @@ import GHCup.Types ( KeyBindings )
import GHCup.Brick.Common ( BrickData(..), BrickSettings(..), Mode(..))
import GHCup.Brick.Widgets.Navigation ( BrickInternalState)
import GHCup.Brick.Widgets.Menus.Context (ContextMenu)
import GHCup.Brick.Widgets.Menus.AdvanceInstall (AdvanceInstallMenu)
import GHCup.Brick.Widgets.Menus.AdvancedInstall (AdvancedInstallMenu)
import GHCup.Brick.Widgets.Menus.CompileGHC (CompileGHCMenu)
import Optics.TH (makeLenses)
import GHCup.Brick.Widgets.Menus.CompileHLS (CompileHLSMenu)


data BrickState = BrickState
{ _appData :: BrickData
, _appSettings :: BrickSettings
, _appState :: BrickInternalState
, _contextMenu :: ContextMenu
, _advanceInstallMenu :: AdvanceInstallMenu
, _compileGHCMenu :: CompileGHCMenu
, _compileHLSMenu :: CompileHLSMenu
, _appKeys :: KeyBindings
, _mode :: Mode
{ _appData :: BrickData
, _appSettings :: BrickSettings
, _appState :: BrickInternalState
, _contextMenu :: ContextMenu
, _advancedInstallMenu :: AdvancedInstallMenu
, _compileGHCMenu :: CompileGHCMenu
, _compileHLSMenu :: CompileHLSMenu
, _appKeys :: KeyBindings
, _mode :: Mode
}
--deriving Show

Expand Down
10 changes: 5 additions & 5 deletions lib-tui/GHCup/Brick/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ module GHCup.Brick.Common (
UrlEditBox, SetCheckBox, IsolateEditBox, ForceCheckBox, AdditionalEditBox
, TargetGhcEditBox, BootstrapGhcEditBox, HadrianGhcEditBox, JobsEditBox, BuildConfigEditBox
, PatchesEditBox, CrossTargetEditBox, AddConfArgsEditBox, OvewrwiteVerEditBox
, BuildFlavourEditBox, BuildSystemEditBox, OkButton, AdvanceInstallButton
, BuildFlavourEditBox, BuildSystemEditBox, OkButton, AdvancedInstallButton
, CompileGHCButton, CompileHLSButton, CabalProjectEditBox
, CabalProjectLocalEditBox, UpdateCabalCheckBox, GitRefEditBox
, BootstrapGhcSelectBox, HadrianGhcSelectBox, ToolVersionBox, GHCInstallTargets
Expand Down Expand Up @@ -77,8 +77,8 @@ newtype ResourceId = ResourceId Int deriving (Eq, Ord, Show)

pattern OkButton :: ResourceId
pattern OkButton = ResourceId 0
pattern AdvanceInstallButton :: ResourceId
pattern AdvanceInstallButton = ResourceId 100
pattern AdvancedInstallButton :: ResourceId
pattern AdvancedInstallButton = ResourceId 100
pattern CompileGHCButton :: ResourceId
pattern CompileGHCButton = ResourceId 101
pattern CompileHLSButton :: ResourceId
Expand Down Expand Up @@ -149,7 +149,7 @@ data Name = AllTools -- ^ The main list widget
| TutorialBox -- ^ The tutorial widget
| ContextBox -- ^ The resource for Context Menu
| CompileGHCBox -- ^ The resource for CompileGHC Menu
| AdvanceInstallBox -- ^ The resource for AdvanceInstall Menu
| AdvancedInstallBox -- ^ The resource for AdvancedInstall Menu
| 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
-- invisible, or just one of them is visible.
Expand All @@ -161,7 +161,7 @@ data Mode = Navigation
| KeyInfo
| Tutorial
| ContextPanel
| AdvanceInstallPanel
| AdvancedInstallPanel
| CompileGHCPanel
| CompileHLSPanel
deriving (Eq, Show, Ord)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -14,9 +14,9 @@
{-# LANGUAGE InstanceSigs #-}
{-# OPTIONS_GHC -Wno-incomplete-patterns #-}

module GHCup.Brick.Widgets.Menus.AdvanceInstall (
module GHCup.Brick.Widgets.Menus.AdvancedInstall (
InstallOptions (..),
AdvanceInstallMenu,
AdvancedInstallMenu,
create,
handler,
draw,
Expand Down Expand Up @@ -70,10 +70,10 @@ makeLensesFor [
]
''InstallOptions

type AdvanceInstallMenu = Menu InstallOptions Name
type AdvancedInstallMenu = Menu InstallOptions Name

create :: MenuKeyBindings -> AdvanceInstallMenu
create k = Menu.createMenu AdvanceInstallBox initialState "Advance Install" validator k [ok] fields
create :: MenuKeyBindings -> AdvancedInstallMenu
create k = Menu.createMenu AdvancedInstallBox initialState "Advanced Install" validator k [ok] fields
where
initialInstallTargets = "install"
initialState = InstallOptions Nothing False Nothing Nothing False [] initialInstallTargets
Expand Down Expand Up @@ -124,12 +124,12 @@ create k = Menu.createMenu AdvanceInstallBox initialState "Advance Install" vali
]

ok = Menu.createButtonField (Common.MenuElement Common.OkButton)
& Menu.fieldLabelL .~ "Advance Install"
& Menu.fieldLabelL .~ "Advanced Install"
& Menu.fieldHelpMsgL .~ "Install with options below"

handler :: BrickEvent Name e -> EventM Name AdvanceInstallMenu ()
handler :: BrickEvent Name e -> EventM Name AdvancedInstallMenu ()
handler = Menu.handlerMenu


draw :: AdvanceInstallMenu -> [Widget Name]
draw :: AdvancedInstallMenu -> [Widget Name]
draw = Menu.drawMenu
4 changes: 2 additions & 2 deletions lib-tui/GHCup/Brick/Widgets/Menus/Context.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,9 +32,9 @@ create :: ListResult -> MenuKeyBindings -> ContextMenu
create lr keyBindings = Menu.createMenu Common.ContextBox lr "" validator keyBindings buttons []
where
advInstallButton =
Menu.createButtonField (MenuElement Common.AdvanceInstallButton)
Menu.createButtonField (MenuElement Common.AdvancedInstallButton)
& Menu.fieldLabelL .~ "Install"
& Menu.fieldHelpMsgL .~ "Advance Installation Settings"
& Menu.fieldHelpMsgL .~ "Advanced Installation Settings"
compileGhcButton =
Menu.createButtonField (MenuElement Common.CompileGHCButton)
& Menu.fieldLabelL .~ "Compile"
Expand Down
4 changes: 2 additions & 2 deletions lib-tui/GHCup/BrickMain.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ import qualified GHCup.Brick.Attributes as Attributes
import qualified GHCup.Brick.BrickState as AppState
import qualified GHCup.Brick.Widgets.Menus.Context as ContextMenu
import qualified GHCup.Brick.Widgets.SectionList as Navigation
import qualified GHCup.Brick.Widgets.Menus.AdvanceInstall as AdvanceInstall
import qualified GHCup.Brick.Widgets.Menus.AdvancedInstall as AdvancedInstall
import qualified GHCup.Brick.Widgets.Menus.CompileGHC as CompileGHC
import GHCup.Brick.Widgets.Menu (MenuKeyBindings(..))
import qualified Brick
Expand Down Expand Up @@ -73,7 +73,7 @@ brickMain s = do
Common.defaultAppSettings
initial_list
(ContextMenu.create e exit_key)
(AdvanceInstall.create exit_key)
(AdvancedInstall.create exit_key)
(CompileGHC.create exit_key installedGHCs)
(CompileHLS.create exit_key installedGHCs)
(keyBindings s)
Expand Down
Loading