module BNFC.Options.Commands where
import BNFC.Prelude
import BNFC.Backend.Agda.Options ( AgdaBackendOptions, agdaOptionsParser )
import BNFC.Backend.C ( CBackendOptions, cOptionsParser )
import BNFC.Backend.CPP ( CppBackendOptions, cppOptionsParser )
import BNFC.Backend.Haskell.Options ( HaskellBackendOptions, haskellOptionsParser )
import BNFC.Backend.Txt2Tags.Options ( Txt2TagsBackendOptions, txt2tagsOptionsParser )
import BNFC.Backend.Java ( JavaBackendOptions, javaOptionsParser )
import BNFC.Backend.Latex ( LatexBackendOptions, latexOptionsParser )
import BNFC.Backend.OCaml ( OcamlBackendOptions, ocamlOptionsParser )
import Options.Applicative
commandsParser :: Parser Command
commandsParser :: Parser Command
commandsParser = Mod CommandFields Command -> Parser Command
forall a. Mod CommandFields a -> Parser a
hsubparser
( String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"c" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (CBackendOptions -> Command
C (CBackendOptions -> Command)
-> Parser CBackendOptions -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser CBackendOptions
cOptionsParser) (String -> InfoMod Command
forall a. String -> InfoMod a
progDesc String
"Output C code"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"cpp" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (CppBackendOptions -> Command
Cpp (CppBackendOptions -> Command)
-> Parser CppBackendOptions -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser CppBackendOptions
cppOptionsParser) (String -> InfoMod Command
forall a. String -> InfoMod a
progDesc String
"Output C++ code"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"haskell" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (HaskellBackendOptions -> Command
Haskell (HaskellBackendOptions -> Command)
-> Parser HaskellBackendOptions -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser HaskellBackendOptions
haskellOptionsParser)
(String -> InfoMod Command
forall a. String -> InfoMod a
progDesc String
"Output Haskell code for use with Alex and Happy"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"agda" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (AgdaBackendOptions -> Command
Agda (AgdaBackendOptions -> Command)
-> Parser AgdaBackendOptions -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser AgdaBackendOptions
agdaOptionsParser)
(String -> InfoMod Command
forall a. String -> InfoMod a
progDesc String
"Output Haskell code for use with Alex and Happy together with Agda bindings for AST, parser and printer"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"java" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (JavaBackendOptions -> Command
Java (JavaBackendOptions -> Command)
-> Parser JavaBackendOptions -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser JavaBackendOptions
javaOptionsParser) (String -> InfoMod Command
forall a. String -> InfoMod a
progDesc String
"Output Java code"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"latex" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (LatexBackendOptions -> Command
Latex (LatexBackendOptions -> Command)
-> Parser LatexBackendOptions -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser LatexBackendOptions
latexOptionsParser)
(String -> InfoMod Command
forall a. String -> InfoMod a
progDesc String
"Output LaTeX code to generate a PDF description of the language"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"ocaml" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (OcamlBackendOptions -> Command
OCaml (OcamlBackendOptions -> Command)
-> Parser OcamlBackendOptions -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser OcamlBackendOptions
ocamlOptionsParser) (String -> InfoMod Command
forall a. String -> InfoMod a
progDesc String
"Output Ocaml code"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"txt2tags" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Txt2TagsBackendOptions -> Command
Txt2Tags (Txt2TagsBackendOptions -> Command)
-> Parser Txt2TagsBackendOptions -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Txt2TagsBackendOptions
txt2tagsOptionsParser)
(String -> InfoMod Command
forall a. String -> InfoMod a
progDesc String
"Output a text file to feed to txt2tags"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<> String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"check" (Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Command -> Parser Command
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
Check) (String -> InfoMod Command
forall a. String -> InfoMod a
progDesc String
"Just check the input LBNF file. No output."))
)
data Command
= Agda AgdaBackendOptions
| C CBackendOptions
| Cpp CppBackendOptions
| Haskell HaskellBackendOptions
| Java JavaBackendOptions
| Latex LatexBackendOptions
| OCaml OcamlBackendOptions
| Txt2Tags Txt2TagsBackendOptions
| Check