| Safe Haskell | Safe |
|---|---|
| Language | Haskell98 |
Options.Generic
Contents
Description
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}}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
Maybes 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’- getRecord :: (MonadIO io, ParseRecord a) => Text -> io a
- class ParseRecord a where
- parseRecord :: Parser a
- class ParseRecord a => ParseFields a where
- class ParseField a where
- newtype Only a = Only a
- getOnly :: Only a -> a
- newtype field <?> help = Helpful {
- unHelpful :: field
- 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
Arguments
| :: (MonadIO io, ParseRecord a) | |
| => Text | Program description |
| -> io a |
Marshal any value that implements ParseRecord from the command line
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 parseRecordMinimal complete definition
Nothing
Methods
parseRecord :: Parser a Source
Instances
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
Minimal complete definition
Nothing
Instances
| ParseFields Bool Source | |
| ParseFields Char Source | |
| ParseFields Double Source | |
| ParseFields Float Source | |
| ParseFields Int Source | |
| ParseFields Integer Source | |
| ParseFields Ordering Source | |
| ParseFields () Source | |
| ParseFields Void Source | |
| ParseFields All Source | |
| ParseFields Any Source | |
| ParseFields ByteString Source | |
| ParseFields ByteString Source | |
| ParseFields Text Source | |
| ParseFields FilePath Source | |
| ParseFields Text Source | |
| ParseFields Day Source | |
| ParseField a => ParseFields [a] Source | |
| (Num a, ParseField a) => ParseFields (Sum a) Source | |
| (Num a, ParseField a) => ParseFields (Product a) Source | |
| ParseField a => ParseFields (First a) Source | |
| ParseField a => ParseFields (Last a) Source | |
| ParseField a => ParseFields (Maybe a) Source | |
| (ParseFields a, KnownSymbol h) => ParseFields ((<?>) a h) Source |
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
Minimal complete definition
Nothing
Methods
The only reason for this method is to provide a special case for
handling Strings. All other instances should just fall back on the
default implementation for parseListOfField
Instances
A 1-tuple, used solely to translate ParseFields instances into
ParseRecord instances
Constructors
| Only a |
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 parseRecordHelp
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)Instances
| 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 Rep ((<?>) field help) Source |
Re-exports
class Generic a
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
Instances
| Generic Bool | |
| Generic Char | |
| Generic Double | |
| Generic Float | |
| Generic Int | |
| Generic Ordering | |
| Generic () | |
| Generic Void | |
| Generic All | |
| Generic Any | |
| Generic Arity | |
| Generic Fixity | |
| Generic Associativity | |
| Generic [a] | |
| Generic (U1 p) | |
| Generic (Par1 p) | |
| Generic (Identity a) | |
| Generic (ZipList a) | |
| Generic (Dual a) | |
| Generic (Endo a) | |
| Generic (Sum a) | |
| Generic (Product a) | |
| Generic (First a) | |
| Generic (Last a) | |
| Generic (Maybe a) | |
| Generic (Only a) | |
| Generic (Either a b) | |
| Generic (Rec1 f p) | |
| Generic (a, b) | |
| Generic (Const a b) | |
| Generic (WrappedMonad m a) | |
| Generic (Proxy * t) | |
| Generic ((<?>) field help) | |
| Generic (K1 i c p) | |
| Generic ((:+:) f g p) | |
| Generic ((:*:) f g p) | |
| Generic ((:.:) f g p) | |
| Generic (a, b, c) | |
| Generic (WrappedArrow a b c) | |
| Generic (Alt k f a) | |
| Generic (M1 i c f p) | |
| Generic (a, b, c, d) | |
| Generic (a, b, c, d, e) | |
| Generic (a, b, c, d, e, f) | |
| Generic (a, b, c, d, e, f, g) |
newtype First a :: * -> *
Maybe monoid returning the leftmost non-Nothing value.
is isomorphic to First a, but precedes it
historically.Alt Maybe a
Instances
| Monad First | |
| Functor First | |
| Applicative First | |
| Generic1 First | |
| Eq a => Eq (First a) | |
| Ord a => Ord (First a) | |
| Read a => Read (First a) | |
| Show a => Show (First a) | |
| Generic (First a) | |
| Monoid (First a) | |
| ParseField a => ParseRecord (First a) Source | |
| ParseField a => ParseFields (First a) Source | |
| type Rep1 First = D1 D1First (C1 C1_0First (S1 S1_0_0First (Rec1 Maybe))) | |
| type Rep (First a) = D1 D1First (C1 C1_0First (S1 S1_0_0First (Rec0 (Maybe a)))) |
newtype Last a :: * -> *
Maybe monoid returning the rightmost non-Nothing value.
is isomorphic to Last a, and thus to
Dual (First a)Dual (Alt Maybe a)
Instances
| Monad Last | |
| Functor Last | |
| Applicative Last | |
| Generic1 Last | |
| Eq a => Eq (Last a) | |
| Ord a => Ord (Last a) | |
| Read a => Read (Last a) | |
| Show a => Show (Last a) | |
| Generic (Last a) | |
| Monoid (Last a) | |
| ParseField a => ParseRecord (Last a) Source | |
| ParseField a => ParseFields (Last a) Source | |
| type Rep1 Last = D1 D1Last (C1 C1_0Last (S1 S1_0_0Last (Rec1 Maybe))) | |
| type Rep (Last a) = D1 D1Last (C1 C1_0Last (S1 S1_0_0Last (Rec0 (Maybe a)))) |
newtype Sum a :: * -> *
Monoid under addition.
Instances
| Generic1 Sum | |
| 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 => Monoid (Sum a) | |
| (Num a, ParseField a) => ParseRecord (Sum a) Source | |
| (Num a, ParseField a) => ParseFields (Sum a) Source | |
| type Rep1 Sum = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum Par1)) | |
| type Rep (Sum a) = D1 D1Sum (C1 C1_0Sum (S1 S1_0_0Sum (Rec0 a))) |
newtype Product a :: * -> *
Monoid under multiplication.
Constructors
| Product | |
Fields
| |
Instances
| Generic1 Product | |
| 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 => Monoid (Product a) | |
| (Num a, ParseField a) => ParseRecord (Product a) Source | |
| (Num a, ParseField a) => ParseFields (Product a) Source | |
| type Rep1 Product = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product Par1)) | |
| type Rep (Product a) = D1 D1Product (C1 C1_0Product (S1 S1_0_0Product (Rec0 a))) |