-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Command line argument processing -- -- This library provides an easy way to define command line parsers. Most -- users will want to use the System.Console.CmdArgs.Implicit -- module, whose documentation contains an example. -- --
-- [Line "Cooking for hungry people." -- ,Line "Welcome to my cookery recipe program, I sure hope you enjoy using it!" -- ,Line "" -- ,Cols ["Omlette"," A tasty eggy treat."] -- ,Cols [" -m"," --mushrooms"," Some mushrooms, or in fact any other ingredients you have in the cupboards"] -- ,Cols [" -e"," --eggs", " But always you need eggs"] -- ,Line "" -- ,Cols ["Spagetti Bolognaise", " An Italian delight."] -- ,Cols [" -s"," --spagetti"," The first word in the name"] -- ,Cols [" -b"," --bolognaise"," The second word in the name"] -- ,Cols [" -d"," --dolmio"," The magic ingredient!"] -- ,Line "" -- ,Line " The author of this program explicitly disclaims any liability for poisoning people who get their recipes off the internet."] ---- -- With putStrLn (showText (Wrap 50) demo) gives: -- --
-- Cooking for hungry people. -- Welcome to my cookery recipe program, I sure hope -- you enjoy using it! -- -- Omlette A tasty eggy treat. -- -m --mushrooms Some mushrooms, or in fact -- any other ingredients you have -- in the cupboards -- -e --eggs But always you need eggs -- -- Spagetti Bolognaise An Italian delight. -- -s --spagetti The first word in the name -- -b --bolognaise The second word in the name -- -d --dolmio The magic ingredient! -- -- The author of this program explicitly -- disclaims any liability for poisoning people -- who get their recipes off the internet. --module System.Console.CmdArgs.Text -- | How to output the text. data TextFormat -- | Display as HTML. HTML :: TextFormat -- | Display as text wrapped at a certain width (see defaultWrap). Wrap :: Int -> TextFormat -- | Wrap with the default width of 80 characters. defaultWrap :: TextFormat -- | The data type representing some text, typically used as -- [Text]. The formatting is described by: -- --
-- arguments :: Mode [(String,String)] -- arguments = mode "explicit" [] "Explicit sample program" (flagArg (upd "file") "FILE") -- [flagOpt "world" ["hello","h"] (upd "world") "WHO" "World argument" -- ,flagReq ["greeting","g"] (upd "greeting") "MSG" "Greeting to give" -- ,flagHelpSimple (("help",""):)] -- where upd msg x v = Right $ (msg,x):v ---- -- And this can be invoked by: -- --
-- main = do -- x <- processArgs arguments -- if ("help","") `elem` xs then -- print $ helpText def arguments -- else -- print x ---- -- Groups: The Group structure allows flags/modes to be -- grouped for the purpose of displaying help. When processing command -- lines, the group structure is ignored. -- -- Modes: The Explicit module allows multiple mode programs by -- placing additional modes in modeGroupModes. Every mode is -- allowed sub-modes, and thus multiple levels of mode may be created. -- Given a mode x with sub-modes xs, if the first -- argument corresponds to the name of a sub-mode, then that sub-mode -- will be applied. If not, then the arguments will be processed by mode -- x. Consequently, if you wish to force the user to explicitly -- enter a mode, simply give sub-modes, and leave modeArgs as -- Nothing. Alternatively, if you want one sub-mode to be -- selected by default, place all it's flags both in the sub-mode and the -- outer mode. module System.Console.CmdArgs.Explicit -- | Process a list of flags (usually obtained from getArgs) with -- a mode. Returns Left and an error message if the command line -- fails to parse, or Right and the associated value. process :: Mode a -> [String] -> Either String a -- | Process a list of flags (usually obtained from getArgs) with -- a mode. Displays an error and exits with failure if the command line -- fails to parse, or returns the associated value. Implemeneted in terms -- of process. processValue :: Mode a -> [String] -> a -- | Process the flags obtained by getArgs with a mode. Displays -- an error and exits with failure if the command line fails to parse, or -- returns the associated value. Implemented in terms of process. processArgs :: Mode a -> IO a -- | A name, either the name of a flag (--foo) or the name -- of a mode. type Name = String -- | A help message that goes with either a flag or a mode. type Help = String -- | The type of a flag, i.e. --foo=TYPE. type FlagHelp = String -- | Parse a boolean, accepts as True: true yes on enabled 1. parseBool :: String -> Maybe Bool -- | A group of items (modes or flags). The items are treated as a list, -- but the group structure is used when displaying the help message. data Group a Group :: [a] -> [a] -> [(Help, [a])] -> Group a -- | Normal items. groupUnnamed :: Group a -> [a] -- | Items that are hidden (not displayed in the help message). groupHidden :: Group a -> [a] -- | Items that have been grouped, along with a description of each group. groupNamed :: Group a -> [(Help, [a])] -- | Convert a group into a list. fromGroup :: Group a -> [a] -- | Convert a list into a group, placing all fields in -- groupUnnamed. toGroup :: [a] -> Group a -- | A mode. Each mode has three main features: -- --
-- FlagReq FlagOpt FlagOptRare/FlagNone -- -xfoo -x=foo -x=foo -x= -foo -- -x foo -x=foo -x foo -x= foo -- -x=foo -x=foo -x=foo -x=foo -- --xx foo --xx=foo --xx foo --xx foo -- --xx=foo --xx=foo --xx=foo --xx=foo --data FlagInfo -- | Required argument FlagReq :: FlagInfo -- | Optional argument FlagOpt :: String -> FlagInfo -- | Optional argument that requires an = before the value FlagOptRare :: String -> FlagInfo -- | No argument FlagNone :: FlagInfo -- | Extract the value from inside a FlagOpt or FlagOptRare, -- or raises an error. fromFlagOpt :: FlagInfo -> String -- | A function to take a string, and a value, and either produce an error -- message (Left), or a modified value (Right). type Update a = String -> a -> Either String a -- | A flag, consisting of a list of flag names and other information. data Flag a Flag :: [Name] -> FlagInfo -> Update a -> FlagHelp -> Help -> Flag a -- | The names for the flag. flagNames :: Flag a -> [Name] -- | Information about a flag's arguments. flagInfo :: Flag a -> FlagInfo -- | The way of processing a flag. flagValue :: Flag a -> Update a -- | The type of data for the flag argument, i.e. FILE/DIR/EXT flagType :: Flag a -> FlagHelp -- | The help message associated with this flag. flagHelp :: Flag a -> Help -- | An unnamed argument. Anything not starting with - is -- considered an argument, apart from "-" which is considered to -- be the argument "-", and any arguments following -- "--". For example: -- --
-- programname arg1 -j - --foo arg3 -- -arg4 --arg5=1 arg6 ---- -- Would have the arguments: -- --
-- ["arg1","-","arg3","-arg4","--arg5=1","arg6"] --data Arg a Arg :: Update a -> FlagHelp -> Arg a -- | A way of processing the argument. argValue :: Arg a -> Update a -- | The type of data for the argument, i.e. FILE/DIR/EXT argType :: Arg a -> FlagHelp -- | Check that a mode is well formed. checkMode :: Mode a -> Maybe String class Remap m remap :: Remap m => (a -> b) -> (b -> (a, a -> b)) -> m a -> m b remap2 :: Remap m => (a -> b) -> (b -> a) -> m a -> m b -- | Create a mode with a name, an initial value, some help text, a way of -- processing arguments and a list of flags. mode :: Name -> a -> Help -> Arg a -> [Flag a] -> Mode a -- | Create a list of modes, with a program name, an initial value, some -- help text and the child modes. modes :: String -> a -> Help -> [Mode a] -> Mode a -- | Create a flag taking no argument value, with a list of flag names, an -- update function and some help text. flagNone :: [Name] -> (a -> a) -> Help -> Flag a -- | Create a flag taking an optional argument value, with an optional -- value, a list of flag names, an update function, the type of the -- argument and some help text. flagOpt :: String -> [Name] -> Update a -> FlagHelp -> Help -> Flag a -- | Create a flag taking a required argument value, with a list of flag -- names, an update function, the type of the argument and some help -- text. flagReq :: [Name] -> Update a -> FlagHelp -> Help -> Flag a -- | Create an argument flag, with an update function and the type of the -- argument. flagArg :: Update a -> FlagHelp -> Arg a -- | Create a boolean flag, with a list of flag names, an update function -- and some help text. flagBool :: [Name] -> (Bool -> a -> a) -> Help -> Flag a -- | Create a help flag triggered by -?/--help. flagHelpSimple :: (a -> a) -> Flag a -- | Create a help flag triggered by -?/--help. The user -- may optionally modify help by specifying the format, such as: -- --
-- --help=all - help for all modes -- --help=html - help in HTML format -- --help=100 - wrap the text at 100 characters -- --help=100,one - full text wrapped at 100 characters --flagHelpFormat :: (HelpFormat -> TextFormat -> a -> a) -> Flag a -- | Create a version flag triggered by -V/--version. flagVersion :: (a -> a) -> Flag a -- | Create verbosity flags triggered by -v/--verbose and -- -q/--quiet flagsVerbosity :: (Verbosity -> a -> a) -> [Flag a] -- | Specify the format to output the help. data HelpFormat -- | Equivalent to HelpFormatAll if there is not too much text, -- otherwise HelpFormatOne. HelpFormatDefault :: HelpFormat -- | Display only the first mode. HelpFormatOne :: HelpFormat -- | Display all modes. HelpFormatAll :: HelpFormat -- | Generate a help message from a mode. helpText :: HelpFormat -> Mode a -> [Text] -- | This provides a compatiblity wrapper to the -- System.Console.GetOpt module in base. That module is -- essentially a Haskell port of the GNU getopt library. -- -- Changes: The changes from GetOpt are listed in the -- documentation for each function. module System.Console.CmdArgs.GetOpt -- | Given a help text and a list of option descriptions, generate a -- Mode. convert :: String -> [OptDescr a] -> Mode ([a], [String]) -- | Process the command-line, and return the list of values that matched -- (and those that didn't). The arguments are: -- --
-- data Foo = Foo {foo :: Int, bar :: Int} ---- --
-- impure = capture $ Foo {foo = 12, bar = many [1 &= "inner", 2]} &= "top" ---- --
-- pure = capture_ $ record Foo{} [foo := 12, bar :=+ [atom 1 += "inner", atom 2]] += "top" ---- -- Both evaluate to: -- --
-- Capture (Ann "top") (Ctor (Foo 12 1) [Value 12, Many [Ann "inner" (Value 1), Value 2]] --module System.Console.CmdArgs.Annotate -- | The result of capturing some annotations. data Capture ann -- | Many values collapsed (many or many_) Many :: [Capture ann] -> Capture ann -- | An annotation attached to a value (&= or +=) Ann :: ann -> (Capture ann) -> Capture ann -- | A value (just a value, or atom) Value :: Any -> Capture ann -- | A missing field (a RecConError exception, or missing from -- record) Missing :: Any -> Capture ann -- | A constructor (a constructor, or record) Ctor :: Any -> [Capture ann] -> Capture ann -- | Any value, with a Data dictionary. data Any Any :: a -> Any -- | Return the value inside a capture. fromCapture :: Capture ann -> Any -- | Remove all Missing values by using any previous instances as default -- values defaultMissing :: Capture ann -> Capture ann -- | Capture a value. Note that if the value is evaluated more than once -- the result may be different, i.e. -- --
-- capture x /= capture x --capture :: (Data val, Data ann) => val -> Capture ann -- | Collapse multiple values in to one. many :: Data val => [val] -> val -- | Add an annotation to a value. -- -- It is recommended that anyone making use of this function redefine it -- with a more restrictive type signature to control the type of the -- annotation (the second argument). Any redefinitions of this function -- should add an INLINE pragma, to reduce the chance of incorrect -- optimisations. (&=) :: (Data val, Data ann) => val -> ann -> val -- | Capture the annotations from an annotated value. capture_ :: Show a => Annotate a -> Capture a -- | Collapse many annotated values in to one. many_ :: [Annotate a] -> Annotate a -- | Add an annotation to a value. (+=) :: Annotate ann -> ann -> Annotate ann -- | Lift a pure value to an annotation. atom :: Data val => val -> Annotate ann -- | Create a constructor/record. The first argument should be the type of -- field, the second should be a list of fields constructed originally -- defined by := or :=+. -- -- This operation is not type safe, and may raise an exception at runtime -- if any field has the wrong type or label. record :: Data a => a -> [Annotate b] -> Annotate b -- | This type represents an annotated value. The type of the underlying -- value is not specified. data Annotate ann -- | Construct a field, fieldname := value. (:=) :: (c -> f) -> f -> Annotate ann -- | Add annotations to a field. (:=+) :: (c -> f) -> [Annotate ann] -> Annotate ann instance Typeable ExceptionInt instance Show ExceptionInt instance Show ann => Show (Capture ann) instance Exception ExceptionInt instance Functor Capture -- | This module provides simple command line argument processing. The main -- function of interest is cmdArgs. A simple example is: -- --
-- data Sample = Sample {hello :: String} deriving (Show, Data, Typeable) ---- -- sample = Sample{hello = def &= help -- "World argument" &= opt "world"} -- &= summary "Sample v1" -- --
-- main = print =<< cmdArgs sample ---- -- Attributes are used to control a number of behaviours: -- --
-- sample = cmdArgsMode $ Sample{hello = ... -- as before ---- --
-- main = print =<< cmdArgsRun sample ---- -- Even using this scheme, sometimes GHC's optimisations may share values -- who have the same annotation. To disable sharing you may need to -- specify {-# OPTIONS_GHC -fno-cse #-} in the module you define -- the flags. module System.Console.CmdArgs.Implicit -- | Take impurely annotated records and run the corresponding command -- line. Shortcut for cmdArgsRun . cmdArgsMode. cmdArgs :: Data a => a -> IO a -- | Take impurely annotated records and turn them in to a Mode -- value, that can make use of the System.Console.CmdArgs.Explicit -- functions (i.e. process). -- -- Annotated records are impure, and will only contain annotations on -- their first use. The result of this function is pure, and can be -- reused. cmdArgsMode :: Data a => a -> Mode (CmdArgs a) -- | Run a Mode structure. This function reads the command line arguments -- and then performs as follows: -- --
-- {hello = def &= opt "foo"} -- -h --hello[=VALUE] (default=foo) --opt :: (Show a, Typeable a) => a -> Ann -- | Flag: "For this flag, users need to give something of type ..." -- -- The the type of a flag's value, usually upper case. Only used for the -- help message. Commonly the type will be FILE (typFile) -- or DIR (typDir). -- --
-- {hello = def &= typ "MESSAGE"} -- -h --hello=MESSAGE --typ :: String -> Ann -- | Flag: "Users must give a file for this flag's value." -- -- Alias for typ FILE. typFile :: Ann -- | Flag: "Users must give a directory for this flag's value." -- -- Alias for typ DIR. typDir :: Ann -- | Flag/Mode: "The help message is ..." -- -- Descriptive text used in the help output. -- --
-- {hello = def &= help "Help message"} -- -h --hello=VALUE Help message --help :: String -> Ann -- | Flag: "Use this flag name for this field." -- -- Add flags which trigger this option. -- --
-- {hello = def &= name "foo"} -- -h --hello --foo=VALUE --name :: String -> Ann -- | Flag: "Put non-flag arguments here." -- --
-- {hello = def &= args} --args :: Ann -- | Flag: "Put the nth non-flag argument here." -- -- This field should be used to store a particular argument position -- (0-based). -- --
-- {hello = def &= argPos 0} --argPos :: Int -> Ann -- | Flag/Mode: "Give these flags/modes a group name in the help output." -- -- This mode will be used for all following modes/flags, until the next -- groupname. -- --
-- {hello = def &= groupname "Welcomes"} -- Welcomes -- -h --hello=VALUE --groupname :: String -> Ann -- | Mode: "A longer description of this mode is ..." -- -- Suffix to be added to the help message. -- --
-- Sample{..} &= details ["More details on the website www.example.org"] --details :: [String] -> Ann -- | Modes: "My program name/version/copyright is ..." -- -- One line summary of the entire program, the first line of -- --help and the only line of --version. -- --
-- Sample{..} &= summary "CmdArgs v0.0, (C) Neil Mitchell 1981" --summary :: String -> Ann -- | Mode: "If the user doesn't give a mode, use this one." -- -- This mode is the default. If no mode is specified and a mode has this -- attribute then that mode is selected, otherwise an error is raised. -- --
-- modes [Mode1{..}, Mode2{..} &= auto, Mode3{..}] --auto :: Ann -- | Modes: "My program executable is named ..." -- -- This is the name of the program executable. Only used in the help -- message. Defaults to the type of the mode. -- --
-- Sample{..} &= program "sample" --program :: String -> Ann -- | Flag: "Don't guess any names for this field." -- -- A field should not have any flag names guessed for it. All flag names -- must be specified by flag. -- --
-- {hello = def &= explicit &= name "foo"} -- --foo=VALUE --explicit :: Ann -- | Flag/Mode: "Ignore this field, don't let the user set it." -- -- A mode or field is not dealt with by CmdArgs. -- --
-- {hello = def, extra = def &= ignore} -- --hello=VALUE --ignore :: Ann -- | Modes: "My program needs verbosity flags." -- -- Add --verbose and --quiet flags. verbosity :: Ann -- | Modes: "Customise the help argument." -- -- Add extra options to a help argument, such as help, -- name, ignore or explicit. -- --
-- Sample{..} &= helpArg [explicit, name "h"] --helpArg :: [Ann] -> Ann -- | Modes: "Customise the version argument." -- -- Add extra options to a version argument, such as help, -- name, ignore or explicit. -- --
-- Sample{..} &= versionArg [ignore] --versionArg :: [Ann] -> Ann -- | Modes: "Customise the verbosity arguments." -- -- Add extra options to a verbosity arguments (--verbose and -- --quiet), such as help, name, ignore or -- explicit. The verbose options come first, followed by the quiet -- options. -- --
-- Sample{..} &= verbosityArgs [ignore] [name "silent", explicit] --verbosityArgs :: [Ann] -> [Ann] -> Ann -- | Add an annotation to a value. Note that if the value is evaluated more -- than once the annotation will only be available the first time. (&=) :: Data val => val -> Ann -> val -- | Modes: "I want a program with multiple modes, like darcs or cabal." -- -- Takes a list of modes, and creates a mode which includes them all. If -- you want one of the modes to be chosen by default, see auto. -- --
-- data Modes = Mode1 | Mode2 | Mode3 deriving Data -- cmdArgs $ modes [Mode1,Mode2,Mode3] --modes :: Data val => [val] -> val -- | Flag: "I want several different flags to set this one field to -- different values." -- -- This annotation takes a type which is an enumeration, and provides -- multiple separate flags to set the field to each value. -- --
-- data State = On | Off deriving Data -- data Mode = Mode {state :: State} -- cmdArgs $ Mode {state = enum [On &= help "Turn on",Off &= help "Turn off"]} -- --on Turn on -- --off Turn off --enum :: Data val => [val] -> val -- | Add an annotation to a value. (+=) :: Annotate ann -> ann -> Annotate ann -- | Create a constructor/record. The first argument should be the type of -- field, the second should be a list of fields constructed originally -- defined by := or :=+. -- -- This operation is not type safe, and may raise an exception at runtime -- if any field has the wrong type or label. record :: Data a => a -> [Annotate b] -> Annotate b -- | Lift a pure value to an annotation. atom :: Data val => val -> Annotate ann -- | This type represents an annotated value. The type of the underlying -- value is not specified. data Annotate ann -- | Construct a field, fieldname := value. (:=) :: (c -> f) -> f -> Annotate ann enum_ :: (Data c, Data f) => (c -> f) -> [Annotate Ann] -> Annotate Ann modes_ :: [Annotate Ann] -> Annotate Ann -- | The general type of annotations that can be associated with a value. data Ann -- | A mode. Each mode has three main features: -- --
-- data T a b = C1 a b | C2 deriving (Typeable, Data) ---- -- GHC will generate an instance that is equivalent to -- --
-- instance (Data a, Data b) => Data (T a b) where -- gfoldl k z (C1 a b) = z C1 `k` a `k` b -- gfoldl k z C2 = z C2 -- -- gunfold k z c = case constrIndex c of -- 1 -> k (k (z C1)) -- 2 -> z C2 -- -- toConstr (C1 _ _) = con_C1 -- toConstr C2 = con_C2 -- -- dataTypeOf _ = ty_T -- -- con_C1 = mkConstr ty_T "C1" [] Prefix -- con_C2 = mkConstr ty_T "C2" [] Prefix -- ty_T = mkDataType "Module.T" [con_C1, con_C2] ---- -- This is suitable for datatypes that are exported transparently. class Typeable a => Data a -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable a -- | This module re-exports the implicit command line parser. module System.Console.CmdArgs