-- 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. -- -- -- -- For a general reference on what command line flags are commonly used, -- see http://www.faqs.org/docs/artu/ch10s05.html. @package cmdargs @version 0.10.2 -- | A module to deal with verbosity, how 'chatty' a program should be. -- This module defines the Verbosity data type, along with -- functions for manipulating a global verbosity value. module System.Console.CmdArgs.Verbosity -- | The verbosity data type data Verbosity -- | Only output essential messages (typically errors) Quiet :: Verbosity -- | Output normal messages (typically errors and warnings) Normal :: Verbosity -- | Output lots of messages (typically errors, warnings and status -- updates) Loud :: Verbosity -- | Set the global verbosity. setVerbosity :: Verbosity -> IO () -- | Get the global verbosity. Initially Normal before any calls -- to setVerbosity. getVerbosity :: IO Verbosity -- | Used to test if warnings should be output to the user. True -- if the verbosity is set to Normal or Loud (when -- --quiet is not specified). isNormal :: IO Bool -- | Used to test if status updates should be output to the user. -- True if the verbosity is set to Loud (when -- --verbose is specified). isLoud :: IO Bool -- | An action to perform if the verbosity is normal or higher, based on -- isNormal. whenNormal :: IO () -> IO () -- | An action to perform if the verbosity is loud, based on isLoud. whenLoud :: IO () -> IO () instance Typeable Verbosity instance Eq Verbosity instance Ord Verbosity instance Bounded Verbosity instance Enum Verbosity instance Show Verbosity instance Read Verbosity instance Data Verbosity -- | Module for implementing CmdArgs helpers. A CmdArgs helper is an -- external program, that helps a user construct the command line -- arguments. To use a helper set the environment variable -- $CMDARGS_HELPER (or -- $CMDARGS_HELPER_YOURPROGRAM) to one of: -- -- module System.Console.CmdArgs.Helper -- | Run a remote command line entry. execute :: String -> Mode a -> [String] -> IO (Either String [String]) -- | Unknown value, representing the values stored within the Mode -- structure. While the values are not observable, they behave -- identically to the original values. data Unknown -- | Receive information about the mode to display. receive :: IO (Mode Unknown) -- | Send a reply with either an error, or a list of flags to use. This -- function exits the helper program. reply :: Either String [String] -> IO () -- | Send a comment which will be displayed on the calling console, mainly -- useful for debugging. comment :: String -> IO () instance Show Pack instance Read Pack instance Packer FlagInfo instance Packer a => Packer (Arg a) instance Packer a => Packer (Flag a) instance Packer a => Packer (Mode a) instance Packer a => Packer (Group a) instance Packer Bool instance (Packer a, Packer b) => Packer (Either a b) instance Packer a => Packer (Maybe a) instance (Packer a, Packer b) => Packer (a, b) instance Packer Int instance Packer Char instance Packer Value instance (Packer a, Packer b) => Packer (a -> b) instance Packer a => Packer [a] instance Read (NoShow a) instance Show (NoShow a) -- | This module provides default values for many types. To use the default -- value simply write def. module System.Console.CmdArgs.Default -- | Class for default values. class Default a def :: Default a => a instance (Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9, Default a10) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) instance (Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8, Default a9) => Default (a1, a2, a3, a4, a5, a6, a7, a8, a9) instance (Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7, Default a8) => Default (a1, a2, a3, a4, a5, a6, a7, a8) instance (Default a1, Default a2, Default a3, Default a4, Default a5, Default a6, Default a7) => Default (a1, a2, a3, a4, a5, a6, a7) instance (Default a1, Default a2, Default a3, Default a4, Default a5, Default a6) => Default (a1, a2, a3, a4, a5, a6) instance (Default a1, Default a2, Default a3, Default a4, Default a5) => Default (a1, a2, a3, a4, a5) instance (Default a1, Default a2, Default a3, Default a4) => Default (a1, a2, a3, a4) instance (Default a1, Default a2, Default a3) => Default (a1, a2, a3) instance (Default a1, Default a2) => Default (a1, a2) instance Default Word64 instance Default Word32 instance Default Word16 instance Default Word8 instance Default Word instance Default Int64 instance Default Int32 instance Default Int16 instance Default Int8 instance Default (Maybe a) instance Default [a] instance Default Double instance Default Float instance Default Integer instance Default Int instance Default Bool instance Default () -- | A module to represent text with very basic formatting. Values are of -- type [Text] and shown with showText. -- -- As an example of the formatting: -- --
--   [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: -- -- data Text Line :: String -> Text Cols :: [String] -> Text -- | Show some text using the given formatting. showText :: TextFormat -> [Text] -> String instance Read TextFormat instance Show TextFormat instance Eq TextFormat instance Ord TextFormat instance Show Text instance Default TextFormat -- | This module constructs command lines. You may either use the helper -- functions (flagNone, flagOpt, mode etc.) or -- construct the type directly. These types are intended to give all the -- necessary power to the person constructing a command line parser. -- -- For people constructing simpler command line parsers, the module -- System.Console.CmdArgs.Implicit may be more appropriate. -- -- As an example of a parser: -- --
--   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
--       xs <- processArgs arguments
--       if ("help","") `elem` xs then
--           print $ helpText [] HelpFormatDefault arguments
--        else
--           print xs
--   
-- -- 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. -- -- Parsing rules: Command lines are parsed as per most GNU -- programs. Short arguments single letter flags start with -, -- longer flags start with --, and everything else is considered -- an argument. Anything after -- alone is considered to be an -- argument. For example: -- --
--   -f --flag argument1 -- --argument2
--   
-- -- This command line passes one single letter flag (f), one -- longer flag (flag) and two arguments (argument1 and -- --argument2). module System.Console.CmdArgs.Explicit -- | Process a list of flags (usually obtained from -- getArgs/expandArgsAt) 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 the flags obtained by getArgs and -- expandArgsAt 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. This -- function makes use of the following environment variables: -- -- processArgs :: Mode a -> IO a -- | Process a list of flags (usually obtained from getArgs -- and expandArgsAt) 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. This -- function does not take account of any environment variables that may -- be set (see processArgs). processValue :: Mode a -> [String] -> 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. Do not use the Mode constructor directly, instead use -- mode to construct the Mode and then record updates. Each -- mode has three main features: -- -- -- -- To produce the help information for a mode, either use -- helpText or show. data Mode a Mode :: Group (Mode a) -> [Name] -> a -> (a -> Either String a) -> (a -> Maybe [String]) -> Bool -> Help -> [String] -> ([Arg a], Maybe (Arg a)) -> Group (Flag a) -> Mode a -- | The available sub-modes modeGroupModes :: Mode a -> Group (Mode a) -- | The names assigned to this mode (for the root mode, this name is used -- as the program name) modeNames :: Mode a -> [Name] -- | Value to start with modeValue :: Mode a -> a -- | Check the value reprsented by a mode is correct, after applying all -- flags modeCheck :: Mode a -> a -> Either String a -- | Given a value, try to generate the input arguments. modeReform :: Mode a -> a -> Maybe [String] -- | Expand @ arguments with expandArgsAt, defaults to -- True, only applied if using an IO processing function. -- Only the root Modes value will be used. modeExpandAt :: Mode a -> Bool -- | Help text modeHelp :: Mode a -> Help -- | A longer help suffix displayed after a mode modeHelpSuffix :: Mode a -> [String] -- | The unnamed arguments, a series of arguments, followed optionally by -- one for all remaining slots modeArgs :: Mode a -> ([Arg a], Maybe (Arg a)) -- | Groups of flags modeGroupFlags :: Mode a -> Group (Flag a) -- | Extract the modes from a Mode modeModes :: Mode a -> [Mode a] -- | Extract the flags from a Mode modeFlags :: Mode a -> [Flag a] -- | The FlagInfo type has the following meaning: -- --
--                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 -> Bool -> 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 -- | Is at least one of these arguments required, the command line will -- fail if none are set argRequire :: Arg a -> Bool -- | 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 remapUpdate :: Functor f => t -> (t1 -> (t2, a -> b)) -> (t3 -> t2 -> f a) -> t3 -> t1 -> f b -- | Create an empty mode specifying only modeValue. All other -- fields will usually be populated using record updates. modeEmpty :: a -> Mode a -- | 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 -- | Bash completion information HelpFormatBash :: HelpFormat -- | Z shell completion information HelpFormatZsh :: HelpFormat -- | Generate a help message from a mode. The first argument is a prefix, -- which is prepended when not using HelpFormatBash or -- HelpFormatZsh. helpText :: [String] -> HelpFormat -> Mode a -> [Text] -- | Expand @ directives in a list of arguments, usually obtained -- from getArgs. As an example, given the file test.txt -- with the lines hello and world: -- --
--   expandArgsAt ["@test.txt","!"] == ["hello","world","!"]
--   
-- -- Any @ directives in the files will be recursively expanded -- (raising an error if there is infinite recursion). -- -- To supress @ expansion, pass any @ arguments after -- --. expandArgsAt :: [String] -> IO [String] -- | Given a string, split into the available arguments. The inverse of -- joinArgs. splitArgs :: String -> [String] -- | Given a sequence of arguments, join them together in a manner that -- could be used on the command line, giving preference to the Windows -- cmd shell quoting conventions. -- -- For an alternative version, intended for actual running the result in -- a shell, see System.Process.showCommandForUser joinArgs :: [String] -> String -- | How to complete a command line option. The Show instance is -- suitable for parsing from shell scripts. data Complete -- | Complete to a particular value CompleteValue :: String -> Complete -- | Complete to a prefix, and a file CompleteFile :: String -> FilePath -> Complete -- | Complete to a prefix, and a directory CompleteDir :: String -> FilePath -> Complete -- | Given a current state, return the set of commands you could type now, -- in preference order. complete :: Mode a -> [String] -> (Int, Int) -> [Complete] -- | 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: -- -- -- -- getOpt returns a triple consisting of the option arguments, a -- list of non-options, and a list of error messages. -- -- Changes: The list of errors will contain at most one entry, and -- if an error is present then the other two lists will be empty. getOpt :: ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String]) -- | Changes: This is exactly the same as getOpt, but the 3rd -- element of the tuple (second last) will be an empty list. getOpt' :: ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String], [String]) -- | Return a string describing the usage of a command, derived from the -- header (first argument) and the options described by the second -- argument. usageInfo :: String -> [OptDescr a] -> String -- | What to do with options following non-options. -- -- Changes: Only Permute is allowed, both -- RequireOrder and ReturnInOrder have been removed. data ArgOrder a Permute :: ArgOrder a -- | Each OptDescr describes a single option/flag. -- -- The arguments to Option are: -- -- data OptDescr a Option :: [Char] -> [String] -> (ArgDescr a) -> String -> OptDescr a -- | Describes whether an option takes an argument or not, and if so how -- the argument is injected into a value of type a. data ArgDescr a -- | no argument expected NoArg :: a -> ArgDescr a -- | option requires argument ReqArg :: (String -> a) -> String -> ArgDescr a -- | optional argument OptArg :: (Maybe String -> a) -> String -> ArgDescr a -- | This module captures annotations on a value, and builds a -- Capture value. This module has two ways of writing annotations: -- -- Impure: The impure method of writing annotations is susceptible -- to over-optimisation by GHC - sometimes {-# OPTIONS_GHC -fno-cse -- #-} will be required. -- -- Pure: The pure method is more verbose, and lacks some type -- safety. -- -- As an example of the two styles: -- --
--   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 ann] -> 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 -- | Add annotations to a field. (:=+) :: (c -> f) -> [Annotate ann] -> Annotate ann instance Typeable1 Annotate instance Typeable ExceptionInt instance Show ann => Show (Capture ann) instance Show ExceptionInt 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: -- -- -- -- Supported Types: Each field in the record must be one of the -- supported atomic types (String, Int, -- Integer, Float, Double, Bool, an -- enumeration, a tuple of atomic types) or a list ([]) or -- Maybe wrapping at atomic type. -- -- Missing Fields: If a field is shared by multiple modes, it may -- be omitted in subsequent modes, and will default to the previous -- value. -- -- Purity: Values created with annotations are not pure - the -- first time they are computed they will include the annotations, but -- subsequently they will not. If you wish to run the above example in a -- more robust way: -- --
--   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. -- -- Pure annotations: Alternatively, you may use pure annotations, -- which are referentially transparent, but less type safe and more -- verbose. The initial example may be written as: -- -- sample = record Sample{} [hello := def += -- help "World argument" += opt "world"] -- += summary "Sample v1" -- --
--   main = print =<< (cmdArgs_ sample :: IO Sample)
--   
-- -- All the examples are written using impure annotations. To convert to -- pure annotations follow the rules: -- --
--   Ctor {field1 = value1 &= ann1, field2 = value2} &= ann2 ==> record Ctor{} [field1 := value1 += ann1, field2 := value2] += ann2
--   Ctor (value1 &= ann1) value2 &= ann2 ==> record Ctor{} [atom value1 += ann1, atom value2] += ann2
--   modes [Ctor1{...}, Ctor2{...}] ==> modes_ [record Ctor1{} [...], record Ctor2{} [...]]
--   Ctor {field1 = enum [X &= ann, Y]} ==> record Ctor{} [enum_ field1 [atom X += ann, atom Y]]
--   
-- -- If you are willing to use TemplateHaskell, you can write in the impure -- syntax, but have your code automatically translated to the pure style. -- For more details see System.Console.CmdArgs.Quote. module System.Console.CmdArgs.Implicit -- | Take impurely annotated records and run the corresponding command -- line. Shortcut for cmdArgsRun . cmdArgsMode. -- -- To use cmdArgs with custom command line arguments see -- withArgs. 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: -- -- cmdArgsRun :: Mode (CmdArgs a) -> IO a -- | Take purely annotated records and run the corresponding command line. -- Shortcut for cmdArgsRun . cmdArgsMode_. -- -- To use cmdArgs_ with custom command line arguments see -- withArgs. cmdArgs_ :: Data a => Annotate Ann -> IO a -- | Take purely annotated records and turn them in to a Mode value, -- that can make use of the System.Console.CmdArgs.Explicit -- functions (i.e. process). cmdArgsMode_ :: Data a => Annotate Ann -> Mode (CmdArgs a) -- | Perform the necessary actions dictated by a CmdArgs structure. -- -- cmdArgsApply :: CmdArgs a -> IO a -- | A structure to store the additional data relating to --help, -- --version, --quiet and --verbose. data CmdArgs a CmdArgs :: a -> Maybe String -> Maybe String -> Maybe Verbosity -> CmdArgsPrivate -> CmdArgs a -- | The underlying value being wrapped. cmdArgsValue :: CmdArgs a -> a -- | Just if --help is given, then gives the help message -- for display, including a trailing newline. cmdArgsHelp :: CmdArgs a -> Maybe String -- | Just if --version is given, then gives the version -- message for display, including a trailing newline. cmdArgsVersion :: CmdArgs a -> Maybe String -- | Just if --quiet or --verbose is given, then -- gives the verbosity to use. cmdArgsVerbosity :: CmdArgs a -> Maybe Verbosity -- | Private: Only exported due to Haddock limitations. cmdArgsPrivate :: CmdArgs a -> CmdArgsPrivate -- | Flag: "I want users to be able to omit the value associated with this -- flag." -- -- Make the value of a flag optional. If --flag is given, it -- will be treated as --flag=this_argument. -- --
--   {hello = def &= opt "foo"}
--     -h --hello[=VALUE]    (default=foo)
--   
-- -- Note that all flags in CmdArgs are optional, and if omitted will use -- their default value. Those annotated with opt also allow the -- flag to be present without an associated value. As an example: -- --
--   {hello = "DEFAULT" &= opt "OPTIONAL"}
--   
-- --
--   $ main
--   {hello = "DEFAULT"}
--   $ main --hello
--   {hello = "OPTIONAL"}
--   $ main --hello=VALUE
--   {hello = "VALUE"}
--   
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, summary 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 -- | Program: "Turn off @ expansion." -- -- Usually arguments starting with @ are treated as a file containing a -- set of arguments. This annotation turns off that behaviour. -- --
--   Sample{..} &= noAtExpand
--   
noAtExpand :: 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. The first -- element in the list is used as the value of the field. -- --
--   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 ann] -> Annotate ann -- | 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 -- | Like enum, but using the pure annotations. enum_ :: (Data c, Data f) => (c -> f) -> [Annotate Ann] -> Annotate Ann -- | Like modes, but using the pure annotations. modes_ :: [Annotate Ann] -> Annotate Ann -- | The general type of annotations that can be associated with a value. data Ann -- | A mode. Do not use the Mode constructor directly, instead use -- mode to construct the Mode and then record updates. Each -- mode has three main features: -- -- -- -- To produce the help information for a mode, either use -- helpText or show. data Mode a -- | The Data class comprehends a fundamental primitive -- gfoldl for folding over constructor applications, say terms. -- This primitive can be instantiated in several ways to map over the -- immediate subterms of a term; see the gmap combinators later -- in this class. Indeed, a generic programmer does not necessarily need -- to use the ingenious gfoldl primitive but rather the intuitive -- gmap combinators. The gfoldl primitive is completed by -- means to query top-level constructors, to turn constructor -- representations into proper terms, and to list all possible datatype -- constructors. This completion allows us to serve generic programming -- scenarios like read, show, equality, term generation. -- -- The combinators gmapT, gmapQ, gmapM, etc are all -- provided with default definitions in terms of gfoldl, leaving -- open the opportunity to provide datatype-specific definitions. (The -- inclusion of the gmap combinators as members of class -- Data allows the programmer or the compiler to derive -- specialised, and maybe more efficient code per datatype. Note: -- gfoldl is more higher-order than the gmap combinators. -- This is subject to ongoing benchmarking experiments. It might turn out -- that the gmap combinators will be moved out of the class -- Data.) -- -- Conceptually, the definition of the gmap combinators in terms -- of the primitive gfoldl requires the identification of the -- gfoldl function arguments. Technically, we also need to -- identify the type constructor c for the construction of the -- result type from the folded term type. -- -- In the definition of gmapQx combinators, we use -- phantom type constructors for the c in the type of -- gfoldl because the result type of a query does not involve the -- (polymorphic) type of the term argument. In the definition of -- gmapQl we simply use the plain constant type constructor -- because gfoldl is left-associative anyway and so it is readily -- suited to fold a left-associative binary operation over the immediate -- subterms. In the definition of gmapQr, extra effort is needed. We use -- a higher-order accumulation trick to mediate between left-associative -- constructor application vs. right-associative binary operation (e.g., -- (:)). When the query is meant to compute a value of type -- r, then the result type withing generic folding is r -- -> r. So the result of folding is a function to which we -- finally pass the right unit. -- -- With the -XDeriveDataTypeable option, GHC can generate -- instances of the Data class automatically. For example, given -- the declaration -- --
--   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 provides a quotation feature to let you write command line -- arguments in the impure style, but have them translated into the pure -- style, as per System.Console.CmdArgs.Implicit. An example: -- --
--   {-# LANGUAGE TemplateHaskell, DeriveDataTypeable, MagicHash #-}
--   import System.Console.CmdArgs.Implicit
--   import System.Console.CmdArgs.Quote
--   
--   data Sample = Sample {hello :: String} deriving (Show, Data, Typeable)
--   
--   $(cmdArgsQuote [d|
--       sample = Sample{hello = def &=# help "World argument" &=# opt "world"}
--                      &=# summary "Sample v1"
--   
--       run = cmdArgs# sample :: IO Sample
--       |])
--   
--   main = print =<< run
--   
-- -- Inside cmdArgsQuote you supply the command line parser using -- attributes in the impure style. If you run with -- -ddump-splices (to see the Template Haskell output), you -- would see: -- --
--   run = cmdArgs_
--       (record Sample{} [hello := def += help "World argument" += opt "world"]
--           += summary "Sample v1")
--       :: IO Sample
--   
-- -- Stubs -- -- To define the original parser you may use either the standard impure -- annotations ('(&=)', modes), or the stub annotations -- versions defined in this module ('(&=#)', modes). The stub -- versions do not include a Data constraint, so can be used in -- situations where the Data instance is not yet available - typically -- when defining the parser in the same module as the data type on GHC -- 7.2 and above. The stub versions should never be used outside -- cmdArgsQuote and will always raise an error. -- -- Explicit types -- -- There will be a limited number of situations where an impure parser -- will require additional types, typically on the result of -- cmdArgs if the result is used without a fixed type - for -- example if you show it. Most users will not need to add any -- types. In some cases you may need to remove some explicit types, where -- the intermediate type of the annotations has changed - but again, this -- change should be rare. -- -- Completeness -- -- The translation is not complete, although works for all practical -- instances I've tried. The translation works by first expanding out the -- expression (inlining every function defined within the quote, inlining -- let bindings), then performs the translation. This scheme leads to two -- consequences: 1) Any expensive computation executed inside the -- quotation to produce the command line flags may be duplicated (a very -- unlikely scenario). 2) As I do not yet have expansion rules for all -- possible expressions, the expansion (and subsequently the translation) -- may fail. I am interested in any bug reports where the feature does -- not work as intended. module System.Console.CmdArgs.Quote -- | Quotation function to turn an impure version of -- System.Console.CmdArgs.Implicit into a pure one. For details -- see System.Console.CmdArgs.Quote. cmdArgsQuote :: Q [Dec] -> Q [Dec] -- | Version of &= without a Data context, only to be -- used within cmdArgsQuote. (&=#) :: a -> Ann -> a -- | Version of modes without a Data context, only to be used -- within cmdArgsQuote. modes# :: [a] -> a -- | Version of cmdArgsMode without a Data context, only to -- be used within cmdArgsQuote. cmdArgsMode# :: a -> Mode (CmdArgs a) -- | Version of cmdArgs without a Data context, only to be -- used within cmdArgsQuote. cmdArgs# :: a -> IO a -- | Version of enum without a Data context, only to be used -- within cmdArgsQuote. enum# :: [a] -> a -- | This module re-exports the implicit command line parser. module System.Console.CmdArgs