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

Safe HaskellSafe
LanguageHaskell98

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}

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.

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

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

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

Methods

parseRecord :: Parser a Source #

parseRecord :: (Generic a, GenericParseRecord (Rep a)) => Parser a Source #

Instances

ParseRecord Bool Source # 
ParseRecord Char Source # 
ParseRecord Double Source # 
ParseRecord Float Source # 
ParseRecord Int Source # 
ParseRecord Int8 Source # 
ParseRecord Int16 Source # 
ParseRecord Int32 Source # 
ParseRecord Int64 Source # 
ParseRecord Integer Source # 
ParseRecord Natural Source # 
ParseRecord Ordering Source # 
ParseRecord Word8 Source # 
ParseRecord Word16 Source # 
ParseRecord Word32 Source # 
ParseRecord Word64 Source # 
ParseRecord () Source # 

Methods

parseRecord :: Parser () Source #

ParseRecord Void Source # 
ParseRecord All Source # 
ParseRecord Any Source # 
ParseRecord ByteString Source # 
ParseRecord ByteString Source # 
ParseRecord Text Source # 
ParseRecord FilePath Source # 
ParseRecord Text Source # 
ParseRecord Day Source # 
ParseField a => ParseRecord [a] Source # 

Methods

parseRecord :: Parser [a] Source #

ParseField a => ParseRecord (Maybe a) Source # 
ParseFields a => ParseRecord (Only a) Source # 
ParseField a => ParseRecord (NonEmpty a) Source # 
(Num a, ParseField a) => ParseRecord (Sum a) Source # 

Methods

parseRecord :: Parser (Sum a) Source #

(Num a, ParseField a) => ParseRecord (Product a) Source # 
ParseField a => ParseRecord (First a) Source # 
ParseField a => ParseRecord (Last a) Source # 
(ParseFields a, ParseFields b) => ParseRecord (Either a b) Source # 

Methods

parseRecord :: Parser (Either a b) Source #

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

Methods

parseRecord :: Parser (a, b) Source #

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

Methods

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

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

Methods

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

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

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 # 

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 # 

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 # 

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

Methods

parseFields Source #

Arguments

:: Maybe Text

Help message

-> Maybe Text

Field label

-> Maybe Char

Short name

-> Parser a 

parseFields Source #

Arguments

:: ParseField a 
=> Maybe Text

Help message

-> Maybe Text

Field label

-> Maybe Char

Short name

-> Parser a 

Instances

ParseFields Bool Source # 
ParseFields Char Source # 
ParseFields Double Source # 
ParseFields Float Source # 
ParseFields Int Source # 
ParseFields Int8 Source # 
ParseFields Int16 Source # 
ParseFields Int32 Source # 
ParseFields Int64 Source # 
ParseFields Integer Source # 
ParseFields Natural Source # 
ParseFields Ordering Source # 
ParseFields Word8 Source # 
ParseFields Word16 Source # 
ParseFields Word32 Source # 
ParseFields Word64 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 # 
ParseField a => ParseFields (Maybe a) Source # 
ParseField a => ParseFields (NonEmpty 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 # 
(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

Methods

parseField Source #

Arguments

:: Maybe Text

Help message

-> Maybe Text

Field label

-> Maybe Char

Short name

-> Parser a 

parseField Source #

Arguments

:: Maybe Text

Help message

-> Maybe Text

Field label

-> Maybe Char

Short name

-> Parser a 

parseListOfField Source #

Arguments

:: Maybe Text

Help message

-> Maybe Text

Field label

-> Maybe Char

Short name

-> 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 # 
ParseField Char Source # 
ParseField Double Source # 
ParseField Float Source # 
ParseField Int Source # 
ParseField Int8 Source # 
ParseField Int16 Source # 
ParseField Int32 Source # 
ParseField Int64 Source # 
ParseField Integer Source # 
ParseField Natural Source # 
ParseField Ordering Source # 
ParseField Word8 Source # 
ParseField Word16 Source # 
ParseField Word32 Source # 
ParseField Word64 Source # 
ParseField () Source # 
ParseField String Source # 
ParseField Void Source # 
ParseField All Source # 
ParseField Any Source # 
ParseField ByteString Source # 
ParseField ByteString Source # 
ParseField Text Source # 
ParseField FilePath Source # 
ParseField Text Source # 
ParseField Day Source # 
(ParseField a, KnownSymbol h) => ParseField ((<?>) a h) Source # 

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 

Methods

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

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

Eq a => Eq (Only a) 

Methods

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

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

Data a => Data (Only a) 

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) 

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) 
Show a => Show (Only a) 

