| Copyright | (C) 2012-2013 Edward Kmett |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell98 |
Bound.TH
Description
This is a Template Haskell module for deriving Applicative and
Monad instances for data types.
Documentation
makeBound :: Name -> DecsQ Source
Use to automatically derive Applicative and Monad instances for
your datatype.
In GHC 7.10 or later the DeriveAnyClass extension may be used to derive the Show1 and Read1 instances
{--}
{--}
{--}
import Bound (Scope, makeBound)
import Prelude.Extras (Read1, Show1)
data Exp a
= V a
| App (Exp a) (Exp a)
| Lam (Scope () Exp a)
| I Int
deriving (Functor, Read, Read1, Show, Show1)
makeBound ''Exp
and in GHCi
ghci> :set -XDeriveAnyClass ghci> :set -XDeriveFunctor ghci> :set -XTemplateHaskell ghci> import Bound (Scope, makeBound) ghci> import Prelude.Extras (Read1, Show1) ghci> data Exp a = V a | App (Exp a) (Exp a) | Lam (Scope () Exp a) | I Int deriving (Functor, Read, Read1, Show, Show1); makeBound ''Exp
or
ghci> :{
ghci| data Exp a = V a | App (Exp a) (Exp a) | Lam (Scope () Exp a) | I Int deriving (Functor, Read, Read1, Show, Show1)
ghci| makeBound ''Exp
ghci| :}
If DeriveAnyClass is not used the instances must be declared explicitly:
data Exp a = V a | App (Exp a) (Exp a) | Lam (Scope () Exp a) | I Int deriving (Functor, Read, Show) instance Read1 Exp instance Show1 Exp
makeBound ''Exp @
or in GHCi:
ghci> :{
ghci| data Exp a = V a | App (Exp a) (Exp a) | Lam (Scope () Exp a) | I Int deriving (Functor, Read, Show)
ghci| instance Read1 Exp
ghci| instance Show1 Exp
ghci| makeBound ''Exp
ghci| :}
Eq and Ord instances need to be derived differently if the data
type's immediate components include Scope (or other instances of
Bound)
In a file with {--} at the top:
instance Eq1 Exp deriving instance Eq a => Eq (Exp a) instance Ord1 Exp deriving instance Ord a => Ord (Exp a)
or in GHCi:
ghci> :set -XStandaloneDeriving ghci> deriving instance Eq a => Eq (Exp a); instance Eq1 Exp ghci> deriving instance Ord a => Ord (Exp a); instance Ord1 Exp
because their Eq and Ord instances require Exp to be a Monad:
instance (Monad f, Eq b, Eq1 f, Eq a) => Eq (Scope b f a) instance (Monad f, Ord b, Ord1 f, Ord a) => Ord (Scope b f a)
Does not work yet for components that are lists or instances of
Functor or with a great deal other things.