cmdtheline-0.2.3: Declarative command-line option parsing and documentation library.

Safe HaskellSafe-Inferred

System.Console.CmdTheLine

Contents

Synopsis

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

 import Control.Monad ( when )

 -- Define a flag argument under the names '--silent' and '-s'
 silent :: Term Bool
 silent = value . flag $ optInfo [ "silent", "s" ]

 -- Define the 0th positional argument, defaulting to the value '"world"' in
 -- absence.
 greeted :: Term String
 greeted = value $ pos 0 "world" posInfo { posName = "GREETED" }
 
 hello :: Bool -> String -> IO ()
 hello silent str = when (not silent) . putStrLn $ "Hello, " ++ str ++ "!"

 term :: Term (IO ())
 term = hello <$> silent <*> greeted
 
 termInfo :: TermInfo
 termInfo = defTI { 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.

data Term a Source

The underlying Applicative of the library. A Term represents a value in the context of being computed from the command line arguments.

data TermInfo Source

Information about a Term. It is recommended that TermInfos be created by customizing defTI, as in

 termInfo = defTI
   { termName = "caroline-no"
   , termDoc  = "carry a line off"
   }

Constructors

TermInfo 

Fields

termName :: String

The name of the command or program represented by the term. Defaults to "".

termDoc :: String

Documentation for the term. Defaults to "".

termSec :: String

The section under which to place the terms documentation. Defaults to "COMMANDS".

stdOptSec :: String

The section under which to place a term's argument's documentation by default. Defaults to "OPTIONS".

version :: String

A version string. Must be left blank for commands. Defaults to "".

man :: [ManBlock]

A list of ManBlocks to append to the default [ManBlock]. Defaults to [].

Instances

Manpages

data ManBlock Source

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.

Constructors

S String

A section title.

P String

A paragraph.

I String String

A label-content pair. As in an argument definition and its accompanying documentation.

NoBlank

Suppress the normal blank line following a P or an I.

Instances

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 = msgFail   . fsep $ map text strs
 failUsage strs = usageFail . fsep $ map text strs
 success   strs = return . concat $ intersperse " " strs

 help :: String -> Err String
 help name
   | any (== name) cmdNames = helpFail Pager $ Just name
   | name == ""             = helpFail Pager Nothing
   | otherwise              =
     usageFail $ quotes (text name) <+> text "is not the name of a command"

 noCmd :: Err String
 noCmd = 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

For other examples of ways to use the Err monad, see the source of the *Exists family of functions in System.Console.CmdTheLine.Util.

data HelpFormat Source

The format to print help in.

Constructors

Pager 
Plain 
Groff 

type Err = ErrorT Fail IOSource

A monad for values in the context of possibly failing with a helpful message.

msgFail :: Doc -> Err aSource

Fail with an arbitrary message on failure.

usageFail :: Doc -> Err aSource

Fail with a message along with the usage on failure.

helpFail :: HelpFormat -> Maybe String -> Err aSource

A format to print the help in and an optional name of the term to print help for. If Nothing is supplied, help will be printed for the currently evaluating term.

ret :: Term (Err a) -> Term aSource

ret term folds term's Err context into the library to be handled internally and as seamlessly as other error messages that are built in.