Safe Haskell | Safe |
---|---|
Language | Haskell98 |
This library auto-generates command-line parsers for data types using Haskell's built-in support for generic programming. The best way to understand how this library works is to walk through a few examples.
For example, suppose that you want to parse a record with named fields like this:
-- Example.hs {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} import Options.Generic data Example = Example { foo :: Int, bar :: Double } deriving (Generic, Show) instance ParseRecord Example main = do x <- getRecord "Test program" print (x :: Example)
Named fields translate to flags which you can provide in any order:
$ stack build optparse-generic $ stack runghc Example.hs -- --bar 2.5 --foo 1 Example {foo = 1, bar = 2.5}
This also auto-generates --help
output:
$ stack runghc Example.hs -- --help Test program Usage: Example.hs --foo INT --bar DOUBLE Available options: -h,--help Show this help text
You can also add help descriptions to each field, like this:
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeOperators #-} import Options.Generic data Example = Example { foo :: Int <?> "Documentation for the foo flag" , bar :: Double <?> "Documentation for the bar flag" } deriving (Generic, Show) instance ParseRecord Example main = do x <- getRecord "Test program" print (x :: Example)
... which produces the following --help
output:
$ stack runghc Example.hs -- --help Test program Usage: Example.hs --foo INT --bar DOUBLE Available options: -h,--help Show this help text --foo INT Documentation for the foo flag --bar DOUBLE Documentation for the bar flag
However, any fields you document will be wrapped in the Helpful
constructor:
$ stack runghc Example.hs -- --foo 1 --bar 2.5 Example {foo = Helpful {unHelpful = 1}, bar = Helpful {unHelpful = 2.5}}
To avoid this, while still being able to document your fields, you may
generalize the definition of your record with a parameter w
, and use
unwrapRecord
.
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleInstances #-} -- One more extension. {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE StandaloneDeriving #-} -- To derive Show {-# LANGUAGE TypeOperators #-} import Options.Generic data Example w = Example { foo :: w ::: Int <?> "Documentation for the foo flag" , bar :: w ::: Double <?> "Documentation for the bar flag" } deriving (Generic) instance ParseRecord (Example Wrapped) deriving instance Show (Example Unwrapped) main = do x <- unwrapRecord "Test program" print (x :: Example Unwrapped)
Example Unwrapped
is equivalent to a record type with simple fields:
$ stack runghc Example.hs -- --foo 1 --bar 2.5 Example {foo = 1, bar = 2.5}
For the following examples I encourage you to test what --help
output they
generate.
This library will also do the right thing if the fields have no labels:
data Example = Example Int Double deriving (Generic, Show)
Fields without labels translate into positional command-line arguments:
$ stack runghc Example.hs -- 1 2.5 Example 1 2.5
Certain types of fields are given special treatment, such as in this example:
data Example = Example { switch :: Bool , list :: [Int] , optional :: Maybe Int , first :: First Int , last :: Last Int , sum :: Sum Int , product :: Product Int } deriving (Generic, Show)
This gives the following behavior:
$ stack runghc Example.hs -- --switch --optional 1 --list 1 --list 2 --first 1 --first 2 --last 1 --last 2 --sum 1 --sum 2 --product 1 --product 2 Example {switch = True, list = [1,2], optional = Just 1, first = First {getFirst = Just 1}, last = Last {getLast = Just 2}, sum = Sum {getSum = 3}, product = Product {getProduct = 2}} $ stack runghc Example.hs Example {switch = False, list = [], optional = Nothing, first = First {getFirst = Nothing}, second = Last {getLast = Nothing}, sum = Sum {getSum = 0}, product = Product {getProduct = 1}}
If a datatype has multiple constructors:
data Example = Create { name :: Text, duration :: Maybe Int } | Kill { name :: Text } deriving (Generic, Show)
... then they will translate into subcommands named after each constructor:
$ stack runghc Example.hs -- create --name foo --duration=60 Create {name = "foo", duration = Just 60} $ stack runghc Example.hs -- kill --name foo Kill {name = "foo"}
This library also provides out-of-the-box support for many existing types,
like tuples and Either
.
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} import Options.Generic main = do x <- getRecord "Test program" print (x :: Either Double Int)
$ stack runghc Example.hs -- left 1.0 Left 1.0 $ stack runghc Example.hs -- right 2 Right 2
main = do x <- getRecord "Test program" print (x :: (Double, Int))
$ stack runghc Example.hs -- 1.0 2 (1.0,2)
... and you can also just parse a single value:
main = do x <- getRecord "Test program" print (x :: Int)
$ stack runghc Example.hs -- 2 2
However, there are some types that this library cannot generate sensible command-line parsers for, such as:
recursive types:
data Example = Example { foo :: Example }
records whose fields are other records
data Outer = Outer { foo :: Inner } deriving (Show, Generic) data Inner = Inner { bar :: Int } deriving (Show, Generic)
record fields with nested
Maybe
s or nested listsdata Example = Example { foo :: Maybe (Maybe Int) } data Example = Example { foo :: [[Int]] }
If you try to auto-generate a parser for these types you will get an error at compile time that will look something like this:
No instance for (ParseFields TheTypeOfYourField) arising from a use of ‘Options.Generic.$gdmparseRecord’ In the expression: Options.Generic.$gdmparseRecord In an equation for ‘parseRecord’: parseRecord = Options.Generic.$gdmparseRecord In the instance declaration for ‘ParseRecord TheTypeOfYourRecord’
You can customize the library's default behavior using the
parseRecordWithModifiers
utility, like this:
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} import Options.Generic data Example = Example { foo :: Int, bar :: Double } deriving (Generic, Show) modifiers :: Modifiers modifiers = defaultModifiers { shortNameModifier = firstLetter } instance ParseRecord Example where parseRecord = parseRecordWithModifiers modifiers main = do x <- getRecord "Test program" print (x :: Example)
- getRecord :: (MonadIO io, ParseRecord a) => Text -> io a
- getWithHelp :: (MonadIO io, ParseRecord a) => Text -> io (a, io ())
- getRecordPure :: ParseRecord a => [Text] -> Maybe a
- unwrapRecord :: (Functor io, MonadIO io, ParseRecord (f Wrapped), Unwrappable f) => Text -> io (f Unwrapped)
- unwrapWithHelp :: (MonadIO io, ParseRecord (f Wrapped), Unwrappable f) => Text -> io (f Unwrapped, io ())
- unwrapRecordPure :: (ParseRecord (f Wrapped), Unwrappable f) => [Text] -> Maybe (f Unwrapped)
- class ParseRecord a where
- class ParseRecord a => ParseFields a where
- class ParseField a where
- newtype Only a :: * -> * = Only {
- fromOnly :: a
- getOnly :: Only a -> a
- data Modifiers = Modifiers {
- fieldNameModifier :: String -> String
- constructorNameModifier :: String -> String
- shortNameModifier :: String -> Maybe Char
- parseRecordWithModifiers :: (Generic a, GenericParseRecord (Rep a)) => Modifiers -> Parser a
- defaultModifiers :: Modifiers
- lispCaseModifiers :: Modifiers
- firstLetter :: String -> Maybe Char
- newtype (field :: *) <?> (help :: Symbol) = Helpful {
- unHelpful :: field
- type family wrap ::: wrapped
- data Wrapped
- data Unwrapped
- type Unwrappable f = (Generic (f Wrapped), Generic (f Unwrapped), GenericUnwrappable (Rep (f Wrapped)) (Rep (f Unwrapped)))
- class Generic a
- data Text :: *
- newtype All :: * = All {}
- newtype Any :: * = Any {}
- newtype First a :: * -> * = First {}
- newtype Last a :: * -> * = Last {}
- newtype Sum a :: * -> * = Sum {
- getSum :: a
- newtype Product a :: * -> * = Product {
- getProduct :: a
Parsers
:: (MonadIO io, ParseRecord a) | |
=> Text | Program description |
-> io a |
Marshal any value that implements ParseRecord
from the command line
If you need to modify the top-level ParserInfo
or ParserPrefs
use the getRecordWith
function.
:: (MonadIO io, ParseRecord a) | |
=> Text | Program description |
-> io (a, io ()) | (options, io action to print help message) |
Marshal any value that implements ParseRecord
from the commmand line
alongside an io action that prints the help message.
:: ParseRecord a | |
=> [Text] | Command-line arguments |
-> Maybe a |
Pure version of getRecord
If you need to modify the parser's ParserInfo
or ParserPrefs
, use
getRecordPureWith
.
>>>
:set -XOverloadedStrings
>>>
getRecordPure ["1"] :: Maybe Int
Just 1>>>
getRecordPure ["1", "2"] :: Maybe [Int]
Just [1,2]>>>
getRecordPure ["Foo"] :: Maybe Int
Nothing
unwrapRecord :: (Functor io, MonadIO io, ParseRecord (f Wrapped), Unwrappable f) => Text -> io (f Unwrapped) Source #
Marshal any value that implements ParseRecord
from the command line
and unwrap its fields
:: (MonadIO io, ParseRecord (f Wrapped), Unwrappable f) | |
=> Text | Program description |
-> io (f Unwrapped, io ()) | (options, io action to print help message) |
Marshal any value that implements ParseRecord
from the command line
and unwrap its fields alongside an io action to print the help message
:: (ParseRecord (f Wrapped), Unwrappable f) | |
=> [Text] | Command-line arguments |
-> Maybe (f Unwrapped) |
Pure version of unwrapRecord
class ParseRecord a where Source #
A class for types that can be parsed from the command line
This class has a default implementation for any type that implements
Generic
and you can derive Generic
for many types by enabling the
DeriveGeneric
language extension
You can also use getOnly
to create a ParseRecord
instance from a
ParseFields
instance:
instance ParseRecord MyType where parseRecord = fmap getOnly parseRecord
parseRecord :: Parser a Source #
parseRecord :: (Generic a, GenericParseRecord (Rep a)) => Parser a Source #
class ParseRecord a => ParseFields a where Source #
A class for all types that can be parsed from zero or more arguments/options on the command line
parseFields
has a default implementation for any type that implements
ParseField
class ParseField a where Source #
A class for all record fields that can be parsed from exactly one option or argument on the command line
parseField
has a default implementation for any type that implements
Read
and Typeable
. You can derive Read
for many types and you can
derive Typeable
for any type if you enable the DeriveDataTypeable
language extension
The only reason for this method is to provide a special case for
handling String
s. All other instances should just fall back on the
default implementation for parseListOfField
readField :: Read a => ReadM a Source #
The 1-tuple type or single-value "collection".
This type is structurally equivalent to the
Identity
type, but its intent is more
about serving as the anonymous 1-tuple type missing from Haskell for attaching
typeclass instances.
Parameter usage example:
encodeSomething (Only
(42::Int))
Result usage example:
xs <- decodeSomething
forM_ xs $ \(Only
id) -> {- ... -}
getOnly :: Only a -> a Source #
This is a convenience function that you can use if you want to create a
ParseRecord
instance that just defers to the ParseFields
instance for
the same type:
instance ParseRecord MyType where parseRecord = fmap getOnly parseRecord
Options for customizing derived ParseRecord
implementations for Generic
types
You can either create the Modifiers
record directly:
modifiers :: Modifiers modifiers = Modifiers { fieldNameModifier = ... , constructorNameModifier = ... , shortNameModifier = ... }
... or you can tweak the defaultModifiers
:
modifiers :: Modifiers modifiers = defaultModifiers { fieldNameModifier = ... }
... or you can use/tweak a predefined Modifier
, like lispCaseModifiers
The parseRecordWithModifiers
function uses this Modifiers
record when
generating a Generic
implementation of ParseRecord
Modifiers | |
|
parseRecordWithModifiers :: (Generic a, GenericParseRecord (Rep a)) => Modifiers -> Parser a Source #
Use parseRecordWithModifiers
when you want to tweak the behavior of a
derived ParseRecord
implementation, like this:
myModifiers :: Modifiers myModifiers = defaultModifiers { constructorNameModifier = id } instance ParseRecord MyType where parseRecord = parseRecordWithModifiers myModifiers
This will still require that you derive Generic
for your type to automate
most of the implementation, but the Modifiers
that you pass will change
how the implementation generates the command line interface
defaultModifiers :: Modifiers Source #
These are the default modifiers used if you derive a Generic
implementation. You can customize this and pass the result to
parseRecordWithModifiers
if you would like to modify the derived
implementation:
myModifiers :: Modifiers myModifiers = defaultModifiers { constructorNameModifier = id } instance ParseRecord MyType where parseRecord = parseRecordWithModifiers myModifiers
lispCaseModifiers :: Modifiers Source #
Convert field and constructor names from CamelCase
to lisp-case
.
Leading underscores are dropped, allowing one to use option names which are Haskell keywords or otherwise conflicting identifiers.
BuildCommand -> build-command someFlag -> --some-flag _type -> --type _splitAt -> --split-at
firstLetter :: String -> Maybe Char Source #
Use this for the shortNameModifier
field of the Modifiers
record if
you want to use the first letter of each option as the short name
Help
newtype (field :: *) <?> (help :: Symbol) Source #
Use this to annotate a field with a type-level string (i.e. a Symbol
)
representing the help description for that field:
data Example = Example { foo :: Int <?> "Documentation for the foo flag" , bar :: Double <?> "Documentation for the bar flag" } deriving (Generic, Show)
Show field => Show ((<?>) field help) Source # | |
Generic ((<?>) field help) Source # | |
(ParseFields a, KnownSymbol h) => ParseRecord ((<?>) a h) Source # | |
(ParseFields a, KnownSymbol h) => ParseFields ((<?>) a h) Source # | |
(ParseField a, KnownSymbol h) => ParseField ((<?>) a h) Source # | |
type Unwrapped ::: ((<?>) field helper) Source # | |
type Rep ((<?>) field help) Source # | |
Flag to unwrap fields annotated using '(?)'
type Unwrappable f = (Generic (f Wrapped), Generic (f Unwrapped), GenericUnwrappable (Rep (f Wrapped)) (Rep (f Unwrapped))) Source #
Constraint for types whose fields can be unwrapped
Re-exports
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
A space efficient, packed, unboxed Unicode text type.
Boolean monoid under conjunction (&&
).
Boolean monoid under disjunction (||
).
Maybe monoid returning the leftmost non-Nothing value.
is isomorphic to First
a
, but precedes it
historically.Alt
Maybe
a
Monad First | |
Functor First | |
Applicative First | |
Foldable First | Since: 4.8.0.0 |
Eq a => Eq (First a) | |
Ord a => Ord (First a) | |
Read a => Read (First a) | |
Show a => Show (First a) | |
Generic (First a) | |
Semigroup (First a) | Since: 4.9.0.0 |
Monoid (First a) | Since: 2.1 |
ParseField a => ParseRecord (First a) Source # | |
ParseField a => ParseFields (First a) Source # | |
Generic1 * First | |
type Rep (First a) | |
type Rep1 * First | |
Maybe monoid returning the rightmost non-Nothing value.
is isomorphic to Last
a
, and thus to
Dual
(First
a)Dual
(Alt
Maybe
a)
Monad Last | |
Functor Last | |
Applicative Last | |
Foldable Last | Since: 4.8.0.0 |
Eq a => Eq (Last a) | |
Ord a => Ord (Last a) | |
Read a => Read (Last a) | |
Show a => Show (Last a) | |
Generic (Last a) | |
Semigroup (Last a) | Since: 4.9.0.0 |
Monoid (Last a) | Since: 2.1 |
ParseField a => ParseRecord (Last a) Source # | |
ParseField a => ParseFields (Last a) Source # | |
Generic1 * Last | |
type Rep (Last a) | |
type Rep1 * Last | |
Monoid under addition.
Monad Sum | Since: 4.8.0.0 |
Functor Sum | Since: 4.8.0.0 |
Applicative Sum | Since: 4.8.0.0 |
Foldable Sum | Since: 4.8.0.0 |
Bounded a => Bounded (Sum a) | |
Eq a => Eq (Sum a) | |
Num a => Num (Sum a) | |
Ord a => Ord (Sum a) | |
Read a => Read (Sum a) | |
Show a => Show (Sum a) | |
Generic (Sum a) | |
Num a => Semigroup (Sum a) | Since: 4.9.0.0 |
Num a => Monoid (Sum a) | Since: 2.1 |
(Num a, ParseField a) => ParseRecord (Sum a) Source # | |
(Num a, ParseField a) => ParseFields (Sum a) Source # | |
Generic1 * Sum | |
type Rep (Sum a) | |
type Rep1 * Sum | |
Monoid under multiplication.
Product | |
|
Monad Product | Since: 4.8.0.0 |
Functor Product | Since: 4.8.0.0 |
Applicative Product | Since: 4.8.0.0 |
Foldable Product | Since: 4.8.0.0 |
Bounded a => Bounded (Product a) | |
Eq a => Eq (Product a) | |
Num a => Num (Product a) | |
Ord a => Ord (Product a) | |
Read a => Read (Product a) | |
Show a => Show (Product a) | |
Generic (Product a) | |
Num a => Semigroup (Product a) | Since: 4.9.0.0 |
Num a => Monoid (Product a) | Since: 2.1 |
(Num a, ParseField a) => ParseRecord (Product a) Source # | |
(Num a, ParseField a) => ParseFields (Product a) Source # | |
Generic1 * Product | |
type Rep (Product a) | |
type Rep1 * Product | |