| Safe Haskell | Safe-Infered |
|---|
System.Console.CmdTheLine
- module System.Console.CmdTheLine.Term
- module System.Console.CmdTheLine.Arg
- module System.Console.CmdTheLine.ArgVal
- data Term a
- data TermInfo = TermInfo {}
- class Default a where
- def :: a
- data ManBlock
- data ArgInfo
- data Fail
- data HelpFormat
- type Err a = Either Fail a
- ret :: Term (Err a) -> Term a
Documentation
Terms
CmdTheLine is centered around the Term Applicative Functor. It allows us
to define command line programs like the following.
import System.Console.CmdTheLine
import Control.Applicative
-- Define a flag argument under the names '--silent' and '-s'
silent :: Term Bool
silent = flag $ optInfo [ "silent", "s" ]
-- Define the 0th positional argument, defaulting to the value '"world"' in
-- absence.
greeted :: Term String
greeted = pos 0 "world" posInfo { argName = "GREETED" }
hello :: Bool -> String -> IO ()
hello silent str =
if silent
then return ()
else putStrLn $ "Hello, " ++ str ++ "!"
term :: Term (IO ())
term = foo <$> silent <*> greeted
termInfo :: TermInfo
termInfo = def { termName = "Hello", version = "1.0" }
main :: IO ()
main = run ( term, termInfo )
CmdTheLine then generates usage, help in the form of man-pages, and manages all the related tedium of getting values from the command line into our program so we can go on thinking in regular Haskell functions.
See the accompanying examples(including the above) provided under the
doc/examples directory of the distributed package, or go to
http://github.com/eli-frey/cmdtheline and peruse them there.
The underlying Applicative of the library. A Term represents a value
in the context of being computed from the command line arguments.
Instances
Information about a Term. It is recommended that TermInfos be
created by customizing the Default instance, as in
termInfo = def
{ termName = "caroline-no"
, termDoc = "carry a line off"
}
Constructors
| TermInfo | |
Fields
| |
class Default a where
A class for types with a default value.
Instances
| Default Double | |
| Default Float | |
| Default Int | |
| Default Int8 | |
| Default Int16 | |
| Default Int32 | |
| Default Int64 | |
| Default Integer | |
| Default Ordering | |
| Default Word | |
| Default Word8 | |
| Default Word16 | |
| Default Word32 | |
| Default Word64 | |
| Default () | |
| Default All | |
| Default Any | |
| Default IntSet | |
| Default TimeLocale | |
| Default TermInfo | |
| Default [a] | |
| Integral a => Default (Ratio a) | |
| Default a => Default (IO a) | |
| (Default a, RealFloat a) => Default (Complex a) | |
| Default a => Default (Dual a) | |
| Default (Endo a) | |
| Num a => Default (Sum a) | |
| Num a => Default (Product a) | |
| Default (First a) | |
| Default (Last a) | |
| Default (Maybe a) | |
| Default a => Default (Tree a) | |
| Default (Seq a) | |
| Default (IntMap v) | |
| Default (Set v) | |
| Default (DList a) | |
| Default r => Default (e -> r) | |
| (Default a, Default b) => Default (a, b) | |
| Default (Map k v) | |
| (Default a, Default b, Default c) => Default (a, b, c) | |
| (Default a, Default b, Default c, Default d) => Default (a, b, c, d) | |
| (Default a, Default b, Default c, Default d, Default e) => Default (a, b, c, d, e) |
Manpages
Any String argument to a ManBlock constructor may contain the
following significant forms for a limited kind of meta-programing.
- $(i,text): italicizes
text. - $(b,text): bolds
text. - $(mname): evaluates to the name of the default term if there are choices of commands, or the only term otherwise.
- $(tname): evaluates to the name of the currently evaluating term.
Additionally, text inside the content portion of an I constructor may
contain one of the following significant forms.
- $(argName): evaluates to the name of the argument being documented.
Argument information
Information about an argument. The following fields are exported for your use.
argName- ::
StringA name to be used in the documentation to refer to the argument's value. Defaults to"".
argDoc- ::
StringA documentation string for the argument. Defaults to"".
argSection- ::
StringThe section under which to place the argument's documentation. Defaults to"OPTIONS"for optional arguments and"ARGUMENTS"for positional arguments.
User error reporting
There is nothing stopping you from printing and formating your own error
messages. However, some of the time you will want more tight integration
with the library. That is what Fail, the Err monad, and ret are for.
Here is a snippet of an example program that can be found at
doc/examples/fail.hs in the library distribution tarball, or at
http://github.com/eli-frey/cmdtheline.
import System.Console.CmdTheLine
import Control.Applicative
import Text.PrettyPrint ( fsep -- Paragraph fill a list of 'Doc'.
, text -- Make a 'String' into a 'Doc'.
, quotes -- Quote a 'Doc'.
, (<+>) -- Glue two 'Doc' together with a space.
)
import Data.List ( intersperse )
failMsg, failUsage, success :: [String] -> Err String
failMsg strs = Left . MsgFail . fsep $ map text strs
failUsage strs = Left . UsageFail . fsep $ map text strs
success strs = Right . concat $ intersperse " " strs
help :: String -> Err String
help name
| any (== name) cmdNames = Left . HelpFail Pager $ Just name
| name == "" = Left $ HelpFail Pager Nothing
| otherwise =
Left . UsageFail $ quotes (text name) <+> text "is not the name of a command"
noCmd :: Err String
noCmd = Left $ HelpFail Pager Nothing
We can now turn any of these functions into a Term String by lifting into
Term and passing the result to ret to fold the Err monad into the
library. Here is an example of what it might look like to do this with noCmd.
noCmdTerm :: Term (Err String) noCmdTerm = pure noCmd prepedNoCmdTerm :: Term String prepedNoCmdTerm = ret noCmdTerm
Constructors
| MsgFail Doc | An arbitrary message to be printed on failure. |
| UsageFail Doc | A message to be printed along with the usage on failure. |
| HelpFail HelpFormat (Maybe String) | A format to print the help in and an optional name of the term
to print help for. If |