| Copyright | (C) 2015-2017 Ryan Scott | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Ryan Scott | 
| Portability | Template Haskell | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
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
- deriveFoldable :: Name -> Q [Dec]
- deriveFoldableOptions :: FFTOptions -> Name -> Q [Dec]
- makeFoldMap :: Name -> Q Exp
- makeFoldMapOptions :: FFTOptions -> Name -> Q Exp
- makeFoldr :: Name -> Q Exp
- makeFoldrOptions :: FFTOptions -> Name -> Q Exp
- makeFold :: Name -> Q Exp
- makeFoldOptions :: FFTOptions -> Name -> Q Exp
- makeFoldl :: Name -> Q Exp
- makeFoldlOptions :: FFTOptions -> Name -> Q Exp
- makeNull :: Name -> Q Exp
- makeNullOptions :: FFTOptions -> Name -> Q Exp
- newtype FFTOptions = FFTOptions {}
- defaultFFTOptions :: FFTOptions
Foldable
deriveFoldable :: Name -> Q [Dec] Source #
Generates a Foldable 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
 Foldable 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
 Foldable 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
 Foldable 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
 Foldable 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
 Foldable 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 FunctorFoldableTraversable.)
Constructors
| FFTOptions | |
| Fields | |
Instances
| Eq FFTOptions Source # | |
| Defined in Data.Functor.Deriving.Internal | |
| Ord FFTOptions Source # | |
| Defined in Data.Functor.Deriving.Internal Methods compare :: FFTOptions -> FFTOptions -> Ordering # (<) :: FFTOptions -> FFTOptions -> Bool # (<=) :: FFTOptions -> FFTOptions -> Bool # (>) :: FFTOptions -> FFTOptions -> Bool # (>=) :: FFTOptions -> FFTOptions -> Bool # max :: FFTOptions -> FFTOptions -> FFTOptions # min :: FFTOptions -> FFTOptions -> FFTOptions # | |
| Read FFTOptions Source # | |
| Defined in Data.Functor.Deriving.Internal Methods readsPrec :: Int -> ReadS FFTOptions # readList :: ReadS [FFTOptions] # readPrec :: ReadPrec FFTOptions # readListPrec :: ReadPrec [FFTOptions] # | |
| Show FFTOptions Source # | |
| Defined in Data.Functor.Deriving.Internal Methods showsPrec :: Int -> FFTOptions -> ShowS # show :: FFTOptions -> String # showList :: [FFTOptions] -> ShowS # | |
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 -XGADTsor-XExistentialQuantificationextensions, an existential constraint cannot mention the last type variable. For example,data Illegal a = forall a. Show a => Illegal acannot have a derivedFunctorinstance.
- Type variables of kind * -> *are assumed to haveFoldableconstraints. If this is not desirable, usemakeFoldrormakeFoldMap.