module BNFC.Options.GlobalOptions where
import BNFC.Prelude
import Options.Applicative
data GlobalOptions = GlobalOptions
{ GlobalOptions -> Bool
optVerbose :: Bool
, GlobalOptions -> Bool
optDryRun :: Bool
, GlobalOptions -> Bool
optForce :: Bool
, GlobalOptions -> Maybe FilePath
optOutDir :: Maybe FilePath
, GlobalOptions -> Bool
optMakeFile :: Bool
, GlobalOptions -> FilePath
optInput :: FilePath
} deriving Int -> GlobalOptions -> ShowS
[GlobalOptions] -> ShowS
GlobalOptions -> FilePath
(Int -> GlobalOptions -> ShowS)
-> (GlobalOptions -> FilePath)
-> ([GlobalOptions] -> ShowS)
-> Show GlobalOptions
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [GlobalOptions] -> ShowS
$cshowList :: [GlobalOptions] -> ShowS
show :: GlobalOptions -> FilePath
$cshow :: GlobalOptions -> FilePath
showsPrec :: Int -> GlobalOptions -> ShowS
$cshowsPrec :: Int -> GlobalOptions -> ShowS
Show
globalOptionsParser :: Parser GlobalOptions
globalOptionsParser :: Parser GlobalOptions
globalOptionsParser = Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Bool
-> FilePath
-> GlobalOptions
GlobalOptions
(Bool
-> Bool
-> Bool
-> Maybe FilePath
-> Bool
-> FilePath
-> GlobalOptions)
-> Parser Bool
-> Parser
(Bool
-> Bool -> Maybe FilePath -> Bool -> FilePath -> GlobalOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
oVerbose
Parser
(Bool
-> Bool -> Maybe FilePath -> Bool -> FilePath -> GlobalOptions)
-> Parser Bool
-> Parser
(Bool -> Maybe FilePath -> Bool -> FilePath -> GlobalOptions)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
oDryRun
Parser
(Bool -> Maybe FilePath -> Bool -> FilePath -> GlobalOptions)
-> Parser Bool
-> Parser (Maybe FilePath -> Bool -> FilePath -> GlobalOptions)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
oForce
Parser (Maybe FilePath -> Bool -> FilePath -> GlobalOptions)
-> Parser (Maybe FilePath)
-> Parser (Bool -> FilePath -> GlobalOptions)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe FilePath)
oOutDir
Parser (Bool -> FilePath -> GlobalOptions)
-> Parser Bool -> Parser (FilePath -> GlobalOptions)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
oMakeFile
Parser (FilePath -> GlobalOptions)
-> Parser FilePath -> Parser GlobalOptions
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FilePath
oInput
where
oForce :: Parser Bool
oForce =
Mod FlagFields Bool -> Parser Bool
switch
(Mod FlagFields Bool -> Parser Bool)
-> Mod FlagFields Bool -> Parser Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"force"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'f'
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Continue in spite of errors."
oDryRun :: Parser Bool
oDryRun =
Mod FlagFields Bool -> Parser Bool
switch
(Mod FlagFields Bool -> Parser Bool)
-> Mod FlagFields Bool -> Parser Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"dry-run"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Do not write any output files, just explain what would happen."
oVerbose :: Parser Bool
oVerbose =
Mod FlagFields Bool -> Parser Bool
switch
(Mod FlagFields Bool -> Parser Bool)
-> Mod FlagFields Bool -> Parser Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"verbose"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'v'
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Comment on what is happening."
oOutDir :: Parser (Maybe FilePath)
oOutDir =
Parser FilePath -> Parser (Maybe FilePath)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser FilePath -> Parser (Maybe FilePath))
-> Parser FilePath -> Parser (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
(Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"outdir"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'o'
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"OUTDIR"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasCompleter f => FilePath -> Mod f a
action FilePath
"directory"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Name of output directory."
oMakeFile :: Parser Bool
oMakeFile =
Mod FlagFields Bool -> Parser Bool
switch
(Mod FlagFields Bool -> Parser Bool)
-> Mod FlagFields Bool -> Parser Bool
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"makefile"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'm'
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Generate Makefile"
oInput :: Parser FilePath
oInput :: Parser FilePath
oInput =
Mod ArgumentFields FilePath -> Parser FilePath
forall s. IsString s => Mod ArgumentFields s -> Parser s
strArgument
(Mod ArgumentFields FilePath -> Parser FilePath)
-> Mod ArgumentFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"GRAMMARFILE"
Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasCompleter f => FilePath -> Mod f a
action FilePath
"file"
Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"The LBNF grammar file."