module BNFC.Backend.Agda.Options where import BNFC.Prelude import Options.Applicative data AgdaBackendOptions = AgdaOpts { nameSpace :: Maybe String , inDir :: Bool , functor :: Bool , generic :: Bool } agdaOptionsParser :: Parser AgdaBackendOptions agdaOptionsParser = AgdaOpts <$> oNameSpace <*> oInDir <*> oFunctor <*> oGeneric where -- name-space option oNameSpace = optional $ strOption ( short 'p' <> long "name-space" <> help "Prepend NAMESPACE to the package/module name" <> metavar "NAMESPACE") -- inDir option oInDir = switch ( short 'd' <> help "Put Haskell code in modules LANG.* instead of LANG* (recommended)" ) -- functor option oFunctor = switch ( long "functor" <> help "Make the AST a functor and use it to store the position of the nodes" ) -- generic option oGeneric = switch ( long "generic" <> help "Derive Data, Generic, and Typeable instances for AST types" ) printAgdaOptions :: AgdaBackendOptions -> String printAgdaOptions opts = unwords $ filter (not . null) [ nSpace, dir, funct, gen ] where nSpace = case nameSpace opts of Just n -> "-p " ++ n Nothing -> "" dir = if inDir opts then "-d" else "" funct = if functor opts then "--functor" else "" gen = if generic opts then "--generic" else ""