optparse-generic-1.4.4: Auto-generate a command-line parser for your datatype

Safe HaskellSafe
LanguageHaskell2010

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}}

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}

You can also add default values to each Readable field, like this:

{-# LANGUAGE DataKinds         #-}
{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators     #-}

import Options.Generic

data Example = Example
    { foo :: Int    <!> "1"
    , bar :: String <!> "hello"
    } deriving (Generic, Show)

instance ParseRecord Example

main = do
    x <- getRecord "Test program"
    print (x :: Example)

Default values will work alongside help descriptions and unwrapping.

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 lists

    data 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)
Synopsis

Parsers

getRecord Source #

Arguments

:: (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.

getRecordWith Source #

Arguments

:: (MonadIO io, ParseRecord a) 
=> InfoMod a

ParserInfo modifiers

-> PrefsMod

ParserPrefs modifiers

-> io a 

Marshal any value that implements ParseRecord from the command line

This is the lower-level sibling of 'getRecord and lets you modify the ParserInfo and ParserPrefs records.

getWithHelp Source #

Arguments

:: (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.

getRecordPure Source #

Arguments

:: 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

getRecordPureWith Source #

Arguments

:: ParseRecord a 
=> [Text]

Command-line arguments

-> InfoMod a

ParserInfo modifiers

-> PrefsMod

ParserPrefs modifiers

-> Maybe a 

Pure version of getRecordWith

Like getRecordWith, this is a sibling of 'getRecordPure and exposes the monoidal modifier structures for ParserInfo and ParserPrefs to you.

>>> :set -XOverloadedStrings
>>> getRecordPureWith ["1"] mempty mempty :: Maybe Int
Just 1
>>> getRecordPureWith ["1", "2"] mempty mempty :: Maybe [Int]
Just [1,2]
>>> getRecordPureWith ["Foo"] mempty mempty :: 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

unwrapWithHelp Source #

Arguments

:: (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

unwrapRecordPure Source #

Arguments

:: (ParseRecord (f Wrapped), Unwrappable f) 
=> [Text]

Command-line arguments

-> Maybe (f Unwrapped) 

Pure version of unwrapRecord

unwrap :: forall f. Unwrappable f => f Wrapped -> f Unwrapped Source #

Unwrap the fields of a constructor

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

Minimal complete definition

Nothing

Instances
ParseRecord Bool Source # 
Instance details

Defined in Options.Generic

ParseRecord Char Source # 
Instance details

Defined in Options.Generic

ParseRecord Double Source # 
Instance details

Defined in Options.Generic

ParseRecord Float Source # 
Instance details

Defined in Options.Generic

ParseRecord Int Source # 
Instance details

Defined in Options.Generic

ParseRecord Int8 Source # 
Instance details

Defined in Options.Generic

ParseRecord Int16 Source # 
Instance details

Defined in Options.Generic

ParseRecord Int32 Source # 
Instance details

Defined in Options.Generic

ParseRecord Int64 Source # 
Instance details

Defined in Options.Generic

ParseRecord Integer Source # 
Instance details

Defined in Options.Generic

ParseRecord Natural Source # 
Instance details

Defined in Options.Generic

ParseRecord Ordering Source # 
Instance details

Defined in Options.Generic

ParseRecord Word8 Source # 
Instance details

Defined in Options.Generic

ParseRecord Word16 Source # 
Instance details

Defined in Options.Generic

ParseRecord Word32 Source # 
Instance details

Defined in Options.Generic

ParseRecord Word64 Source # 
Instance details

Defined in Options.Generic

ParseRecord () Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser () Source #

ParseRecord Void Source # 
Instance details

Defined in Options.Generic

ParseRecord All Source # 
Instance details

Defined in Options.Generic

ParseRecord Any Source # 
Instance details

Defined in Options.Generic

ParseRecord ByteString Source # 
Instance details

Defined in Options.Generic

ParseRecord ByteString Source # 
Instance details

Defined in Options.Generic

ParseRecord Text Source # 
Instance details

Defined in Options.Generic

ParseRecord FilePath Source # 
Instance details

Defined in Options.Generic

ParseRecord Text Source # 
Instance details

Defined in Options.Generic

ParseRecord Day Source # 
Instance details

Defined in Options.Generic

ParseField a => ParseRecord [a] Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser [a] Source #

ParseField a => ParseRecord (Maybe a) Source # 
Instance details

Defined in Options.Generic

ParseFields a => ParseRecord (Only a) Source # 
Instance details

Defined in Options.Generic

ParseField a => ParseRecord (First a) Source # 
Instance details

Defined in Options.Generic

ParseField a => ParseRecord (Last a) Source # 
Instance details

Defined in Options.Generic

(Num a, ParseField a) => ParseRecord (Sum a) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (Sum a) Source #

(Num a, ParseField a) => ParseRecord (Product a) Source # 
Instance details

Defined in Options.Generic

ParseField a => ParseRecord (NonEmpty a) Source # 
Instance details

Defined in Options.Generic

(ParseFields a, ParseFields b) => ParseRecord (Either a b) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (Either a b) Source #

(ParseFields a, ParseFields b) => ParseRecord (a, b) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (a, b) Source #

(ParseFields a, KnownSymbol h) => ParseRecord (a <!> h) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (a <!> h) Source #

(ParseFields a, KnownSymbol h) => ParseRecord (a <?> h) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (a <?> h) Source #

(ParseFields a, ParseFields b, ParseFields c) => ParseRecord (a, b, c) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (a, b, c) Source #

(ParseFields a, ParseFields b, ParseFields c, ParseFields d) => ParseRecord (a, b, c, d) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (a, b, c, d) Source #

(ParseFields a, ParseFields b, ParseFields c, ParseFields d, ParseFields e) => ParseRecord (a, b, c, d, e) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (a, b, c, d, e) Source #

(ParseFields a, ParseFields b, ParseFields c, ParseFields d, ParseFields e, ParseFields f) => ParseRecord (a, b, c, d, e, f) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (a, b, c, d, e, f) Source #

(ParseFields a, ParseFields b, ParseFields c, ParseFields d, ParseFields e, ParseFields f, ParseFields g) => ParseRecord (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (a, b, c, d, e, f, g) 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

Minimal complete definition

Nothing

Methods

parseFields Source #

Arguments

:: Maybe Text

Help message

-> Maybe Text

Field label

-> Maybe Char

Short name

-> Maybe String

Default value

-> Parser a 

parseFields Source #

Arguments

:: ParseField a 
=> Maybe Text

Help message

-> Maybe Text

Field label

-> Maybe Char

Short name

-> Maybe String

Default value

-> Parser a 
Instances
ParseFields Bool Source # 
Instance details

Defined in Options.Generic

ParseFields Char Source # 
Instance details

Defined in Options.Generic

ParseFields Double Source # 
Instance details

Defined in Options.Generic

ParseFields Float Source # 
Instance details

Defined in Options.Generic

ParseFields Int Source # 
Instance details

Defined in Options.Generic

ParseFields Int8 Source # 
Instance details

Defined in Options.Generic

ParseFields Int16 Source # 
Instance details

Defined in Options.Generic

ParseFields Int32 Source # 
Instance details

Defined in Options.Generic

ParseFields Int64 Source # 
Instance details

Defined in Options.Generic

ParseFields Integer Source # 
Instance details

Defined in Options.Generic

ParseFields Natural Source # 
Instance details

Defined in Options.Generic

ParseFields Ordering Source # 
Instance details

Defined in Options.Generic

ParseFields Word8 Source # 
Instance details

Defined in Options.Generic

ParseFields Word16 Source # 
Instance details

Defined in Options.Generic

ParseFields Word32 Source # 
Instance details

Defined in Options.Generic

ParseFields Word64 Source # 
Instance details

Defined in Options.Generic

ParseFields () Source # 
Instance details

Defined in Options.Generic

ParseFields Void Source # 
Instance details

Defined in Options.Generic

ParseFields All Source # 
Instance details

Defined in Options.Generic

ParseFields Any Source # 
Instance details

Defined in Options.Generic

ParseFields ByteString Source # 
Instance details

Defined in Options.Generic

ParseFields ByteString Source # 
Instance details

Defined in Options.Generic

ParseFields Text Source # 
Instance details

Defined in Options.Generic

ParseFields FilePath Source # 
Instance details

Defined in Options.Generic

ParseFields Text Source # 
Instance details

Defined in Options.Generic

ParseFields Day Source # 
Instance details

Defined in Options.Generic

ParseField a => ParseFields [a] Source # 
Instance details

Defined in Options.Generic

ParseField a => ParseFields (Maybe a) Source # 
Instance details

Defined in Options.Generic

ParseField a => ParseFields (First a) Source # 
Instance details

Defined in Options.Generic

ParseField a => ParseFields (Last a) Source # 
Instance details

Defined in Options.Generic

(Num a, ParseField a) => ParseFields (Sum a) Source # 
Instance details

Defined in Options.Generic

(Num a, ParseField a) => ParseFields (Product a) Source # 
Instance details

Defined in Options.Generic

ParseField a => ParseFields (NonEmpty a) Source # 
Instance details

Defined in Options.Generic

(ParseFields a, KnownSymbol d) => ParseFields (a <!> d) Source # 
Instance details

Defined in Options.Generic

(ParseFields a, KnownSymbol h) => ParseFields (a <?> h) Source # 
Instance details

Defined in Options.Generic

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

parseField Source #

Arguments

:: Maybe Text

Help message

-> Maybe Text

Field label

-> Maybe Char

Short name

-> Maybe String

Default value

-> Parser a 

parseField Source #

Arguments

:: Read a 
=> Maybe Text

Help message

-> Maybe Text

Field label

-> Maybe Char

Short name

-> Maybe String

Default value

-> Parser a 

parseListOfField Source #

Arguments

:: Maybe Text

Help message

-> Maybe Text

Field label

-> Maybe Char

Short name

-> Maybe String

Default value

-> Parser [a] 

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

readField :: ReadM a Source #

readField :: Read a => ReadM a Source #

metavar :: proxy a -> String Source #

metavar :: Typeable a => proxy a -> String Source #

Instances
ParseField Bool Source # 
Instance details

Defined in Options.Generic

ParseField Char Source # 
Instance details

Defined in Options.Generic

ParseField Double Source # 
Instance details

Defined in Options.Generic

ParseField Float Source # 
Instance details

Defined in Options.Generic

ParseField Int Source # 
Instance details

Defined in Options.Generic

ParseField Int8 Source # 
Instance details

Defined in Options.Generic

ParseField Int16 Source # 
Instance details

Defined in Options.Generic

ParseField Int32 Source # 
Instance details

Defined in Options.Generic

ParseField Int64 Source # 
Instance details

Defined in Options.Generic

ParseField Integer Source # 
Instance details

Defined in Options.Generic

ParseField Natural Source # 
Instance details

Defined in Options.Generic

ParseField Ordering Source # 
Instance details

Defined in Options.Generic

ParseField Word8 Source # 
Instance details

Defined in Options.Generic

ParseField Word16 Source # 
Instance details

Defined in Options.Generic

ParseField Word32 Source # 
Instance details

Defined in Options.Generic

ParseField Word64 Source # 
Instance details

Defined in Options.Generic

ParseField () Source # 
Instance details

Defined in Options.Generic

ParseField String Source # 
Instance details

Defined in Options.Generic

ParseField Void Source # 
Instance details

Defined in Options.Generic

ParseField All Source # 
Instance details

Defined in Options.Generic

ParseField Any Source # 
Instance details

Defined in Options.Generic

ParseField ByteString Source # 
Instance details

Defined in Options.Generic

ParseField ByteString Source # 
Instance details

Defined in Options.Generic

ParseField Text Source # 
Instance details

Defined in Options.Generic

ParseField FilePath Source # 
Instance details

Defined in Options.Generic

ParseField Text Source # 
Instance details

Defined in Options.Generic

ParseField Day Source # 
Instance details

Defined in Options.Generic

(ParseField a, KnownSymbol d) => ParseField (a <!> d) Source # 
Instance details

Defined in Options.Generic

(ParseField a, KnownSymbol h) => ParseField (a <?> h) Source # 
Instance details

Defined in Options.Generic

newtype Only a #

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) -> {- ... -}

Constructors

Only 

Fields

Instances
Functor Only 
Instance details

Defined in Data.Tuple.Only

Methods

fmap :: (a -> b) -> Only a -> Only b #

(<$) :: a -> Only b -> Only a #

Eq a => Eq (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

(==) :: Only a -> Only a -> Bool #

(/=) :: Only a -> Only a -> Bool #

Data a => Data (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Only a -> c (Only a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Only a) #

toConstr :: Only a -> Constr #

dataTypeOf :: Only a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Only a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Only a)) #

gmapT :: (forall b. Data b => b -> b) -> Only a -> Only a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Only a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Only a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

Ord a => Ord (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

compare :: Only a -> Only a -> Ordering #

(<) :: Only a -> Only a -> Bool #

(<=) :: Only a -> Only a -> Bool #

(>) :: Only a -> Only a -> Bool #

(>=) :: Only a -> Only a -> Bool #

max :: Only a -> Only a -> Only a #

min :: Only a -> Only a -> Only a #

Read a => Read (Only a) 
Instance details

Defined in Data.Tuple.Only

Show a => Show (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

showsPrec :: Int -> Only a -> ShowS #

show :: Only a -> String #

showList :: [Only a] -> ShowS #

Generic (Only a) 
Instance details

Defined in Data.Tuple.Only

Associated Types

type Rep (Only a) :: Type -> Type #

Methods

from :: Only a -> Rep (Only a) x #

to :: Rep (Only a) x -> Only a #

NFData a => NFData (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

rnf :: Only a -> () #

ParseFields a => ParseRecord (Only a) Source # 
Instance details

Defined in Options.Generic

type Rep (Only a) 
Instance details

Defined in Data.Tuple.Only

type Rep (Only a) = D1 (MetaData "Only" "Data.Tuple.Only" "Only-0.1-4eYnxvcrr7tEbYgCvIkHLb" True) (C1 (MetaCons "Only" PrefixI True) (S1 (MetaSel (Just "fromOnly") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

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

data Modifiers Source #

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

Constructors

Modifiers 

Fields

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

class GenericParseRecord f where Source #

Instances
GenericParseRecord (V1 :: Type -> Type) Source # 
Instance details

Defined in Options.Generic

GenericParseRecord (U1 :: Type -> Type) Source # 
Instance details

Defined in Options.Generic

(Constructor c1, Constructor c2, GenericParseRecord f1, GenericParseRecord f2) => GenericParseRecord (M1 C c1 f1 :+: M1 C c2 f2) Source # 
Instance details

Defined in Options.Generic

Methods

genericParseRecord :: Modifiers -> Parser ((M1 C c1 f1 :+: M1 C c2 f2) p) Source #

(Constructor c, GenericParseRecord f, GenericParseRecord (g :+: h)) => GenericParseRecord (M1 C c f :+: (g :+: h)) Source # 
Instance details

Defined in Options.Generic

Methods

genericParseRecord :: Modifiers -> Parser ((M1 C c f :+: (g :+: h)) p) Source #

(Constructor c, GenericParseRecord (f :+: g), GenericParseRecord h) => GenericParseRecord ((f :+: g) :+: M1 C c h) Source # 
Instance details

Defined in Options.Generic

Methods

genericParseRecord :: Modifiers -> Parser (((f :+: g) :+: M1 C c h) p) Source #

(GenericParseRecord (f :+: g), GenericParseRecord (h :+: i)) => GenericParseRecord ((f :+: g) :+: (h :+: i)) Source # 
Instance details

Defined in Options.Generic

Methods

genericParseRecord :: Modifiers -> Parser (((f :+: g) :+: (h :+: i)) p) Source #

(GenericParseRecord f, GenericParseRecord g) => GenericParseRecord (f :*: g) Source # 
Instance details

Defined in Options.Generic

GenericParseRecord f => GenericParseRecord (M1 D c f) Source # 
Instance details

Defined in Options.Generic

GenericParseRecord f => GenericParseRecord (M1 C c f) Source # 
Instance details

Defined in Options.Generic

(Selector s, ParseFields a) => GenericParseRecord (M1 S s (K1 i a :: Type -> Type)) Source # 
Instance details

Defined in Options.Generic

Methods

genericParseRecord :: Modifiers -> Parser (M1 S s (K1 i a) p) Source #

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)

Constructors

Helpful 

Fields

Instances
Show field => Show (field <?> help) Source # 
Instance details

Defined in Options.Generic

Methods

showsPrec :: Int -> (field <?> help) -> ShowS #

show :: (field <?> help) -> String #

showList :: [field <?> help] -> ShowS #

Generic (field <?> help) Source # 
Instance details

Defined in Options.Generic

Associated Types

type Rep (field <?> help) :: Type -> Type #

Methods

from :: (field <?> help) -> Rep (field <?> help) x #

to :: Rep (field <?> help) x -> field <?> help #

(ParseFields a, KnownSymbol h) => ParseRecord (a <?> h) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (a <?> h) Source #

(ParseFields a, KnownSymbol h) => ParseFields (a <?> h) Source # 
Instance details

Defined in Options.Generic

(ParseField a, KnownSymbol h) => ParseField (a <?> h) Source # 
Instance details

Defined in Options.Generic

type Rep (field <?> help) Source # 
Instance details

Defined in Options.Generic

type Rep (field <?> help) = D1 (MetaData "<?>" "Options.Generic" "optparse-generic-1.4.4-JmVeTk7RnnZBhKhyktYf0d" True) (C1 (MetaCons "Helpful" PrefixI True) (S1 (MetaSel (Just "unHelpful") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 field)))

newtype (field :: *) <!> (value :: Symbol) Source #

Use this to annotate a field with a type-level string (i.e. a Symbol) representing the default value for that field:

data Example = Example
    { foo :: Int    <!> "1"
    , bar :: Double <!> "0.5"
    } deriving (Generic, Show)

Constructors

DefValue 

Fields

Instances
Show field => Show (field <!> value) Source # 
Instance details

Defined in Options.Generic

Methods

showsPrec :: Int -> (field <!> value) -> ShowS #

show :: (field <!> value) -> String #

showList :: [field <!> value] -> ShowS #

Generic (field <!> value) Source # 
Instance details

Defined in Options.Generic

Associated Types

type Rep (field <!> value) :: Type -> Type #

Methods

from :: (field <!> value) -> Rep (field <!> value) x #

to :: Rep (field <!> value) x -> field <!> value #

(ParseFields a, KnownSymbol h) => ParseRecord (a <!> h) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (a <!> h) Source #

(ParseFields a, KnownSymbol d) => ParseFields (a <!> d) Source # 
Instance details

Defined in Options.Generic

(ParseField a, KnownSymbol d) => ParseField (a <!> d) Source # 
Instance details

Defined in Options.Generic

type Rep (field <!> value) Source # 
Instance details

Defined in Options.Generic

type Rep (field <!> value) = D1 (MetaData "<!>" "Options.Generic" "optparse-generic-1.4.4-JmVeTk7RnnZBhKhyktYf0d" True) (C1 (MetaCons "DefValue" PrefixI True) (S1 (MetaSel (Just "unDefValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 field)))

type family wrap ::: wrapped infixr 0 Source #

A type family to extract fields wrapped using '(?)'

Instances
type Unwrapped ::: wrapped Source # 
Instance details

Defined in Options.Generic

type Unwrapped ::: wrapped
type Wrapped ::: wrapped Source # 
Instance details

Defined in Options.Generic

type Wrapped ::: wrapped = wrapped

data Wrapped Source #

Flag to keep fields wrapped

Instances
type Wrapped ::: wrapped Source # 
Instance details

Defined in Options.Generic

type Wrapped ::: wrapped = wrapped

data Unwrapped Source #

Flag to unwrap fields annotated using '(?)'

Instances
type Unwrapped ::: wrapped Source # 
Instance details

Defined in Options.Generic

type Unwrapped ::: wrapped

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

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

A Generic instance must satisfy the following laws:

from . toid
to . fromid

Minimal complete definition

from, to

Instances
Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic () 
Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: Type -> Type #

Methods

from :: () -> Rep () x #

to :: Rep () x -> () #

Generic Void 
Instance details

Defined in Data.Void

Associated Types

type Rep Void :: Type -> Type #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic Version 
Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Fixity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type #

Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic [a] 
Instance details

Defined in GHC.Generics

Associated Types

type Rep [a] :: Type -> Type #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Maybe a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Generic (Par1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Par1 p) :: Type -> Type #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (Only a) 
Instance details

Defined in Data.Tuple.Only

Associated Types

type Rep (Only a) :: Type -> Type #

Methods

from :: Only a -> Rep (Only a) x #

to :: Rep (Only a) x -> Only a #

Generic (Complex a) 
Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a) :: Type -> Type #

Methods

from :: Complex a -> Rep (Complex a) x #

to :: Rep (Complex a) x -> Complex a #

Generic (Min a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Min a) :: Type -> Type #

Methods

from :: Min a -> Rep (Min a) x #

to :: Rep (Min a) x -> Min a #

Generic (Max a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Max a) :: Type -> Type #

Methods

from :: Max a -> Rep (Max a) x #

to :: Rep (Max a) x -> Max a #

Generic (First a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (First a) :: Type -> Type #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Last a) :: Type -> Type #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (WrappedMonoid m) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m) :: Type -> Type #

Generic (Option a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Option a) :: Type -> Type #

Methods

from :: Option a -> Rep (Option a) x #

to :: Rep (Option a) x -> Option a #

Generic (ZipList a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (ZipList a) :: Type -> Type #

Methods

from :: ZipList a -> Rep (ZipList a) x #

to :: Rep (ZipList a) x -> ZipList a #

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) :: Type -> Type #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Generic (First a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a) :: Type -> Type #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Last a) :: Type -> Type #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a) :: Type -> Type #

Methods

from :: Dual a -> Rep (Dual a) x #

to :: Rep (Dual a) x -> Dual a #

Generic (Endo a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Endo a) :: Type -> Type #

Methods

from :: Endo a -> Rep (Endo a) x #

to :: Rep (Endo a) x -> Endo a #

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) :: Type -> Type #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) :: Type -> Type #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Generic (Down a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) :: Type -> Type #

Methods

from :: Down a -> Rep (Down a) x #

to :: Rep (Down a) x -> Down a #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Generic (Tree a) 
Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a) :: Type -> Type #

Methods

from :: Tree a -> Rep (Tree a) x #

to :: Rep (Tree a) x -> Tree a #

Generic (FingerTree a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (FingerTree a) :: Type -> Type #

Methods

from :: FingerTree a -> Rep (FingerTree a) x #

to :: Rep (FingerTree a) x -> FingerTree a #

Generic (Digit a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Digit a) :: Type -> Type #

Methods

from :: Digit a -> Rep (Digit a) x #

to :: Rep (Digit a) x -> Digit a #

Generic (Node a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Node a) :: Type -> Type #

Methods

from :: Node a -> Rep (Node a) x #

to :: Rep (Node a) x -> Node a #

Generic (Elem a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Elem a) :: Type -> Type #

Methods

from :: Elem a -> Rep (Elem a) x #

to :: Rep (Elem a) x -> Elem a #

Generic (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewL a) :: Type -> Type #

Methods

from :: ViewL a -> Rep (ViewL a) x #

to :: Rep (ViewL a) x -> ViewL a #

Generic (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewR a) :: Type -> Type #

Methods

from :: ViewR a -> Rep (ViewR a) x #

to :: Rep (ViewR a) x -> ViewR a #

Generic (Either a b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b) :: Type -> Type #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (V1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (V1 p) :: Type -> Type #

Methods

from :: V1 p -> Rep (V1 p) x #

to :: Rep (V1 p) x -> V1 p #

Generic (U1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p) :: Type -> Type #

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Generic (a, b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b) :: Type -> Type #

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (Arg a b) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b) :: Type -> Type #

Methods

from :: Arg a b -> Rep (Arg a b) x #

to :: Rep (Arg a b) x -> Arg a b #

Generic (WrappedMonad m a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedMonad m a) :: Type -> Type #

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a #

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Generic (field <!> value) Source # 
Instance details

Defined in Options.Generic

Associated Types

type Rep (field <!> value) :: Type -> Type #

Methods

from :: (field <!> value) -> Rep (field <!> value) x #

to :: Rep (field <!> value) x -> field <!> value #

Generic (field <?> help) Source # 
Instance details

Defined in Options.Generic

Associated Types

type Rep (field <?> help) :: Type -> Type #

Methods

from :: (field <?> help) -> Rep (field <?> help) x #

to :: Rep (field <?> help) x -> field <?> help #

Generic (Rec1 f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Rec1 f p) :: Type -> Type #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x #

to :: Rep (Rec1 f p) x -> Rec1 f p #

Generic (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

Generic (URec Char p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) :: Type -> Type #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

Generic (URec Double p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

Generic (URec Int p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) :: Type -> Type #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

Generic (URec Word p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Generic (a, b, c) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c) :: Type -> Type #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (WrappedArrow a b c) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedArrow a b c) :: Type -> Type #

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x #

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c #

Generic (Const a b) 
Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) :: Type -> Type #

Methods

from :: Const a b -> Rep (Const a b) x #

to :: Rep (Const a b) x -> Const a b #

Generic (Ap f a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) :: Type -> Type #

Methods

from :: Ap f a -> Rep (Ap f a) x #

to :: Rep (Ap f a) x -> Ap f a #

Generic (Alt f a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) :: Type -> Type #

Methods

from :: Alt f a -> Rep (Alt f a) x #

to :: Rep (Alt f a) x -> Alt f a #

Generic (K1 i c p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (K1 i c p) :: Type -> Type #

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic ((f :+: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) :: Type -> Type #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

Generic ((f :*: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) :: Type -> Type #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

Generic (a, b, c, d) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d) :: Type -> Type #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (Product f g a) 
Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a) :: Type -> Type #

Methods

from :: Product f g a -> Rep (Product f g a) x #

to :: Rep (Product f g a) x -> Product f g a #

Generic (Sum f g a) 
Instance details

Defined in Data.Functor.Sum

Associated Types

type Rep (Sum f g a) :: Type -> Type #

Methods

from :: Sum f g a -> Rep (Sum f g a) x #

to :: Rep (Sum f g a) x -> Sum f g a #

Generic (M1 i c f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p) :: Type -> Type #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Generic ((f :.: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :.: g) p) :: Type -> Type #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

Generic (a, b, c, d, e) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e) :: Type -> Type #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (Compose f g a) 
Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep (Compose f g a) :: Type -> Type #

Methods

from :: Compose f g a -> Rep (Compose f g a) x #

to :: Rep (Compose f g a) x -> Compose f g a #

Generic (a, b, c, d, e, f) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances
ParseRecord Text Source # 
Instance details

Defined in Options.Generic

ParseFields Text Source # 
Instance details

Defined in Options.Generic

ParseField Text Source # 
Instance details

Defined in Options.Generic

type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char

newtype All #

Boolean monoid under conjunction (&&).

>>> getAll (All True <> mempty <> All False)
False
>>> getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))
False

Constructors

All 

Fields

Instances
Bounded All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: All #

maxBound :: All #

Eq All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: All -> All -> Bool #

(/=) :: All -> All -> Bool #

Ord All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: All -> All -> Ordering #

(<) :: All -> All -> Bool #

(<=) :: All -> All -> Bool #

(>) :: All -> All -> Bool #

(>=) :: All -> All -> Bool #

max :: All -> All -> All #

min :: All -> All -> All #

Read All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Semigroup All

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: All -> All -> All #

sconcat :: NonEmpty All -> All #

stimes :: Integral b => b -> All -> All #

Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

ParseRecord All Source # 
Instance details

Defined in Options.Generic

ParseFields All Source # 
Instance details

Defined in Options.Generic

ParseField All Source # 
Instance details

Defined in Options.Generic

type Rep All

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep All = D1 (MetaData "All" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "All" PrefixI True) (S1 (MetaSel (Just "getAll") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

newtype Any #

Boolean monoid under disjunction (||).

>>> getAny (Any True <> mempty <> Any False)
True
>>> getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))
True

Constructors

Any 

Fields

Instances
Bounded Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: Any #

maxBound :: Any #

Eq Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Any -> Any -> Bool #

(/=) :: Any -> Any -> Bool #

Ord Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Any -> Any -> Ordering #

(<) :: Any -> Any -> Bool #

(<=) :: Any -> Any -> Bool #

(>) :: Any -> Any -> Bool #

(>=) :: Any -> Any -> Bool #

max :: Any -> Any -> Any #

min :: Any -> Any -> Any #

Read Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

Generic Any 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Semigroup Any

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Any -> Any -> Any #

sconcat :: NonEmpty Any -> Any #

stimes :: Integral b => b -> Any -> Any #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

ParseRecord Any Source # 
Instance details

Defined in Options.Generic

ParseFields Any Source # 
Instance details

Defined in Options.Generic

ParseField Any Source # 
Instance details

Defined in Options.Generic

type Rep Any

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep Any = D1 (MetaData "Any" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Any" PrefixI True) (S1 (MetaSel (Just "getAny") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

newtype First a #

Maybe monoid returning the leftmost non-Nothing value.

First a is isomorphic to Alt Maybe a, but precedes it historically.

>>> getFirst (First (Just "hello") <> First Nothing <> First (Just "world"))
Just "hello"

Use of this type is discouraged. Note the following equivalence:

Data.Monoid.First x === Maybe (Data.Semigroup.First x)

In addition to being equivalent in the structural sense, the two also have Monoid instances that behave the same. This type will be marked deprecated in GHC 8.8, and removed in GHC 8.10. Users are advised to use the variant from Data.Semigroup and wrap it in Maybe.

Constructors

First 

Fields

Instances
Monad First

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

(>>=) :: First a -> (a -> First b) -> First b #

(>>) :: First a -> First b -> First b #

return :: a -> First a #

fail :: String -> First a #

Functor First

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

fmap :: (a -> b) -> First a -> First b #

(<$) :: a -> First b -> First a #

Applicative First

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> First a #

(<*>) :: First (a -> b) -> First a -> First b #

liftA2 :: (a -> b -> c) -> First a -> First b -> First c #

(*>) :: First a -> First b -> First b #

(<*) :: First a -> First b -> First a #

Foldable First

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => First m -> m #

foldMap :: Monoid m => (a -> m) -> First a -> m #

foldr :: (a -> b -> b) -> b -> First a -> b #

foldr' :: (a -> b -> b) -> b -> First a -> b #

foldl :: (b -> a -> b) -> b -> First a -> b #

foldl' :: (b -> a -> b) -> b -> First a -> b #

foldr1 :: (a -> a -> a) -> First a -> a #

foldl1 :: (a -> a -> a) -> First a -> a #

toList :: First a -> [a] #

null :: First a -> Bool #

length :: First a -> Int #

elem :: Eq a => a -> First a -> Bool #

maximum :: Ord a => First a -> a #

minimum :: Ord a => First a -> a #

sum :: Num a => First a -> a #

product :: Num a => First a -> a #

Traversable First

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> First a -> f (First b) #

sequenceA :: Applicative f => First (f a) -> f (First a) #

mapM :: Monad m => (a -> m b) -> First a -> m (First b) #

sequence :: Monad m => First (m a) -> m (First a) #

Eq a => Eq (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

(==) :: First a -> First a -> Bool #

(/=) :: First a -> First a -> Bool #

Ord a => Ord (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

compare :: First a -> First a -> Ordering #

(<) :: First a -> First a -> Bool #

(<=) :: First a -> First a -> Bool #

(>) :: First a -> First a -> Bool #

(>=) :: First a -> First a -> Bool #

max :: First a -> First a -> First a #

min :: First a -> First a -> First a #

Read a => Read (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Show a => Show (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Generic (First a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a) :: Type -> Type #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Semigroup (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Monoid (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

ParseField a => ParseRecord (First a) Source # 
Instance details

Defined in Options.Generic

ParseField a => ParseFields (First a) Source # 
Instance details

Defined in Options.Generic

Generic1 First 
Instance details

Defined in Data.Monoid

Associated Types

type Rep1 First :: k -> Type #

Methods

from1 :: First a -> Rep1 First a #

to1 :: Rep1 First a -> First a #

type Rep (First a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

type Rep (First a) = D1 (MetaData "First" "Data.Monoid" "base" True) (C1 (MetaCons "First" PrefixI True) (S1 (MetaSel (Just "getFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))
type Rep1 First

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

type Rep1 First = D1 (MetaData "First" "Data.Monoid" "base" True) (C1 (MetaCons "First" PrefixI True) (S1 (MetaSel (Just "getFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Maybe)))

newtype Last a #

Maybe monoid returning the rightmost non-Nothing value.

Last a is isomorphic to Dual (First a), and thus to Dual (Alt Maybe a)

>>> getLast (Last (Just "hello") <> Last Nothing <> Last (Just "world"))
Just "world"

Use of this type is discouraged. Note the following equivalence:

Data.Monoid.Last x === Maybe (Data.Semigroup.Last x)

In addition to being equivalent in the structural sense, the two also have Monoid instances that behave the same. This type will be marked deprecated in GHC 8.8, and removed in GHC 8.10. Users are advised to use the variant from Data.Semigroup and wrap it in Maybe.

Constructors

Last 

Fields

Instances
Monad Last

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

(>>=) :: Last a -> (a -> Last b) -> Last b #

(>>) :: Last a -> Last b -> Last b #

return :: a -> Last a #

fail :: String -> Last a #

Functor Last

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

fmap :: (a -> b) -> Last a -> Last b #

(<$) :: a -> Last b -> Last a #

Applicative Last

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> Last a #

(<*>) :: Last (a -> b) -> Last a -> Last b #

liftA2 :: (a -> b -> c) -> Last a -> Last b -> Last c #

(*>) :: Last a -> Last b -> Last b #

(<*) :: Last a -> Last b -> Last a #

Foldable Last

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Last m -> m #

foldMap :: Monoid m => (a -> m) -> Last a -> m #

foldr :: (a -> b -> b) -> b -> Last a -> b #

foldr' :: (a -> b -> b) -> b -> Last a -> b #

foldl :: (b -> a -> b) -> b -> Last a -> b #

foldl' :: (b -> a -> b) -> b -> Last a -> b #

foldr1 :: (a -> a -> a) -> Last a -> a #

foldl1 :: (a -> a -> a) -> Last a -> a #

toList :: Last a -> [a] #

null :: Last a -> Bool #

length :: Last a -> Int #

elem :: Eq a => a -> Last a -> Bool #

maximum :: Ord a => Last a -> a #

minimum :: Ord a => Last a -> a #

sum :: Num a => Last a -> a #

product :: Num a => Last a -> a #

Traversable Last

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Last a -> f (Last b) #

sequenceA :: Applicative f => Last (f a) -> f (Last a) #

mapM :: Monad m => (a -> m b) -> Last a -> m (Last b) #

sequence :: Monad m => Last (m a) -> m (Last a) #

Eq a => Eq (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

(==) :: Last a -> Last a -> Bool #

(/=) :: Last a -> Last a -> Bool #

Ord a => Ord (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

compare :: Last a -> Last a -> Ordering #

(<) :: Last a -> Last a -> Bool #

(<=) :: Last a -> Last a -> Bool #

(>) :: Last a -> Last a -> Bool #

(>=) :: Last a -> Last a -> Bool #

max :: Last a -> Last a -> Last a #

min :: Last a -> Last a -> Last a #

Read a => Read (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Show a => Show (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Generic (Last a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Last a) :: Type -> Type #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Semigroup (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Monoid (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

ParseField a => ParseRecord (Last a) Source # 
Instance details

Defined in Options.Generic

ParseField a => ParseFields (Last a) Source # 
Instance details

Defined in Options.Generic

Generic1 Last 
Instance details

Defined in Data.Monoid

Associated Types

type Rep1 Last :: k -> Type #

Methods

from1 :: Last a -> Rep1 Last a #

to1 :: Rep1 Last a -> Last a #

type Rep (Last a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

type Rep (Last a) = D1 (MetaData "Last" "Data.Monoid" "base" True) (C1 (MetaCons "Last" PrefixI True) (S1 (MetaSel (Just "getLast") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))
type Rep1 Last

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

type Rep1 Last = D1 (MetaData "Last" "Data.Monoid" "base" True) (C1 (MetaCons "Last" PrefixI True) (S1 (MetaSel (Just "getLast") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Maybe)))

newtype Sum a #

Monoid under addition.

>>> getSum (Sum 1 <> Sum 2 <> mempty)
3

Constructors

Sum 

Fields

Instances
Monad Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Sum a -> (a -> Sum b) -> Sum b #

(>>) :: Sum a -> Sum b -> Sum b #

return :: a -> Sum a #

fail :: String -> Sum a #

Functor Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Sum a -> Sum b #

(<$) :: a -> Sum b -> Sum a #

Applicative Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Sum a #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b #

liftA2 :: (a -> b -> c) -> Sum a -> Sum b -> Sum c #

(*>) :: Sum a -> Sum b -> Sum b #

(<*) :: Sum a -> Sum b -> Sum a #

Foldable Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Sum m -> m #

foldMap :: Monoid m => (a -> m) -> Sum a -> m #

foldr :: (a -> b -> b) -> b -> Sum a -> b #

foldr' :: (a -> b -> b) -> b -> Sum a -> b #

foldl :: (b -> a -> b) -> b -> Sum a -> b #

foldl' :: (b -> a -> b) -> b -> Sum a -> b #

foldr1 :: (a -> a -> a) -> Sum a -> a #

foldl1 :: (a -> a -> a) -> Sum a -> a #

toList :: Sum a -> [a] #

null :: Sum a -> Bool #

length :: Sum a -> Int #

elem :: Eq a => a -> Sum a -> Bool #

maximum :: Ord a => Sum a -> a #

minimum :: Ord a => Sum a -> a #

sum :: Num a => Sum a -> a #

product :: Num a => Sum a -> a #

Traversable Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Sum a -> f (Sum b) #

sequenceA :: Applicative f => Sum (f a) -> f (Sum a) #

mapM :: Monad m => (a -> m b) -> Sum a -> m (Sum b) #

sequence :: Monad m => Sum (m a) -> m (Sum a) #

Bounded a => Bounded (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: Sum a #

maxBound :: Sum a #

Eq a => Eq (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Sum a -> Sum a -> Bool #

(/=) :: Sum a -> Sum a -> Bool #

Num a => Num (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(+) :: Sum a -> Sum a -> Sum a #

(-) :: Sum a -> Sum a -> Sum a #

(*) :: Sum a -> Sum a -> Sum a #

negate :: Sum a -> Sum a #

abs :: Sum a -> Sum a #

signum :: Sum a -> Sum a #

fromInteger :: Integer -> Sum a #

Ord a => Ord (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Sum a -> Sum a -> Ordering #

(<) :: Sum a -> Sum a -> Bool #

(<=) :: Sum a -> Sum a -> Bool #

(>) :: Sum a -> Sum a -> Bool #

(>=) :: Sum a -> Sum a -> Bool #

max :: Sum a -> Sum a -> Sum a #

min :: Sum a -> Sum a -> Sum a #

Read a => Read (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Sum a -> ShowS #

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) :: Type -> Type #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Num a => Semigroup (Sum a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

(Num a, ParseField a) => ParseRecord (Sum a) Source # 
Instance details

Defined in Options.Generic

Methods

parseRecord :: Parser (Sum a) Source #

(Num a, ParseField a) => ParseFields (Sum a) Source # 
Instance details

Defined in Options.Generic

Generic1 Sum 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Sum :: k -> Type #

Methods

from1 :: Sum a -> Rep1 Sum a #

to1 :: Rep1 Sum a -> Sum a #

type Rep (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Sum a) = D1 (MetaData "Sum" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Sum" PrefixI True) (S1 (MetaSel (Just "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Sum

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep1 Sum = D1 (MetaData "Sum" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Sum" PrefixI True) (S1 (MetaSel (Just "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype Product a #

Monoid under multiplication.

>>> getProduct (Product 3 <> Product 4 <> mempty)
12

Constructors

Product 

Fields

Instances
Monad Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Product a -> (a -> Product b) -> Product b #

(>>) :: Product a -> Product b -> Product b #

return :: a -> Product a #

fail :: String -> Product a #

Functor Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Product a -> Product b #

(<$) :: a -> Product b -> Product a #

Applicative Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Product a #

(<*>) :: Product (a -> b) -> Product a -> Product b #

liftA2 :: (a -> b -> c) -> Product a -> Product b -> Product c #

(*>) :: Product a -> Product b -> Product b #

(<*) :: Product a -> Product b -> Product a #

Foldable Product

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Product m -> m #

foldMap :: Monoid m => (a -> m) -> Product a -> m #

foldr :: (a -> b -> b) -> b -> Product a -> b #

foldr' :: (a -> b -> b) -> b -> Product a -> b #

foldl :: (b -> a -> b) -> b -> Product a -> b #

foldl' :: (b -> a -> b) -> b -> Product a -> b #

foldr1 :: (a -> a -> a) -> Product a -> a #

foldl1 :: (a -> a -> a) -> Product a -> a #

toList :: Product a -> [a] #

null :: Product a -> Bool #

length :: Product a -> Int #

elem :: Eq a => a -> Product a -> Bool #

maximum :: Ord a => Product a -> a #

minimum :: Ord a => Product a -> a #

sum :: Num a => Product a -> a #

product :: Num a => Product a -> a #

Traversable Product

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Product a -> f (Product b) #

sequenceA :: Applicative f => Product (f a) -> f (Product a) #

mapM :: Monad m => (a -> m b) -> Product a -> m (Product b) #

sequence :: Monad m => Product (m a) -> m (Product a) #

Bounded a => Bounded (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq a => Eq (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Product a -> Product a -> Bool #

(/=) :: Product a -> Product a -> Bool #

Num a => Num (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(+) :: Product a -> Product a -> Product a #

(-) :: Product a -> Product a -> Product a #

(*) :: Product a -> Product a -> Product a #

negate :: Product a -> Product a #

abs :: Product a -> Product a #

signum :: Product a -> Product a #

fromInteger :: Integer -> Product a #

Ord a => Ord (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Product a -> Product a -> Ordering #

(<) :: Product a -> Product a -> Bool #

(<=) :: Product a -> Product a -> Bool #

(>) :: Product a -> Product a -> Bool #

(>=) :: Product a -> Product a -> Bool #

max :: Product a -> Product a -> Product a #

min :: Product a -> Product a -> Product a #

Read a => Read (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Product a -> ShowS #

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) :: Type -> Type #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Num a => Semigroup (Product a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Product a -> Product a -> Product a #

sconcat :: NonEmpty (Product a) -> Product a #

stimes :: Integral b => b -> Product a -> Product a #

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

(Num a, ParseField a) => ParseRecord (Product a) Source # 
Instance details

Defined in Options.Generic

(Num a, ParseField a) => ParseFields (Product a) Source # 
Instance details

Defined in Options.Generic

Generic1 Product 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Product :: k -> Type #

Methods

from1 :: Product a -> Rep1 Product a #

to1 :: Rep1 Product a -> Product a #

type Rep (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Product a) = D1 (MetaData "Product" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Product" PrefixI True) (S1 (MetaSel (Just "getProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Product

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep1 Product = D1 (MetaData "Product" "Data.Semigroup.Internal" "base" True) (C1 (MetaCons "Product" PrefixI True) (S1 (MetaSel (Just "getProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))