intrinsic-superclasses-0.3.0.0: A quasiquoter for better instance deriving and default methods

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.TH.Instances

Synopsis

Documentation

instances :: QuasiQuoter Source #

QuasiQuoter for providing intrinsic-superclasses.

Example:

 class Semigroup a where mappend :: a -> a -> a
 class Semigroup a => Commutative a
 class Semigroup a => Monoid a where mempty :: a
 class Monoid a => Group a where inverse :: a -> a
 class (Commutative a, Group a) => CommutativeGroup a
 [instances| Num a => CommutativeGroup a where
     mempty = fromInteger 0
     mappend a b = a + b
     inverse = negate
     |]

will generate the appropriate instances for Semigroup, Monoid, and Group:

 instance Num a => Semigroup a where mappend a b = a + b
 instance Num a => Commutative a
 instance Num a => Monoid a where mempty = fromInteger 0
 instance Num a => Group a where inverse = negate
 instance Num a => CommutativeGroup a

defaulting :: Name -> Q Exp -> Q [Dec] Source #

Give a default for a typeclass method that will be utilized by the instances quasiquoter. The default will be implicitly brought into scope when the module is imported, like typeclass instances.

Example:

module Data.Traversable.Defaults (module X) where
import Data.Traversable as X
import Data.Functor.Identity as X
import Data.Functor.Const as X
defaultMethod 'fmap [|\f -> runIdentity . traverse (Identity . f)|]
defaultMethod 'foldmap [|\f -> getConst . traverse (Const . f)|]
module MyData where
import Data.Traversable.Defaults

data Foo a = Foo a a
[instances| Travesable Foo where traverse f (Foo a a') = Foo <$> f a <*> f a'|]

will generate

instance Functor Foo where fmap = \f -> runIdentity . traverse (Identity . f)
instance Foldable Foo where foldMap = \f -> getConst . traverse (Const . f)
instance Travesable Foo where traverse f (Foo a a') = Foo <$> f a <*> f a'