{-# LANGUAGE GADTs #-} {- | Module : $Header$ Description: Command line parser options. Copyright : (c) Alexander Berntsen 2015 License : GPL-3 Maintainer : alexander@plaimi.net -} module Clac.CliParser where import Control.Applicative ( (<$>), (<*>), ) import Data.Monoid ( (<>), mempty, ) import Options.Applicative ( Parser, help, long, many, short, strArgument, switch, ) -- | The command line options for clac. 'h' is whether the user wants help. -- 'r' is whether the user wants to print the repl help. 'v' is whether the -- user wants verbose mode. Everything else is attempted parsed as an -- equation. data Opt where MkOpt :: {h :: Bool ,r :: Bool ,v :: Bool ,e :: [String] } -> Opt ops :: Parser Opt -- | The parser for the line options for clac. ops = MkOpt <$> switch ( long "operations" <> short 'o' <> help "Print all operations" ) <*> switch ( long "repl operations" <> short 'r' <> help "Print repl operations" ) <*> switch ( long "verbose" <> short 'v' <> help "Verbose output" ) <*> many (strArgument mempty)