cmdargs-0.10.5: Command line argument processing

Safe HaskellNone

System.Console.CmdArgs.Quote

Contents

Description

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.

Synopsis

Template Haskell quotation function

cmdArgsQuote :: Q [Dec] -> Q [Dec]Source

Quotation function to turn an impure version of System.Console.CmdArgs.Implicit into a pure one. For details see System.Console.CmdArgs.Quote.

Stub versions of the impure annotations

(&=#) :: a -> Ann -> aSource

Version of &= without a Data context, only to be used within cmdArgsQuote.

modes# :: [a] -> aSource

Version of modes without a Data context, only to be used within cmdArgsQuote.

cmdArgsMode# :: a -> Mode (CmdArgs a)Source

Version of cmdArgsMode without a Data context, only to be used within cmdArgsQuote.

cmdArgs# :: a -> IO aSource

Version of cmdArgs without a Data context, only to be used within cmdArgsQuote.

enum# :: [a] -> aSource

Version of enum without a Data context, only to be used within cmdArgsQuote.