{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
module Stack.Options.SetupParser
( setupOptsParser
) where
import qualified Data.Text as T
import qualified Options.Applicative as OA
import qualified Options.Applicative.Builder.Extra as OA
import qualified Options.Applicative.Types as OA
import Stack.Prelude
import Stack.SetupCmd ( SetupCmdOpts (..) )
setupOptsParser :: OA.Parser SetupCmdOpts
setupOptsParser :: Parser SetupCmdOpts
setupOptsParser = Maybe WantedCompiler
-> Bool -> Maybe String -> [String] -> Bool -> SetupCmdOpts
SetupCmdOpts
(Maybe WantedCompiler
-> Bool -> Maybe String -> [String] -> Bool -> SetupCmdOpts)
-> Parser (Maybe WantedCompiler)
-> Parser
(Bool -> Maybe String -> [String] -> Bool -> SetupCmdOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser WantedCompiler -> Parser (Maybe WantedCompiler)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
OA.optional (ReadM WantedCompiler
-> Mod ArgumentFields WantedCompiler -> Parser WantedCompiler
forall a. ReadM a -> Mod ArgumentFields a -> Parser a
OA.argument ReadM WantedCompiler
readVersion
( String -> Mod ArgumentFields WantedCompiler
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"GHC_VERSION"
Mod ArgumentFields WantedCompiler
-> Mod ArgumentFields WantedCompiler
-> Mod ArgumentFields WantedCompiler
forall a. Semigroup a => a -> a -> a
<> String -> Mod ArgumentFields WantedCompiler
forall (f :: * -> *) a. String -> Mod f a
OA.help String
"Version of GHC to install, e.g. 9.6.2. (default: install \
\the version implied by the resolver)"
))
Parser (Bool -> Maybe String -> [String] -> Bool -> SetupCmdOpts)
-> Parser Bool
-> Parser (Maybe String -> [String] -> Bool -> SetupCmdOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> String -> String -> Mod FlagFields Bool -> Parser Bool
OA.boolFlags Bool
False
String
"reinstall"
String
"reinstalling GHC, even if available (incompatible with --system-ghc)."
Mod FlagFields Bool
forall m. Monoid m => m
OA.idm
Parser (Maybe String -> [String] -> Bool -> SetupCmdOpts)
-> Parser (Maybe String)
-> Parser ([String] -> Bool -> SetupCmdOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
OA.optional (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OA.strOption
( String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"ghc-bindist"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"URL"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OA.help String
"Alternate GHC binary distribution (requires custom \
\--ghc-variant)."
))
Parser ([String] -> Bool -> SetupCmdOpts)
-> Parser [String] -> Parser (Bool -> SetupCmdOpts)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser [String]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
OA.many (Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OA.strOption
( String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OA.long String
"ghcjs-boot-options"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OA.metavar String
"GHCJS_BOOT"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OA.help String
"Additional ghcjs-boot options."
))
Parser (Bool -> SetupCmdOpts) -> Parser Bool -> Parser SetupCmdOpts
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> String -> String -> Mod FlagFields Bool -> Parser Bool
OA.boolFlags Bool
True
String
"ghcjs-boot-clean"
String
"Control if ghcjs-boot should have --clean option present."
Mod FlagFields Bool
forall m. Monoid m => m
OA.idm
where
readVersion :: ReadM WantedCompiler
readVersion = do
String
s <- ReadM String
OA.readerAsk
case Text -> Either PantryException WantedCompiler
parseWantedCompiler (Text
"ghc-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
s) of
Left PantryException
_ ->
case Text -> Either PantryException WantedCompiler
parseWantedCompiler (String -> Text
T.pack String
s) of
Left PantryException
_ -> String -> ReadM WantedCompiler
forall a. String -> ReadM a
OA.readerError (String -> ReadM WantedCompiler) -> String -> ReadM WantedCompiler
forall a b. (a -> b) -> a -> b
$ String
"Invalid version: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
Right WantedCompiler
x -> WantedCompiler -> ReadM WantedCompiler
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure WantedCompiler
x
Right WantedCompiler
x -> WantedCompiler -> ReadM WantedCompiler
forall a. a -> ReadM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure WantedCompiler
x