constraints-deriving-1.1.1.1: Manipulating constraints and deriving class instances programmatically.

Safe HaskellNone
LanguageHaskell2010

Data.Constraint.Deriving.ClassDict

Synopsis

Documentation

data ClassDict Source #

A marker to tell the core plugin to replace the implementation of a top-level function by a corresponding class data constructor (wrapped into Dict).

Example:

class BarClass a => FooClass a where
  fooFun1 :: a -> a -> Int
  fooFun2 :: a -> Bool

{-# ANN deriveFooClass ClassDict #-}
deriveFooClass :: forall a . BarClass a
               => (a -> a -> Int)
               -> (a -> Bool)
               -> Dict (FooClass a)
deriveFooClass = deriveFooClass

That is, the plugin replaces the RHS of deriveFooClass function with classDataCon wrapped by bareToDict.

Note:

  • The plugin requires you to create a dummy function deriveFooClass and annotate it with ClassDict instead of automatically creating this function for you; this way, the function is visible during type checking: you can use it in the same module (avoiding orphans) and you see its type signature.
  • You have to provide a correct signature for deriveFooClass function; the plugin compares this signature against visible classes and their constructors. An incorrect signature will result in a compile-time error.
  • The dummy implementation deriveFooClass = deriveFooClass is used here to prevent GHC from inlining the function before the plugin can replace it. But you can implement in any way you like at your own risk.

Constructors

ClassDict 
Instances
Eq ClassDict Source # 
Instance details

Defined in Data.Constraint.Deriving.ClassDict

Data ClassDict Source # 
Instance details

Defined in Data.Constraint.Deriving.ClassDict

Methods

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

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

toConstr :: ClassDict -> Constr #

dataTypeOf :: ClassDict -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ClassDict Source # 
Instance details

Defined in Data.Constraint.Deriving.ClassDict

Show ClassDict Source # 
Instance details

Defined in Data.Constraint.Deriving.ClassDict

type CorePluginEnvRef = IORef CorePluginEnv Source #

Reference to the plugin environment variables.

initCorePluginEnv :: CoreM (IORef CorePluginEnv) Source #

Init the CorePluginM environment and save it to IORef.