| Copyright | (C) 2015 Ryan Scott |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Ryan Scott |
| Portability | Template Haskell |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Foldable.Deriving
Contents
Description
Exports functions to mechanically derive Foldable instances in a way that mimics
how the -XDeriveFoldable extension works since GHC 7.12. These changes make it
possible to derive Foldable instances for data types with existential constraints,
e.g.,
{-# LANGUAGE DeriveFoldable, GADTs, StandaloneDeriving, TemplateHaskell #-}
data WrappedSet a where
WrapSet :: Ord a => a -> WrappedSet a
deriving instance Foldable WrappedSet -- On GHC 7.12 on later
$(deriveFoldable ''WrappedSet) -- On GHC 7.10 and earlier
For more info on these changes, see this GHC wiki page.
deriveFoldable
deriveFoldable automatically generates a Foldable instances for a given data
type, newtype, or data family instance that has at least one type variable. Examples:
{-# LANGUAGE TemplateHaskell #-}
import Data.Foldable.Deriving
data Pair a = Pair a a
$(deriveFoldable ''Pair) -- instance Foldable Pair where ...
data Product f g a = Product (f a) (g a)
$(deriveFoldable ''Product)
-- instance (Foldable f, Foldable g) => Foldable (Pair f g) where ...
If you are using template-haskell-2.7.0.0 or later (i.e., GHC 7.4 or later),
then deriveFoldable can be used with data family instances (which requires the
-XTypeFamilies extension). To do so, pass the name of a data or newtype instance
constructor (NOT a data family name!) to deriveFoldable. Note that the
generated code may require the -XFlexibleInstances extension. Example:
{-# LANGUAGE FlexibleInstances, TemplateHaskell, TypeFamilies #-}
import Data.Foldable.Deriving
class AssocClass a b where
data AssocData a b
instance AssocClass Int b where
data AssocData Int b = AssocDataInt1 Int | AssocDataInt2 b
$(deriveFoldable 'AssocDataInt1) -- instance Foldable (AssocData Int) where ...
-- Alternatively, one could use $(deriveFoldable 'AssocDataInt2)
Note that there are some limitations:
- The
Nameargument must not be a type synonym. - The last type variable must be of kind
*. Other type variables of kind* -> *are assumed to require aFoldableconstraint. If your data type doesn't meet this assumption, use amakefunction. - If using the
-XDatatypeContextsextension, a constraint cannot mention the last type variable. For example,data Illegal a where I :: Ord a => a -> Illegal acannot have a derivedFoldableinstance. - If the last type variable is used within a constructor argument's type, it must
only be used in the last type argument. For example,
data Legal a b = Legal (Int, Int, a, b)can have a derivedFoldableinstance, butdata Illegal a b = Illegal (a, b, a, b)cannot. - Data family instances must be able to eta-reduce the last type variable. In other words, if you have a instance of the form:
data family Family a1 ... an t data instance Family e1 ... e2 v = ...
Then the following conditions must hold:
vmust be a type variable.vmust not be mentioned in any ofe1, ...,e2.
- In GHC 7.8, a bug exists that can cause problems when a data family declaration and one of its data instances use different type variables, e.g.,
data family Foo a b data instance Foo Int z = Foo Int z $(deriveFoldable 'Foo)
To avoid this issue, it is recommened that you use the same type variables in the same positions in which they appeared in the data family declaration:
data family Foo a b data instance Foo Int b = Foo Int b $(deriveFoldable 'Foo)
deriveFoldable :: Name -> Q [Dec] Source
Generates a Foldable instance declaration for the given data type or data
family instance. This mimics how the -XDeriveFoldable extension works since
GHC 7.12.
make- functions
There may be scenarios in which you want to, say, fold over an arbitrary data type
or data family instance without having to make the type an instance of Foldable. For
these cases, this module provides several functions (all prefixed with make-) that
splice the appropriate lambda expression into your source code.
This is particularly useful for creating instances for sophisticated data types. For
example, deriveFoldable cannot infer the correct type context for
newtype HigherKinded f a b = HigherKinded (f a b), since f is of kind
* -> * -> *. However, it is still possible to create a Foldable instance for
HigherKinded without too much trouble using makeFoldr:
{-# LANGUAGE FlexibleContexts, TemplateHaskell #-}
import Data.Foldable.Deriving
newtype HigherKinded f a b = HigherKinded (f a b)
instance Foldable (f a) => Foldable (HigherKinded f a) where
foldr = $(makeFoldr ''HigherKinded)
makeFoldMap :: Name -> Q Exp Source
Generates a lambda expression which behaves like foldMap (without requiring a
Foldable instance). This mimics how the -XDeriveFoldable extension works since
GHC 7.12.