{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# OPTIONS_GHC -Wno-unused-record-wildcards #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module GHCup.Brick.Widgets.KeyInfo where
import GHCup.Types ( KeyBindings(..) )
import qualified GHCup.Brick.Common as Common
import Brick
( Padding(Max),
Widget(..),
(<+>),
(<=>))
import qualified Brick
import Brick.Widgets.Center ( center )
import Prelude hiding ( appendFile )
draw :: KeyBindings -> Widget Common.Name
draw :: KeyBindings -> Widget Name
draw KeyBindings {KeyCombination
bUp :: KeyCombination
bDown :: KeyCombination
bQuit :: KeyCombination
bInstall :: KeyCombination
bUninstall :: KeyCombination
bSet :: KeyCombination
bChangelog :: KeyCombination
bShowAllVersions :: KeyCombination
bChangelog :: KeyBindings -> KeyCombination
bDown :: KeyBindings -> KeyCombination
bInstall :: KeyBindings -> KeyCombination
bQuit :: KeyBindings -> KeyCombination
bSet :: KeyBindings -> KeyCombination
bShowAllVersions :: KeyBindings -> KeyCombination
bUninstall :: KeyBindings -> KeyCombination
bUp :: KeyBindings -> KeyCombination
..} =
let
mkTextBox :: [Widget n] -> Widget n
mkTextBox = Int -> Widget n -> Widget n
forall n. Int -> Widget n -> Widget n
Brick.hLimitPercent Int
70 (Widget n -> Widget n)
-> ([Widget n] -> Widget n) -> [Widget n] -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
Brick.vBox ([Widget n] -> Widget n)
-> ([Widget n] -> [Widget n]) -> [Widget n] -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Widget n -> Widget n) -> [Widget n] -> [Widget n]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Padding -> Widget n -> Widget n
forall n. Padding -> Widget n -> Widget n
Brick.padRight Padding
Brick.Max)
in Text -> Widget Name -> Widget Name
forall n. Text -> Widget n -> Widget n
Common.frontwardLayer Text
"Key Actions"
(Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.vBox [
Widget Name -> Widget Name
forall n. Widget n -> Widget n
center (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$
[Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
mkTextBox [
[Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [
Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
"Press "
, KeyCombination -> Widget Name
forall n. KeyCombination -> Widget n
Common.keyToWidget KeyCombination
bUp, Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
" and ", KeyCombination -> Widget Name
forall n. KeyCombination -> Widget n
Common.keyToWidget KeyCombination
bDown
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
" to navigate the list of tools"
]
, [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [
Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
"Press "
, KeyCombination -> Widget Name
forall n. KeyCombination -> Widget n
Common.keyToWidget KeyCombination
bInstall
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
" to install the selected tool. Notice, you may need to set it as default afterwards"
]
, [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [
Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
"Press "
, KeyCombination -> Widget Name
forall n. KeyCombination -> Widget n
Common.keyToWidget KeyCombination
bSet
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
" to set a tool as the one for use"
]
, [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [
Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
"Press "
, KeyCombination -> Widget Name
forall n. KeyCombination -> Widget n
Common.keyToWidget KeyCombination
bUninstall
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
" to uninstall a tool"
]
, [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [
Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
"Press "
, KeyCombination -> Widget Name
forall n. KeyCombination -> Widget n
Common.keyToWidget KeyCombination
bChangelog
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
" to open the tool's changelog. It will open a web browser"
]
, [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [
Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
"Press "
, KeyCombination -> Widget Name
forall n. KeyCombination -> Widget n
Common.keyToWidget KeyCombination
bShowAllVersions
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
" to show older version of each tool"
]
]
]
Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<=> [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
"Press " Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<+> KeyCombination -> Widget Name
forall n. KeyCombination -> Widget n
Common.keyToWidget KeyCombination
bQuit Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<+> Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
" to return to Navigation" Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<+> Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
Brick.padRight Padding
Brick.Max (Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
" ") Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<+> Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
"Press Enter to go to the Tutorial"]