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 |
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.
Also works for components that are lists or instances of Functor
,
but still does not work for a great deal of other things.
deriving-compat
package may be used to derive the Show1
and Read1
instances
{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE TemplateHaskell #-} import Bound (Scope, makeBound) import Data.Functor.Classes (Show1, Read1, shosPrec1, readsPrec1) import Data.Deriving (deriveShow1, deriveRead1) data Exp a = V a | App (Exp a) (Exp a) | Lam (Scope () Exp a) | ND [Exp a] | I Int deriving (Functor) makeBound ''Exp deriveShow1 ''Exp deriveRead1 ''Exp instance Read a => Read (Exp a) where readsPrec = readsPrec1 instance Show a => Show (Exp a) where showsPrec = showsPrec1
and in GHCi
ghci> :set -XDeriveFunctor ghci> :set -XTemplateHaskell ghci> import Bound (Scope, makeBound) ghci> import Data.Functor.Classes (Show1, Read1, showsPrec1, readsPrec1) ghci> import Data.Deriving (deriveShow1, deriveRead1) ghci> :{ ghci| data Exp a = V a | App (Exp a) (Exp a) | Lam (Scope () Exp a) | ND [Exp a] | I Int deriving (Functor) ghci| makeBound ''Exp ghci| deriveShow1 ''Exp ghci| deriveRead1 ''Exp ghci| instance Read a => Read (Exp a) where readsPrec = readsPrec1 ghci| instance Show a => Show (Exp a) where showsPrec = showsPrec1 ghci| :}
Eq
and Ord
instances can be derived similarly
import Data.Functor.Classes (Eq1, Ord1, eq1, compare1) import Data.Deriving (deriveEq1, deriveOrd1) deriveEq1 ''Exp deriveOrd1 ''Exp instance Eq a => Eq (Exp a) where (==) = eq1 instance Ord a => Ord (Exp a) where compare = compare1
or in GHCi:
ghci> import Data.Functor.Classes (Eq1, Ord1, eq1, compare1) ghci> import Data.Deriving (deriveEq1, deriveOrd1) ghci> :{ ghci| deriveEq1 ''Exp ghci| deriveOrd1 ''Exp ghci| instance Eq a => Eq (Exp a) where (==) = eq1 ghci| instance Ord a => Ord (Exp a) where compare = compare1 ghci| :}
We cannot automatically derive Eq
and Ord
using the standard GHC mechanism,
because 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)