intrinsic-superclasses-0.4.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:

 {-# language TemplateHaskell,QuasiQuotes,FlexibleInstances,UndecidableInstances #-}
 import Prelude hiding (Monoid(..))
 import Language.Haskell.TH.Instances

 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
 $(return []) -- Only needed if classes are defined in the same module, to make sure they're in scope below
 [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

data Defaults Source #

Give a default for a typeclass method that will be utilized by the instances quasiquoter. Defaults are declared by giving an annotation like:

{-# ann type MySubClass (Defaults 'mySuperclassMethod 'myDefaultDefinition) #-}

For example, we could modify Data.Traversable to work with instances like so:

{-# language TemplateHaskell #-}
module Data.Traversable where
{- ... normal imports ... -}
import Language.Haskell.TH.Instances.Defaults

class (Functor t, Foldable t) => Traversable t where ...  -- Same as normal
{-# ANN type Traversable (Defaults 'fmap 'fmapDefault) #-}
{-# ANN type Traversable (Defaults 'foldMap 'foldMapDefault) #-}
module MyData where
import Data.Traversable

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 = fmapDefault
instance Foldable Foo where foldMap = foldMapDefault
instance Travesable Foo where traverse f (Foo a a') = Foo <$> f a <*> f a'

Constructors

Defaults 

Fields

  • defining :: Name

    The name of the superclass method being provided

  • definition :: Name

    The name of a function implementing the superclass method

Instances
Data Defaults Source # 
Instance details

Defined in Language.Haskell.TH.Instances.Defaults

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Defaults -> c Defaults #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Defaults #

toConstr :: Defaults -> Constr #

dataTypeOf :: Defaults -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Defaults) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Defaults) #

gmapT :: (forall b. Data b => b -> b) -> Defaults -> Defaults #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Defaults -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Defaults -> r #

gmapQ :: (forall d. Data d => d -> u) -> Defaults -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Defaults -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Defaults -> m Defaults #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Defaults -> m Defaults #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Defaults -> m Defaults #

Show Defaults Source # 
Instance details

Defined in Language.Haskell.TH.Instances.Defaults