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.Traversable.Deriving

Contents

Description

Exports functions to mechanically derive Traversable instances in a way that mimics how the -XDeriveTraversable extension works since GHC 8.0.

Derived Traversable instances from this module do not generate superfluous pure expressions in its implementation of traverse. One can verify this by compiling a module that uses deriveTraversable with the -ddump-splices GHC flag.

These changes make it possible to derive Traversable instances for data types with unlifted argument types, e.g.,

data IntHash a = IntHash Int# a

deriving instance Traversable IntHash -- On GHC 8.0  on later
$(deriveTraversable ''IntHash)        -- On GHC 7.10 and earlier

For more info on these changes, see this GHC wiki page.

Synopsis

Traversable

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

deriveTraversable limitations

Be aware of the following potential gotchas:

  • If you are using the -XGADTs or -XExistentialQuantification extensions, an existential constraint cannot mention the last type variable. For example, data Illegal a = forall a. Show a => Illegal a cannot have a derived Traversable instance.
  • Type variables of kind * -> * are assumed to have Traversable constraints. If this is not desirable, use makeTraverse.