{-# 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,
gitRef,
)
where
import GHCup.Brick.Widgets.Menu (Menu, MenuKeyBindings)
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 (VersionPattern, ToolVersion(..))
import URI.ByteString (URI)
import qualified Data.Text as T
import Data.Bifunctor (Bifunctor(..))
import qualified Data.List.NonEmpty as NE
import Data.Function ((&))
import Optics ((.~))
import Data.Char (isSpace)
import Data.Versions
import Control.Applicative (Alternative((<|>)))
import Text.Read (readEither)
import qualified GHCup.Utils.Parsers as Utils
import Text.PrettyPrint.HughesPJClass ( prettyShow )
data CompileHLSOptions = CompileHLSOptions
{ CompileHLSOptions -> Maybe Int
_jobs :: Maybe Int
, CompileHLSOptions -> Bool
_setCompile :: Bool
, CompileHLSOptions -> Bool
_updateCabal :: Bool
, CompileHLSOptions -> Maybe [VersionPattern]
_overwriteVer :: Maybe [VersionPattern]
, CompileHLSOptions -> Maybe String
_isolateDir :: Maybe FilePath
, CompileHLSOptions -> Maybe (Either String URI)
_cabalProject :: Maybe (Either FilePath URI)
, CompileHLSOptions -> Maybe URI
_cabalProjectLocal :: Maybe URI
, CompileHLSOptions -> Maybe (Either String [URI])
_patches :: Maybe (Either FilePath [URI])
, CompileHLSOptions -> [ToolVersion]
_targetGHCs :: [ToolVersion]
, CompileHLSOptions -> [Text]
_cabalArgs :: [T.Text]
, CompileHLSOptions -> Maybe String
_gitRef :: Maybe String
} deriving (CompileHLSOptions -> CompileHLSOptions -> Bool
(CompileHLSOptions -> CompileHLSOptions -> Bool)
-> (CompileHLSOptions -> CompileHLSOptions -> Bool)
-> Eq CompileHLSOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompileHLSOptions -> CompileHLSOptions -> Bool
== :: CompileHLSOptions -> CompileHLSOptions -> Bool
$c/= :: CompileHLSOptions -> CompileHLSOptions -> Bool
/= :: CompileHLSOptions -> CompileHLSOptions -> Bool
Eq, Int -> CompileHLSOptions -> ShowS
[CompileHLSOptions] -> ShowS
CompileHLSOptions -> String
(Int -> CompileHLSOptions -> ShowS)
-> (CompileHLSOptions -> String)
-> ([CompileHLSOptions] -> ShowS)
-> Show CompileHLSOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompileHLSOptions -> ShowS
showsPrec :: Int -> CompileHLSOptions -> ShowS
$cshow :: CompileHLSOptions -> String
show :: CompileHLSOptions -> String
$cshowList :: [CompileHLSOptions] -> ShowS
showList :: [CompileHLSOptions] -> ShowS
Show)
makeLenses ''CompileHLSOptions
type = Menu CompileHLSOptions Name
create :: MenuKeyBindings -> [Version] -> CompileHLSMenu
create :: MenuKeyBindings -> [Version] -> CompileHLSMenu
create MenuKeyBindings
k [Version]
availableGHCs = Name
-> CompileHLSOptions
-> Text
-> (CompileHLSOptions -> Maybe Text)
-> MenuKeyBindings
-> [MenuField CompileHLSOptions Name]
-> [MenuField CompileHLSOptions Name]
-> CompileHLSMenu
forall n s.
n
-> s
-> Text
-> (s -> Maybe Text)
-> MenuKeyBindings
-> [Button s n]
-> [Button s n]
-> Menu s n
Menu.createMenu Name
CompileGHCBox CompileHLSOptions
initialState Text
"Compile HLS" CompileHLSOptions -> Maybe Text
forall {a}. IsString a => CompileHLSOptions -> Maybe a
validator MenuKeyBindings
k [MenuField CompileHLSOptions Name]
forall {s}. [MenuField s Name]
buttons [MenuField CompileHLSOptions Name]
fields
where
initialState :: CompileHLSOptions
initialState =
Maybe Int
-> Bool
-> Bool
-> Maybe [VersionPattern]
-> Maybe String
-> Maybe (Either String URI)
-> Maybe URI
-> Maybe (Either String [URI])
-> [ToolVersion]
-> [Text]
-> Maybe String
-> CompileHLSOptions
CompileHLSOptions
Maybe Int
forall a. Maybe a
Nothing
Bool
False
Bool
False
Maybe [VersionPattern]
forall a. Maybe a
Nothing
Maybe String
forall a. Maybe a
Nothing
Maybe (Either String URI)
forall a. Maybe a
Nothing
Maybe URI
forall a. Maybe a
Nothing
Maybe (Either String [URI])
forall a. Maybe a
Nothing
[]
[]
Maybe String
forall a. Maybe a
Nothing
validator :: CompileHLSOptions -> Maybe a
validator CompileHLSOptions {Bool
[Text]
[ToolVersion]
Maybe Int
Maybe String
Maybe [VersionPattern]
Maybe (Either String [URI])
Maybe (Either String URI)
Maybe URI
_jobs :: CompileHLSOptions -> Maybe Int
_setCompile :: CompileHLSOptions -> Bool
_updateCabal :: CompileHLSOptions -> Bool
_overwriteVer :: CompileHLSOptions -> Maybe [VersionPattern]
_isolateDir :: CompileHLSOptions -> Maybe String
_cabalProject :: CompileHLSOptions -> Maybe (Either String URI)
_cabalProjectLocal :: CompileHLSOptions -> Maybe URI
_patches :: CompileHLSOptions -> Maybe (Either String [URI])
_targetGHCs :: CompileHLSOptions -> [ToolVersion]
_cabalArgs :: CompileHLSOptions -> [Text]
_gitRef :: CompileHLSOptions -> Maybe String
_jobs :: Maybe Int
_setCompile :: Bool
_updateCabal :: Bool
_overwriteVer :: Maybe [VersionPattern]
_isolateDir :: Maybe String
_cabalProject :: Maybe (Either String URI)
_cabalProjectLocal :: Maybe URI
_patches :: Maybe (Either String [URI])
_targetGHCs :: [ToolVersion]
_cabalArgs :: [Text]
_gitRef :: Maybe String
..} = case (Bool
_setCompile, Maybe String
_isolateDir) of
(Bool
True, Just String
_) -> a -> Maybe a
forall a. a -> Maybe a
Just a
"Cannot set active when doing an isolated install"
(Bool, Maybe String)
_ -> if [ToolVersion] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ToolVersion]
_targetGHCs
then a -> Maybe a
forall a. a -> Maybe a
Just a
"Specify at least one valid target GHC"
else Maybe a
forall a. Maybe a
Nothing
emptyEditor :: Text -> Bool
emptyEditor Text
i = Text -> Bool
T.null Text
i Bool -> Bool -> Bool
|| (Text
i Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"\n")
whenEmpty :: a -> (T.Text -> Either Menu.ErrorMessage a) -> T.Text -> Either Menu.ErrorMessage a
whenEmpty :: forall a. a -> (Text -> Either Text a) -> Text -> Either Text a
whenEmpty a
emptyval Text -> Either Text a
f Text
i = if Bool -> Bool
not (Text -> Bool
emptyEditor Text
i) then Text -> Either Text a
f Text
i else a -> Either Text a
forall a b. b -> Either a b
Right a
emptyval
readUri :: T.Text -> Either Menu.ErrorMessage URI
readUri :: Text -> Either Text URI
readUri = (String -> Text) -> Either String URI -> Either Text URI
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first String -> Text
T.pack (Either String URI -> Either Text URI)
-> (Text -> Either String URI) -> Text -> Either Text URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Either String URI
Utils.uriParser (String -> Either String URI)
-> (Text -> String) -> Text -> Either String URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
cabalProjectV :: T.Text -> Either Menu.ErrorMessage (Maybe (Either FilePath URI))
cabalProjectV :: Text -> Either Text (Maybe (Either String URI))
cabalProjectV = Maybe (Either String URI)
-> (Text -> Either Text (Maybe (Either String URI)))
-> Text
-> Either Text (Maybe (Either String URI))
forall a. a -> (Text -> Either Text a) -> Text -> Either Text a
whenEmpty Maybe (Either String URI)
forall a. Maybe a
Nothing Text -> Either Text (Maybe (Either String URI))
parseFileOrUri
where
parseFileOrUri :: Text -> Either Text (Maybe (Either String URI))
parseFileOrUri Text
i =
let x :: Either String (Either a URI)
x = (Text -> String)
-> (URI -> Either a URI)
-> Either Text URI
-> Either String (Either a URI)
forall a b c d. (a -> b) -> (c -> d) -> Either a c -> Either b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Text -> String
T.unpack URI -> Either a URI
forall a b. b -> Either a b
Right (Text -> Either Text URI
readUri Text
i)
y :: Either a (Either String b)
y = Either String b -> Either a (Either String b)
forall a b. b -> Either a b
Right (Either String b -> Either a (Either String b))
-> (Text -> Either String b) -> Text -> Either a (Either String b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Either String b
forall a b. a -> Either a b
Left (String -> Either String b)
-> (Text -> String) -> Text -> Either String b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack (Text -> Either a (Either String b))
-> Text -> Either a (Either String b)
forall a b. (a -> b) -> a -> b
$ Text
i
in (String -> Text)
-> (Either String URI -> Maybe (Either String URI))
-> Either String (Either String URI)
-> Either Text (Maybe (Either String URI))
forall a b c d. (a -> b) -> (c -> d) -> Either a c -> Either b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap String -> Text
T.pack Either String URI -> Maybe (Either String URI)
forall a. a -> Maybe a
Just (Either String (Either String URI)
-> Either Text (Maybe (Either String URI)))
-> Either String (Either String URI)
-> Either Text (Maybe (Either String URI))
forall a b. (a -> b) -> a -> b
$ Either String (Either String URI)
forall {a}. Either String (Either a URI)
x Either String (Either String URI)
-> Either String (Either String URI)
-> Either String (Either String URI)
forall a. Either String a -> Either String a -> Either String a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Either String (Either String URI)
forall {a} {b}. Either a (Either String b)
y
cabalProjectLocalV :: T.Text -> Either Menu.ErrorMessage (Maybe URI)
cabalProjectLocalV :: Text -> Either Text (Maybe URI)
cabalProjectLocalV = Maybe URI
-> (Text -> Either Text (Maybe URI))
-> Text
-> Either Text (Maybe URI)
forall a. a -> (Text -> Either Text a) -> Text -> Either Text a
whenEmpty Maybe URI
forall a. Maybe a
Nothing ((URI -> Maybe URI) -> Either Text URI -> Either Text (Maybe URI)
forall b c a. (b -> c) -> Either a b -> Either a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second URI -> Maybe URI
forall a. a -> Maybe a
Just (Either Text URI -> Either Text (Maybe URI))
-> (Text -> Either Text URI) -> Text -> Either Text (Maybe URI)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text URI
readUri)
ghcVersionTagEither :: T.Text -> Either Menu.ErrorMessage [ToolVersion]
ghcVersionTagEither :: Text -> Either Text [ToolVersion]
ghcVersionTagEither = [ToolVersion]
-> (Text -> Either Text [ToolVersion])
-> Text
-> Either Text [ToolVersion]
forall a. a -> (Text -> Either Text a) -> Text -> Either Text a
whenEmpty [] ((Text -> Either Text [ToolVersion])
-> Text -> Either Text [ToolVersion])
-> (Text -> Either Text [ToolVersion])
-> Text
-> Either Text [ToolVersion]
forall a b. (a -> b) -> a -> b
$ (String -> Text)
-> Either String [ToolVersion] -> Either Text [ToolVersion]
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first String -> Text
T.pack (Either String [ToolVersion] -> Either Text [ToolVersion])
-> (Text -> Either String [ToolVersion])
-> Text
-> Either Text [ToolVersion]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Either String ToolVersion)
-> [Text] -> Either String [ToolVersion]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (String -> Either String ToolVersion
Utils.ghcVersionTagEither (String -> Either String ToolVersion)
-> (Text -> String) -> Text -> Either String ToolVersion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack) ([Text] -> Either String [ToolVersion])
-> (Text -> [Text]) -> Text -> Either String [ToolVersion]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> [Text]
T.split Char -> Bool
isSpace
overWriteVersionParser :: T.Text -> Either Menu.ErrorMessage (Maybe [VersionPattern])
overWriteVersionParser :: Text -> Either Text (Maybe [VersionPattern])
overWriteVersionParser = Maybe [VersionPattern]
-> (Text -> Either Text (Maybe [VersionPattern]))
-> Text
-> Either Text (Maybe [VersionPattern])
forall a. a -> (Text -> Either Text a) -> Text -> Either Text a
whenEmpty Maybe [VersionPattern]
forall a. Maybe a
Nothing ((Text -> Either Text (Maybe [VersionPattern]))
-> Text -> Either Text (Maybe [VersionPattern]))
-> (Text -> Either Text (Maybe [VersionPattern]))
-> Text
-> Either Text (Maybe [VersionPattern])
forall a b. (a -> b) -> a -> b
$ (String -> Text)
-> ([VersionPattern] -> Maybe [VersionPattern])
-> Either String [VersionPattern]
-> Either Text (Maybe [VersionPattern])
forall a b c d. (a -> b) -> (c -> d) -> Either a c -> Either b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap String -> Text
T.pack [VersionPattern] -> Maybe [VersionPattern]
forall a. a -> Maybe a
Just (Either String [VersionPattern]
-> Either Text (Maybe [VersionPattern]))
-> (Text -> Either String [VersionPattern])
-> Text
-> Either Text (Maybe [VersionPattern])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Either String [VersionPattern]
Utils.overWriteVersionParser (String -> Either String [VersionPattern])
-> (Text -> String) -> Text -> Either String [VersionPattern]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
jobsV :: T.Text -> Either Menu.ErrorMessage (Maybe Int)
jobsV :: Text -> Either Text (Maybe Int)
jobsV =
let parseInt :: Text -> Either Text (Maybe Int)
parseInt = (String -> Text)
-> (Int -> Maybe Int)
-> Either String Int
-> Either Text (Maybe Int)
forall a b c d. (a -> b) -> (c -> d) -> Either a c -> Either b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (Text -> String -> Text
forall a b. a -> b -> a
const Text
"Invalid value. Must be an integer") Int -> Maybe Int
forall a. a -> Maybe a
Just (Either String Int -> Either Text (Maybe Int))
-> (Text -> Either String Int) -> Text -> Either Text (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Read a => String -> Either String a
readEither @Int (String -> Either String Int)
-> (Text -> String) -> Text -> Either String Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
in Maybe Int
-> (Text -> Either Text (Maybe Int))
-> Text
-> Either Text (Maybe Int)
forall a. a -> (Text -> Either Text a) -> Text -> Either Text a
whenEmpty Maybe Int
forall a. Maybe a
Nothing Text -> Either Text (Maybe Int)
parseInt
patchesV :: T.Text -> Either Menu.ErrorMessage (Maybe (Either FilePath [URI]))
patchesV :: Text -> Either Text (Maybe (Either String [URI]))
patchesV = Maybe (Either String [URI])
-> (Text -> Either Text (Maybe (Either String [URI])))
-> Text
-> Either Text (Maybe (Either String [URI]))
forall a. a -> (Text -> Either Text a) -> Text -> Either Text a
whenEmpty Maybe (Either String [URI])
forall a. Maybe a
Nothing Text -> Either Text (Maybe (Either String [URI]))
readPatches
where
readPatches :: Text -> Either Text (Maybe (Either String [URI]))
readPatches Text
j =
let
x :: Either String (Maybe (Either String b))
x = (String -> Maybe (Either String b))
-> Either String String -> Either String (Maybe (Either String b))
forall b c a. (b -> c) -> Either a b -> Either a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (Either String b -> Maybe (Either String b)
forall a. a -> Maybe a
Just (Either String b -> Maybe (Either String b))
-> (String -> Either String b) -> String -> Maybe (Either String b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Either String b
forall a b. a -> Either a b
Left) (Either String String -> Either String (Maybe (Either String b)))
-> Either String String -> Either String (Maybe (Either String b))
forall a b. (a -> b) -> a -> b
$ String -> Either String String
Utils.absolutePathParser (Text -> String
T.unpack Text
j)
y :: Either String (Maybe (Either a [URI]))
y = ([URI] -> Maybe (Either a [URI]))
-> Either String [URI] -> Either String (Maybe (Either a [URI]))
forall b c a. (b -> c) -> Either a b -> Either a c
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (Either a [URI] -> Maybe (Either a [URI])
forall a. a -> Maybe a
Just (Either a [URI] -> Maybe (Either a [URI]))
-> ([URI] -> Either a [URI]) -> [URI] -> Maybe (Either a [URI])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [URI] -> Either a [URI]
forall a b. b -> Either a b
Right) (Either String [URI] -> Either String (Maybe (Either a [URI])))
-> Either String [URI] -> Either String (Maybe (Either a [URI]))
forall a b. (a -> b) -> a -> b
$ (Text -> Either String URI) -> [Text] -> Either String [URI]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (String -> Either String URI
Utils.uriParser (String -> Either String URI)
-> (Text -> String) -> Text -> Either String URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack) ((Char -> Bool) -> Text -> [Text]
T.split Char -> Bool
isSpace Text
j)
in (String -> Text)
-> Either String (Maybe (Either String [URI]))
-> Either Text (Maybe (Either String [URI]))
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first String -> Text
T.pack (Either String (Maybe (Either String [URI]))
-> Either Text (Maybe (Either String [URI])))
-> Either String (Maybe (Either String [URI]))
-> Either Text (Maybe (Either String [URI]))
forall a b. (a -> b) -> a -> b
$ Either String (Maybe (Either String [URI]))
forall {b}. Either String (Maybe (Either String b))
x Either String (Maybe (Either String [URI]))
-> Either String (Maybe (Either String [URI]))
-> Either String (Maybe (Either String [URI]))
forall a. Either String a -> Either String a -> Either String a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Either String (Maybe (Either String [URI]))
forall {a}. Either String (Maybe (Either a [URI]))
y
filepathV :: T.Text -> Either Menu.ErrorMessage (Maybe FilePath)
filepathV :: Text -> Either Text (Maybe String)
filepathV = Maybe String
-> (Text -> Either Text (Maybe String))
-> Text
-> Either Text (Maybe String)
forall a. a -> (Text -> Either Text a) -> Text -> Either Text a
whenEmpty Maybe String
forall a. Maybe a
Nothing ((String -> Text)
-> (String -> Maybe String)
-> Either String String
-> Either Text (Maybe String)
forall a b c d. (a -> b) -> (c -> d) -> Either a c -> Either b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap String -> Text
T.pack String -> Maybe String
forall a. a -> Maybe a
Just (Either String String -> Either Text (Maybe String))
-> (Text -> Either String String)
-> Text
-> Either Text (Maybe String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Either String String
Utils.isolateParser (String -> Either String String)
-> (Text -> String) -> Text -> Either String String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack)
additionalValidator :: T.Text -> Either Menu.ErrorMessage [T.Text]
additionalValidator :: Text -> Either Text [Text]
additionalValidator = [Text] -> Either Text [Text]
forall a b. b -> Either a b
Right ([Text] -> Either Text [Text])
-> (Text -> [Text]) -> Text -> Either Text [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> [Text]
T.split Char -> Bool
isSpace
targetGHCsField :: MenuField CompileHLSOptions Name
targetGHCsField =
let label :: Text
label = Text
"target GHC(s)"
in case [ToolVersion] -> Maybe (NonEmpty ToolVersion)
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty ((Version -> ToolVersion) -> [Version] -> [ToolVersion]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Version -> ToolVersion
ToolVersion [Version]
availableGHCs) of
Just NonEmpty ToolVersion
ne -> Name
-> Lens' CompileHLSOptions [ToolVersion]
-> NonEmpty ToolVersion
-> (ToolVersion -> Text)
-> MenuKeyBindings
-> MenuField CompileHLSOptions Name
forall n s i.
(Ord n, Show n) =>
n
-> Lens' s [i]
-> NonEmpty i
-> (i -> Text)
-> MenuKeyBindings
-> SelectField s n
Menu.createMultiSelectField (ResourceId -> Name
Common.MenuElement ResourceId
Common.TargetGhcEditBox) Lens' CompileHLSOptions [ToolVersion]
targetGHCs NonEmpty ToolVersion
ne (String -> Text
T.pack (String -> Text) -> (ToolVersion -> String) -> ToolVersion -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ToolVersion -> String
forall a. Pretty a => a -> String
prettyShow) MenuKeyBindings
k
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
label
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"GHC versions to compile for (Press Enter to edit)"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) ErrorStatus
forall s n. Lens' (MenuField s n) ErrorStatus
Menu.fieldStatusL Lens' (MenuField CompileHLSOptions Name) ErrorStatus
-> ErrorStatus
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text -> ErrorStatus
Menu.Invalid Text
"No version selected"
Maybe (NonEmpty ToolVersion)
_ -> Name
-> (Text -> Either Text [ToolVersion])
-> Lens' CompileHLSOptions [ToolVersion]
-> MenuField CompileHLSOptions Name
forall n a s.
(Eq n, Ord n, Show n) =>
n -> (Text -> Either Text a) -> Lens' s a -> EditableField s n
Menu.createEditableField (ResourceId -> Name
Common.MenuElement ResourceId
Common.TargetGhcEditBox) Text -> Either Text [ToolVersion]
ghcVersionTagEither Lens' CompileHLSOptions [ToolVersion]
targetGHCs
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
label
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"space separated list of GHC versions to compile for"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) ErrorStatus
forall s n. Lens' (MenuField s n) ErrorStatus
Menu.fieldStatusL Lens' (MenuField CompileHLSOptions Name) ErrorStatus
-> ErrorStatus
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text -> ErrorStatus
Menu.Invalid Text
"Invalid empty value"
fields :: [MenuField CompileHLSOptions Name]
fields =
[ MenuField CompileHLSOptions Name
targetGHCsField
, Name
-> Lens' CompileHLSOptions Bool -> MenuField CompileHLSOptions Name
forall n s. n -> Lens' s Bool -> CheckBoxField s n
Menu.createCheckBoxField (ResourceId -> Name
Common.MenuElement ResourceId
Common.UpdateCabalCheckBox) Lens' CompileHLSOptions Bool
updateCabal
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"cabal update"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"Run 'cabal update' before the build"
, Name
-> (Text -> Either Text (Maybe Int))
-> Lens' CompileHLSOptions (Maybe Int)
-> MenuField CompileHLSOptions Name
forall n a s.
(Eq n, Ord n, Show n) =>
n -> (Text -> Either Text a) -> Lens' s a -> EditableField s n
Menu.createEditableField (ResourceId -> Name
Common.MenuElement ResourceId
Common.JobsEditBox) Text -> Either Text (Maybe Int)
jobsV Lens' CompileHLSOptions (Maybe Int)
jobs
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"jobs"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"How many jobs to use for make"
, Name
-> Lens' CompileHLSOptions Bool -> MenuField CompileHLSOptions Name
forall n s. n -> Lens' s Bool -> CheckBoxField s n
Menu.createCheckBoxField (ResourceId -> Name
Common.MenuElement ResourceId
Common.SetCheckBox) Lens' CompileHLSOptions Bool
setCompile
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"set"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"Set as active version after install"
, Name
-> (Text -> Either Text [Text])
-> Lens' CompileHLSOptions [Text]
-> MenuField CompileHLSOptions Name
forall n a s.
(Eq n, Ord n, Show n) =>
n -> (Text -> Either Text a) -> Lens' s a -> EditableField s n
Menu.createEditableField (ResourceId -> Name
Common.MenuElement ResourceId
Common.AdditionalEditBox) Text -> Either Text [Text]
additionalValidator Lens' CompileHLSOptions [Text]
cabalArgs
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"CABAL_ARGS"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"Additional arguments to cabal install"
, Name
-> (Text -> Either Text (Maybe String))
-> Lens' CompileHLSOptions (Maybe String)
-> MenuField CompileHLSOptions Name
forall n a s.
(Eq n, Ord n, Show n) =>
n -> (Text -> Either Text a) -> Lens' s a -> EditableField s n
Menu.createEditableField (ResourceId -> Name
Common.MenuElement ResourceId
Common.IsolateEditBox) Text -> Either Text (Maybe String)
filepathV Lens' CompileHLSOptions (Maybe String)
isolateDir
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"isolated"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"install in an isolated absolute directory instead of the default one"
, Name
-> (Text -> Either Text (Maybe [VersionPattern]))
-> Lens' CompileHLSOptions (Maybe [VersionPattern])
-> MenuField CompileHLSOptions Name
forall n a s.
(Eq n, Ord n, Show n) =>
n -> (Text -> Either Text a) -> Lens' s a -> EditableField s n
Menu.createEditableField (ResourceId -> Name
Common.MenuElement ResourceId
Common.OvewrwiteVerEditBox) Text -> Either Text (Maybe [VersionPattern])
overWriteVersionParser Lens' CompileHLSOptions (Maybe [VersionPattern])
overwriteVer
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"overwrite version"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"Allows to overwrite the finally installed VERSION with a different one. Allows to specify patterns: %v (version), %b (branch name), %h (short commit hash), %H (long commit hash), %g ('git describe' output)"
, Name
-> (Text -> Either Text (Maybe (Either String [URI])))
-> Lens' CompileHLSOptions (Maybe (Either String [URI]))
-> MenuField CompileHLSOptions Name
forall n a s.
(Eq n, Ord n, Show n) =>
n -> (Text -> Either Text a) -> Lens' s a -> EditableField s n
Menu.createEditableField (ResourceId -> Name
Common.MenuElement ResourceId
Common.PatchesEditBox) Text -> Either Text (Maybe (Either String [URI]))
patchesV Lens' CompileHLSOptions (Maybe (Either String [URI]))
patches
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"patches"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"Either a URI to a patch (https/http/file) or Absolute path to patch directory"
, Name
-> (Text -> Either Text (Maybe (Either String URI)))
-> Lens' CompileHLSOptions (Maybe (Either String URI))
-> MenuField CompileHLSOptions Name
forall n a s.
(Eq n, Ord n, Show n) =>
n -> (Text -> Either Text a) -> Lens' s a -> EditableField s n
Menu.createEditableField (ResourceId -> Name
Common.MenuElement ResourceId
Common.CabalProjectEditBox) Text -> Either Text (Maybe (Either String URI))
cabalProjectV Lens' CompileHLSOptions (Maybe (Either String URI))
cabalProject
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"cabal project"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"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."
, Name
-> (Text -> Either Text (Maybe URI))
-> Lens' CompileHLSOptions (Maybe URI)
-> MenuField CompileHLSOptions Name
forall n a s.
(Eq n, Ord n, Show n) =>
n -> (Text -> Either Text a) -> Lens' s a -> EditableField s n
Menu.createEditableField (ResourceId -> Name
Common.MenuElement ResourceId
Common.CabalProjectLocalEditBox) Text -> Either Text (Maybe URI)
cabalProjectLocalV Lens' CompileHLSOptions (Maybe URI)
cabalProjectLocal
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"cabal project local"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"URI (https/http/file) to a cabal.project.local to be used for the build. Will be copied over."
, Name
-> (Text -> Either Text (Maybe String))
-> Lens' CompileHLSOptions (Maybe String)
-> MenuField CompileHLSOptions Name
forall n a s.
(Eq n, Ord n, Show n) =>
n -> (Text -> Either Text a) -> Lens' s a -> EditableField s n
Menu.createEditableField (ResourceId -> Name
Common.MenuElement ResourceId
Common.GitRefEditBox) (Maybe String -> Either Text (Maybe String)
forall a b. b -> Either a b
Right (Maybe String -> Either Text (Maybe String))
-> (Text -> Maybe String) -> Text -> Either Text (Maybe String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String)
-> (Text -> String) -> Text -> Maybe String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack) Lens' CompileHLSOptions (Maybe String)
gitRef
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"git-ref"
MenuField CompileHLSOptions Name
-> (MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name)
-> MenuField CompileHLSOptions Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField CompileHLSOptions Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField CompileHLSOptions Name) Text
-> Text
-> MenuField CompileHLSOptions Name
-> MenuField CompileHLSOptions Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"The git commit/branch/ref to build from"
]
buttons :: [MenuField s Name]
buttons = [
Name -> MenuField s Name
forall n s. n -> Button s n
Menu.createButtonField (ResourceId -> Name
Common.MenuElement ResourceId
Common.OkButton)
MenuField s Name
-> (MenuField s Name -> MenuField s Name) -> MenuField s Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField s Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldLabelL Lens' (MenuField s Name) Text
-> Text -> MenuField s Name -> MenuField s Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"Compile"
MenuField s Name
-> (MenuField s Name -> MenuField s Name) -> MenuField s Name
forall a b. a -> (a -> b) -> b
& Lens' (MenuField s Name) Text
forall s n. Lens' (MenuField s n) Text
Menu.fieldHelpMsgL Lens' (MenuField s Name) Text
-> Text -> MenuField s Name -> MenuField s Name
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Text
"Compile HLS from source with options below\nRequired fields: target GHC(s)"
]
handler :: BrickEvent Name e -> EventM Name CompileHLSMenu ()
handler :: forall e. BrickEvent Name e -> EventM Name CompileHLSMenu ()
handler = BrickEvent Name e -> EventM Name CompileHLSMenu ()
forall n e s. Eq n => BrickEvent n e -> EventM n (Menu s n) ()
Menu.handlerMenu
draw :: CompileHLSMenu -> [Widget Name]
draw :: CompileHLSMenu -> [Widget Name]
draw = CompileHLSMenu -> [Widget Name]
forall n s.
(Eq n, Ord n, Show n, Named (MenuField s n) n) =>
Menu s n -> [Widget n]
Menu.drawMenu