{-# 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.Tutorial (draw) where
import qualified GHCup.Brick.Common as Common
import qualified GHCup.Brick.Attributes as Attributes
import GHCup.Types (KeyCombination(..))
import Brick
( Padding(Max),
Widget(..),
(<=>), (<+>))
import qualified Brick
import Brick.Widgets.Center ( center )
import Prelude hiding ( appendFile )
draw :: KeyCombination -> Widget Common.Name
draw :: KeyCombination -> Widget Name
draw KeyCombination
exitKey =
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
"Tutorial"
(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) -> [Widget Name] -> [Widget Name]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Widget Name -> Widget Name
forall n. Widget n -> Widget n
center
[ [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
mkTextBox [Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
"GHCup is a distribution channel for Haskell's tools."]
, Widget Name
forall n. Widget n
Common.separator
, [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
"This symbol "
, AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
Brick.withAttr AttrName
Attributes.installedAttr (String -> Widget Name
forall n. String -> Widget n
Brick.str String
Common.installedSign)
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
" means that the tool is installed but not in used"
]
, [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [
Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
"This symbol "
, AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
Brick.withAttr AttrName
Attributes.setAttr (String -> Widget Name
forall n. String -> Widget n
Brick.str String
Common.setSign)
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
" means that the tool is installed and in used"
]
, [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [
Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
"This symbol "
, AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
Brick.withAttr AttrName
Attributes.notInstalledAttr (String -> Widget Name
forall n. String -> Widget n
Brick.str String
Common.notInstalledSign)
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
" means that the tool isn't installed"
]
]
, Widget Name
forall n. Widget n
Common.separator
, [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
mkTextBox [
[Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [
AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
Brick.withAttr AttrName
Attributes.recommendedAttr (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ String -> Widget Name
forall n. String -> Widget n
Brick.str String
"recommended"
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
" tag is based on community adoption, known bugs, etc... So It makes this version the least experimental"
]
, [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [
AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
Brick.withAttr AttrName
Attributes.latestAttr (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ String -> Widget Name
forall n. String -> Widget n
Brick.str String
"latest"
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
" tag is for the latest distributed version of the tool"
]
, [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
Brick.hBox [
AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
Brick.withAttr AttrName
Attributes.latestAttr (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ String -> Widget Name
forall n. String -> Widget n
Brick.str String
"hls-powered"
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
" denotes the compiler version supported by the currently set ("
, AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
Brick.withAttr AttrName
Attributes.setAttr (String -> Widget Name
forall n. String -> Widget n
Brick.str String
Common.setSign)
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txt Text
") hls"
]
, Text -> Widget Name
forall n. Text -> Widget n
Brick.txtWrap Text
"base-X.Y.Z.W tag is the minimun version of the base package admited in such ghc version"
]
, 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
<=> (Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
Brick.padRight Padding
Brick.Max (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$
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
exitKey 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 exit the tutorial")