| Copyright | (C) 2015-2017 Ryan Scott | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Ryan Scott | 
| Portability | Template Haskell | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.Functor.Deriving.Internal
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
- 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
- deriveFunctor :: Name -> Q [Dec]
- deriveFunctorOptions :: FFTOptions -> Name -> Q [Dec]
- makeFmap :: Name -> Q Exp
- makeFmapOptions :: FFTOptions -> Name -> Q Exp
- makeReplace :: Name -> Q Exp
- makeReplaceOptions :: FFTOptions -> Name -> Q Exp
- deriveTraversable :: Name -> Q [Dec]
- deriveTraversableOptions :: FFTOptions -> Name -> Q [Dec]
- makeTraverse :: Name -> Q Exp
- makeTraverseOptions :: FFTOptions -> Name -> Q Exp
- makeSequenceA :: Name -> Q Exp
- makeSequenceAOptions :: FFTOptions -> Name -> Q Exp
- makeMapM :: Name -> Q Exp
- makeMapMOptions :: FFTOptions -> Name -> Q Exp
- makeSequence :: Name -> Q Exp
- makeSequenceOptions :: FFTOptions -> Name -> Q Exp
- newtype FFTOptions = FFTOptions {}
- defaultFFTOptions :: FFTOptions
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.
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.
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.
makeReplace :: Name -> Q Exp Source #
Generates a lambda expression which behaves like (<$) (without requiring a
 FunctorClass instance).
makeReplaceOptions :: FFTOptions -> Name -> Q Exp Source #
Like makeReplace, 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).
makeSequenceAOptions :: FFTOptions -> Name -> Q Exp Source #
Like makeSequenceA, but takes an FFTOptions argument.
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 FunctorClassFunctorClassFunctorClass.)
Constructors
| FFTOptions | |
| Fields | |
Instances
| 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 # | |
| 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 # | |
defaultFFTOptions :: FFTOptions Source #
Conservative FFTOptions that doesn't attempt to use EmptyCase (to
 prevent users from having to enable that extension at use sites.)