-- | A library for setting up a commandline parser and help generator for an -- application. It aims for conciseness, flexibility and composability. It -- supports both non-modal and modal (with subcommands -- like darcs, cabal and -- the like) applications. -- -- The library supports two main styles of representing flags and -- commands. These are called "Record" and "ADT", respectively, by the -- library. The Record representation is more straightforward and easier to use -- in most instances. The ADT interface is suitable for applications that -- require exact correspondence between the commandline and its runtime -- representation, or when an existing application is being ported to cmdlib -- that is using this style to represent flags. -- -- Using the Record-based interface, a simple Hello World application could -- look like this: -- -- > {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-} -- > import System.Console.CmdLib -- > import Control.Monad -- > -- > data Main = Main { greeting :: String, again :: Bool } -- > deriving (Typeable, Data, Eq) -- > -- > instance Attributes Main where -- > attributes _ = group "Options" [ -- > greeting %> [ Help "The text of the greeting.", ArgHelp "TEXT" -- > , Default "Hello world!" ], -- > again %> Help "Say hello twice." ] -- > -- > instance RecordCommand Main where -- > mode_summary _ = "Hello world with argument parsing." -- > -- > main = getArgs >>= executeR Main {} >>= \opts -> do -- > putStrLn (greeting opts) -- -- Then, saying ./hello --help will give us: -- -- > Hello world with argument parsing. -- > -- > Options: -- > --greeting=TEXT The text of the greeting. (default: Hello world!) -- > --again[=yes|no] Say hello twice. (default: no) module System.Console.CmdLib ( -- * News -- -- | Since version 0.2: The Positional arguments are no longer required to be -- strings. A default (fallback) command may be provided to -- "dispatch"/"dispatchR" (this has also incompatibly changed their -- signature, sorry about that! I have tried to make this extensible -- though...). The "help" command can now be disabled (dispatch [noHelp] -- ...). Commands can now specify how to process options: permuted, -- non-permuted or no options at all. See "optionStyle". -- * Attributes -- -- | To each flag, a number of attributes can be attached. Many reasonable -- defaults are provided by the library. The attributes are described by the -- "Attribute" type and are attached to flags using @"%>"@ and the related -- operators (all described in this section). Attribute(..), enable, disable, long, short, simple , (%%), (%>), (<%), (%+), (+%), everywhere, group -- * Flags -- | Flags (commandline options) can be represented in two basic styles, -- either as a plain ADT (algebraic data type) or as a record type. These two -- styles are implemented using "ADTFlag" and "ADT" for the former and -- "RecordFlag" and "Record" for the latter. The *Flag classes can be used to -- attach attributes to flags and to override the parser for option -- arguments. However, an empty instance is valid for both cases. The "ADT" -- and "Record" newtype wrappers are then used in a "Command" or -- "RecordCommand" instance declaration. , ADT, Record, Attributes(..) -- * Commands , (%:), commandGroup, Command(..), dispatch, execute, helpCommands, helpOptions , noHelp, defaultCommand, OptionStyle(..) -- * Record-based commands , RecordCommand(..), RecordMode(..), recordCommands, dispatchR, executeR -- * Utilities , globalFlag, readCommon, (<+<), HelpCommand(..), die -- * Convenience re-exports , Data, Typeable, getArgs ) where import System.Console.CmdLib.Attribute import System.Console.CmdLib.Flag import System.Console.CmdLib.Command import System.Console.CmdLib.ADTs import System.Console.CmdLib.Record import Data.Data import Data.Typeable import Data.IORef import System.IO.Unsafe import System.Environment -- | Create a global setter/getter pair for a flag. The setter can be then -- passed to the "Global" attribute and the getter used globally to query value -- of that flag. Example: -- -- > data Flag = Wibblify Int | Verbose Bool -- > (setVerbose, isVerbose) = globalFlag False -- > -- > instance ADTFlag Flag where -- > adt_attrs _ = Verbose %> Global setVerbose -- > -- > putVerbose str = isVerbose >>= flip when (putStrLn str) globalFlag :: a -> (a -> IO (), IO a) globalFlag def = unsafePerformIO $ do ref <- newIORef def return (writeIORef ref, readIORef ref) {-# NOINLINE globalFlag #-}