deriving-compat-0.5.6: Backports of GHC deriving extensions

Copyright(C) 2015-2017 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
PortabilityTemplate Haskell
Safe HaskellNone
LanguageHaskell2010

Data.Functor.Deriving.Internal

Contents

Description

The machinery needed to derive FunctorClass, FunctorClass, and FunctorClass instances.

For more info on how deriving Functor works, see this GHC wiki page.

Note: this is an internal module, and as such, the API presented here is not guaranteed to be stable, even between minor releases of this library.

Synopsis

FunctorClass

deriveFoldable :: Name -> Q [Dec] Source #

Generates a FunctorClass instance declaration for the given data type or data family instance.

deriveFoldableOptions :: FFTOptions -> Name -> Q [Dec] Source #

Like deriveFoldable, but takes an FFTOptions argument.

makeFoldMap :: Name -> Q Exp Source #

Generates a lambda expression which behaves like foldMap (without requiring a FunctorClass instance).

makeFoldMapOptions :: FFTOptions -> Name -> Q Exp Source #

Like makeFoldMap, but takes an FFTOptions argument.

makeFoldr :: Name -> Q Exp Source #

Generates a lambda expression which behaves like foldr (without requiring a FunctorClass instance).

makeFoldrOptions :: FFTOptions -> Name -> Q Exp Source #

Like makeFoldr, but takes an FFTOptions argument.

makeFold :: Name -> Q Exp Source #

Generates a lambda expression which behaves like fold (without requiring a FunctorClass instance).

makeFoldOptions :: FFTOptions -> Name -> Q Exp Source #

Like makeFold, but takes an FFTOptions argument.

makeFoldl :: Name -> Q Exp Source #

Generates a lambda expression which behaves like foldl (without requiring a FunctorClass instance).

makeFoldlOptions :: FFTOptions -> Name -> Q Exp Source #

Like makeFoldl, but takes an FFTOptions argument.

FunctorClass

deriveFunctor :: Name -> Q [Dec] Source #

Generates a FunctorClass instance declaration for the given data type or data family instance.

deriveFunctorOptions :: FFTOptions -> Name -> Q [Dec] Source #

Like deriveFunctor, but takes an FFTOptions argument.

makeFmap :: Name -> Q Exp Source #

Generates a lambda expression which behaves like fmap (without requiring a FunctorClass instance).

makeFmapOptions :: FFTOptions -> Name -> Q Exp Source #

Like makeFmap, but takes an FFTOptions argument.

FunctorClass

deriveTraversable :: Name -> Q [Dec] Source #

Generates a FunctorClass instance declaration for the given data type or data family instance.

deriveTraversableOptions :: FFTOptions -> Name -> Q [Dec] Source #

Like deriveTraverse, but takes an FFTOptions argument.

makeTraverse :: Name -> Q Exp Source #

Generates a lambda expression which behaves like traverse (without requiring a FunctorClass instance).

makeTraverseOptions :: FFTOptions -> Name -> Q Exp Source #

Like makeTraverse, but takes an FFTOptions argument.

makeSequenceA :: Name -> Q Exp Source #

Generates a lambda expression which behaves like sequenceA (without requiring a FunctorClass instance).

makeMapM :: Name -> Q Exp Source #

Generates a lambda expression which behaves like mapM (without requiring a FunctorClass instance).

makeMapMOptions :: FFTOptions -> Name -> Q Exp Source #

Like makeMapM, but takes an FFTOptions argument.

makeSequence :: Name -> Q Exp Source #

Generates a lambda expression which behaves like sequence (without requiring a FunctorClass instance).

makeSequenceOptions :: FFTOptions -> Name -> Q Exp Source #

Like makeSequence, but takes an FFTOptions argument.

FFTOptions

newtype FFTOptions Source #

Options that further configure how the functions in Data.Functor.Deriving should behave. (FFT stands for 'Functor'/'Foldable'/'Traversable'.)

Constructors

FFTOptions 

Fields

  • fftEmptyCaseBehavior :: Bool

    If True, derived instances for empty data types (i.e., ones with no data constructors) will use the EmptyCase language extension. If False, derived instances will simply use seq instead. (This has no effect on GHCs before 7.8, since EmptyCase is only available in 7.8 or later.)

defaultFFTOptions :: FFTOptions Source #

Conservative FFTOptions that doesn't attempt to use EmptyCase (to prevent users from having to enable that extension at use sites.)