{-# LANGUAGE DeriveDataTypeable #-} module System.Console.Internal where import Control.Exception (Exception) import Data.Map (Map) import Data.Typeable (Typeable) import qualified System.Console.GetOpt as GetOpt type UserCommand = [String] -- | An @Action m@ is an action (in the monad @m@), which may take arguments -- (\"non-options\") and options from the command line. data Action m = Action { run :: [String] -> Settings -> m () , nonOptions :: [String] , options :: [GetOpt.OptDescr Setting] , ignoringOptions :: [GetOpt.OptDescr Setting] } data Identifier = Short Char | Long String deriving (Eq,Ord) type Setting = (Identifier,Maybe String) type Settings = Map Identifier (Maybe String) -- | A value of type @Option a@ describes an option, that delivers a value -- to the program of type @a@. data Option a = Option Identifier (GetOpt.OptDescr Setting) a (Maybe String -> Either String a) -- | A @Command m@ is an action (in the monad @m@), together with some -- descriptive information. data Command m = Command { -- | This determines which command is executed. name :: String -- | For usage info. , description :: String -- | The actual action performed by this command. , action :: Action m -- | Prefer shortened subcommands over non-option arguments. , shorten :: Bool } data ConsoleProgramException = UnknownCommand String deriving (Typeable) instance Show ConsoleProgramException where show (UnknownCommand c) = "Error: unused non-option or unrecognised command: " ++ c instance Exception ConsoleProgramException