deriving-compat-0.6.2: Backports of GHC deriving extensions
Copyright(C) 2015-2017 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
PortabilityTemplate Haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Foldable.Deriving

Description

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

These changes make it possible to derive Foldable instances for data types with existential constraints, e.g.,

data WrappedSet a where
    WrapSet :: Ord a => a -> WrappedSet a

deriving instance Foldable WrappedSet -- On GHC 8.0  on later
$(deriveFoldable ''WrappedSet)        -- On GHC 7.10 and earlier

In addition, derived Foldable instances from this module do not generate superfluous mempty expressions in its implementation of foldMap. One can verify this by compiling a module that uses deriveFoldable with the -ddump-splices GHC flag.

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

Synopsis

Foldable

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.

makeNull :: Name -> Q Exp Source #

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

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

Like makeNull, 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 FunctorClassFunctorClassFunctorClass.)

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

deriveFoldable 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 Functor instance.
  • Type variables of kind * -> * are assumed to have Foldable constraints. If this is not desirable, use makeFoldr or makeFoldMap.