Methods

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

show :: Only a -> String #

showList :: [Only a] -> ShowS #

Generic (Only a) 

Associated Types

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

Methods

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

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

NFData a => NFData (Only a) 

Methods

rnf :: Only a -> () #

ParseFields a => ParseRecord (Only a) Source # 
type Rep (Only a) 
type Rep (Only a) = D1 * (MetaData "Only" "Data.Tuple.Only" "Only-0.1-K3HSyq2koL8JtFXn0ZkrT6" True) (C1 * (MetaCons "Only" PrefixI True) (S1 * (MetaSel (Just Symbol "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

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 # 

Methods

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

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

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

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

Associated Types

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

Methods

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

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

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

Methods

parseRecord :: Parser (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 Unwrapped ::: ((<?>) field helper) = field
type Rep ((<?>) field help) Source # 
type Rep ((<?>) field help) = D1 * (MetaData "<?>" "Options.Generic" "optparse-generic-1.3.0-LieUxz6zglcCxpbjaidCbS" True) (C1 * (MetaCons "Helpful" PrefixI True) (S1 * (MetaSel (Just Symbol "unHelpful") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * field)))

type family wrap ::: wrapped infixr 0 Source #

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

Instances

type Wrapped ::: wrapped Source # 
type Wrapped ::: wrapped = wrapped
type Unwrapped ::: ((<?>) field helper) Source # 
type Unwrapped ::: ((<?>) field helper) = field

data Wrapped Source #

Flag to keep fields wrapped

Instances

type Wrapped ::: wrapped Source # 
type Wrapped ::: wrapped = wrapped

data Unwrapped Source #

Flag to unwrap fields annotated using '(?)'

Instances

type Unwrapped ::: ((<?>) field helper) Source # 
type Unwrapped ::: ((<?>) field helper) = field

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.

Minimal complete definition

from, to

Instances

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering 

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic () 

Associated Types

type Rep () :: * -> * #

Methods

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

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

Generic Void 

Associated Types

type Rep Void :: * -> * #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic Version 

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic ExitCode 

Associated Types

type Rep ExitCode :: * -> * #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic All 

Associated Types

type Rep All :: * -> * #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any 

Associated Types

type Rep Any :: * -> * #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Fixity 

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity 

Associated Types

type Rep Associativity :: * -> * #

Generic SourceUnpackedness 
Generic SourceStrictness 
Generic DecidedStrictness 
Generic [a] 

Associated Types

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

Methods

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

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

Generic (Maybe a) 

Associated Types

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

Methods

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

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

Generic (Par1 p) 

Associated Types

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

Methods

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

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

Generic (Only a) 

Associated Types

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

Methods

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

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

Generic (Complex a) 

Associated Types

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

Methods

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

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

Generic (Min a) 

Associated Types

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

Methods

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

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

Generic (Max a) 

Associated Types

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

Methods

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

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

Generic (First a) 

Associated Types

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

Methods

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

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

Generic (Last a) 

Associated Types

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

Methods

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

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

Generic (WrappedMonoid m) 

Associated Types

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

Generic (Option a) 

Associated Types

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

Methods

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

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

Generic (NonEmpty a) 

Associated Types

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

Methods

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

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

Generic (ZipList a) 

Associated Types

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

Methods

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

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

Generic (Identity a) 

Associated Types

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

Methods

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

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

Generic (Dual a) 

Associated Types

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

Methods

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

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

Generic (Endo a) 

Associated Types

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

Methods

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

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

Generic (Sum a) 

Associated Types

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

Methods

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

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

Generic (Product a) 

Associated Types

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

Methods

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

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

Generic (First a) 

Associated Types

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

Methods

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

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

Generic (Last a) 

Associated Types

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

Methods

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

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

Generic (Tree a) 

Associated Types

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

Methods

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

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

Generic (ViewL a) 

Associated Types

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

Methods

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

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

Generic (ViewR a) 

Associated Types

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

Methods

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

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

Generic (Either a b) 

Associated Types

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

Methods

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

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

Generic (V1 k p) 

Associated Types

type Rep (V1 k p) :: * -> * #

Methods

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

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

Generic (U1 k p) 

Associated Types

type Rep (U1 k p) :: * -> * #

Methods

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

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

Generic (a, b) 

Associated Types

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

Methods

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

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

Generic (Arg a b) 

Associated Types

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

Methods

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

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

Generic (WrappedMonad m a) 

Associated Types

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

Methods

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

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

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

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

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

Generic ((<?>) field help) # 

Associated Types

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

Methods

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

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

Generic (Rec1 k f p) 

Associated Types

type Rep (Rec1 k f p) :: * -> * #

Methods

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

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

Generic (URec k (Ptr ()) p) 

Associated Types

type Rep (URec k (Ptr ()) p) :: * -> * #

Methods

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

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

Generic (URec k Char p) 

Associated Types

type Rep (URec k Char p) :: * -> * #

Methods

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

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

Generic (URec k Double p) 

Associated Types

type Rep (URec k Double p) :: * -> * #

Methods

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

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

Generic (URec k Float p) 

Associated Types

type Rep (URec k Float p) :: * -> * #

Methods

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

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

Generic (URec k Int p) 

Associated Types

type Rep (URec k Int p) :: * -> * #

Methods

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

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

Generic (URec k Word p) 

Associated Types

type Rep (URec k Word p) :: * -> * #

Methods

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

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

Generic (a, b, c) 

Associated Types

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

Methods

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

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

Generic (WrappedArrow a b c) 

Associated Types

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

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 k a b) 

Associated Types

type Rep (Const k a b) :: * -> * #

Methods

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

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

Generic (Alt k f a) 

Associated Types

type Rep (Alt k f a) :: * -> * #

Methods

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

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

Generic (K1 k i c p) 

Associated Types

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

Methods

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

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

Generic ((:+:) k f g p) 

Associated Types

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

Methods

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

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

Generic ((:*:) k f g p) 

Associated Types

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

Methods

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

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

Generic (a, b, c, d) 

Associated Types

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

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 k f g a) 

Associated Types

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

Methods

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

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

Generic (Sum k f g a) 

Associated Types

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

Methods

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

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

Generic (M1 k i c f p) 

Associated Types

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

Methods

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

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

Generic ((:.:) k2 k1 f g p) 

Associated Types

type Rep ((k2 :.: k1) f g p) :: * -> * #

Methods

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

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

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

Associated Types

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

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 k1 k2 f g a) 

Associated Types

type Rep (Compose k1 k2 f g a) :: * -> * #

Methods

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

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

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

Associated Types

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

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) 

Associated Types

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

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.

newtype All :: * #

Boolean monoid under conjunction (&&).

Constructors

All 

Fields

Instances

Bounded All 

Methods

minBound :: All #

maxBound :: All #

Eq All 

Methods

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

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

Ord All 

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 
Show All 

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Generic All 

Associated Types

type Rep All :: * -> * #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Semigroup All

Since: 4.9.0.0

Methods

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

sconcat :: NonEmpty All -> All #

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

Monoid All

Since: 2.1

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

ParseRecord All Source # 
ParseFields All Source # 
ParseField All Source # 
type Rep All 
type Rep All = D1 * (MetaData "All" "Data.Monoid" "base" True) (C1 * (MetaCons "All" PrefixI True) (S1 * (MetaSel (Just Symbol "getAll") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

newtype Any :: * #

Boolean monoid under disjunction (||).

Constructors

Any 

Fields

Instances

Bounded Any 

Methods

minBound :: Any #

maxBound :: Any #

Eq Any 

Methods

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

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

Ord Any 

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 
Show Any 

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

Generic Any 

Associated Types

type Rep Any :: * -> * #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Semigroup Any

Since: 4.9.0.0

Methods

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

sconcat :: NonEmpty Any -> Any #

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

Monoid Any

Since: 2.1

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

ParseRecord Any Source # 
ParseFields Any Source # 
ParseField Any Source # 
type Rep Any 
type Rep Any = D1 * (MetaData "Any" "Data.Monoid" "base" True) (C1 * (MetaCons "Any" PrefixI True) (S1 * (MetaSel (Just Symbol "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.

Constructors

First 

Fields

Instances

Monad First 

Methods

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

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

return :: a -> First a #

fail :: String -> First a #

Functor First 

Methods

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

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

Applicative First 

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

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 #

Eq a => Eq (First a) 

Methods

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

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

Ord a => Ord (First a) 

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) 
Show a => Show (First a) 

Methods

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

show :: First a -> String #

showList :: [First a] -> ShowS #

Generic (First a) 

Associated Types

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

Methods

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

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

Semigroup (First a)

Since: 4.9.0.0

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

Methods

mempty :: First a #

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

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

ParseField a => ParseRecord (First a) Source # 
ParseField a => ParseFields (First a) Source # 
Generic1 * First 

Associated Types

type Rep1 First (f :: First -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 First f a #

to1 :: Rep1 First f a -> f a #

type Rep (First a) 
type Rep (First a) = D1 * (MetaData "First" "Data.Monoid" "base" True) (C1 * (MetaCons "First" PrefixI True) (S1 * (MetaSel (Just Symbol "getFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe a))))
type Rep1 * First 
type Rep1 * First = D1 * (MetaData "First" "Data.Monoid" "base" True) (C1 * (MetaCons "First" PrefixI True) (S1 * (MetaSel (Just Symbol "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)

Constructors

Last 

Fields

Instances

Monad Last 

Methods

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

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

return :: a -> Last a #

fail :: String -> Last a #

Functor Last 

Methods

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

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

Applicative Last 

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

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 #

Eq a => Eq (Last a) 

Methods

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

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

Ord a => Ord (Last a) 

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) 
Show a => Show (Last a) 

Methods

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

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Generic (Last a) 

Associated Types

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

Methods

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

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

Semigroup (Last a)

Since: 4.9.0.0

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

Methods

mempty :: Last a #

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

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

ParseField a => ParseRecord (Last a) Source # 
ParseField a => ParseFields (Last a) Source # 
Generic1 * Last 

Associated Types

type Rep1 Last (f :: Last -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Last f a #

to1 :: Rep1 Last f a -> f a #

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

newtype Sum a :: * -> * #

Monoid under addition.

Constructors

Sum 

Fields

Instances

Monad Sum

Since: 4.8.0.0

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

Methods

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

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

Applicative Sum

Since: 4.8.0.0

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

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 #

Bounded a => Bounded (Sum a) 

Methods

minBound :: Sum a #

maxBound :: Sum a #

Eq a => Eq (Sum a) 

Methods

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

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

Num a => Num (Sum a) 

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) 

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) 
Show a => Show (Sum a) 

Methods

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

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Generic (Sum a) 

Associated Types

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

Methods

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

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

Num a => Semigroup (Sum a)

Since: 4.9.0.0

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

Methods

mempty :: Sum a #

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

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

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

Methods

parseRecord :: Parser (Sum a) Source #

(Num a, ParseField a) => ParseFields (Sum a) Source # 
Generic1 * Sum 

Associated Types

type Rep1 Sum (f :: Sum -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Sum f a #

to1 :: Rep1 Sum f a -> f a #

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

newtype Product a :: * -> * #

Monoid under multiplication.

Constructors

Product 

Fields

Instances

Monad Product

Since: 4.8.0.0

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

Methods

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

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

Applicative Product

Since: 4.8.0.0

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

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 #

Bounded a => Bounded (Product a) 
Eq a => Eq (Product a) 

Methods

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

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

Num a => Num (Product a) 

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) 

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) 
Show a => Show (Product a) 

Methods

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

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Generic (Product a) 

Associated Types

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

Methods

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

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

Num a => Semigroup (Product a)

Since: 4.9.0.0

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

Methods

mempty :: Product a #

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

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

(Num a, ParseField a) => ParseRecord (Product a) Source # 
(Num a, ParseField a) => ParseFields (Product a) Source # 
Generic1 * Product 

Associated Types

type Rep1 Product (f :: Product -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Product f a #

to1 :: Rep1 Product f a -> f a #

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