| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Constraint.Deriving
Synopsis
- plugin :: Plugin
- data DeriveAll
- = DeriveAll
- | DeriveAllBut {
- _ignoreList :: [String]
- | DeriveAll' {
- _forcedMode :: OverlapMode
- _ignoreList :: [String]
- type family DeriveContext (t :: Type) :: Constraint
- newtype ToInstance = ToInstance {}
- data OverlapMode
- data ClassDict = ClassDict
Documentation
To use the plugin, add
{-# OPTIONS_GHC -fplugin Data.Constraint.Deriving #-}
to the header of your file.
For debugging, add a plugin option dump-instances
{-# OPTIONS_GHC -fplugin-opt Data.Constraint.Deriving:dump-instances #-}
to the header of your file; it will print all instances declared in the module (hand-written and auto-generated).
DeriveAll pass
A marker to tell the core plugin to derive all visible class instances for a given newtype.
The deriving logic is to simply re-use existing instance dictionaries by type-casting.
Constructors
| DeriveAll | Same as |
| DeriveAllBut | Specify a list of class names to ignore |
Fields
| |
| DeriveAll' | Specify an overlap mode and a list of class names to ignore |
Fields
| |
Instances
| Eq DeriveAll Source # | |
| Data DeriveAll Source # | |
Defined in Data.Constraint.Deriving.DeriveAll Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeriveAll -> c DeriveAll # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeriveAll # toConstr :: DeriveAll -> Constr # dataTypeOf :: DeriveAll -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeriveAll) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeriveAll) # gmapT :: (forall b. Data b => b -> b) -> DeriveAll -> DeriveAll # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeriveAll -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeriveAll -> r # gmapQ :: (forall d. Data d => d -> u) -> DeriveAll -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DeriveAll -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeriveAll -> m DeriveAll # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeriveAll -> m DeriveAll # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeriveAll -> m DeriveAll # | |
| Read DeriveAll Source # | |
| Show DeriveAll Source # | |
type family DeriveContext (t :: Type) :: Constraint Source #
ToInstance pass
newtype ToInstance Source #
A marker to tell the core plugin to convert a top-level Dict binding into
an instance declaration.
Example:
type family FooFam a where
FooFam Int = Int
FooFam a = Double
data FooSing a where
FooInt :: FooSing Int
FooNoInt :: FooSing a
class FooClass a where
fooSing :: FooSing a
newtype Bar a = Bar (FooFam a)
{-# ANN fooNum (ToInstance NoOverlap) #-}
fooNum :: forall a . Dict (Num (Bar a))
fooNum = mapDict (unsafeDerive Bar) $ case fooSing @a of
FooInt -> Dict
FooNoInt -> Dict
Note:
fooNumshould be exported by the module (otherwise, it may be optimized-out before the core plugin pass);- Constraints of the function become constraints of the new instance;
- The argument of
Dictmust be a single class (no constraint tuples or equality constraints); - The instance is created in a core-to-core pass, so it does not exist for the type checker in the current module.
Constructors
| ToInstance | |
Fields | |
Instances
data OverlapMode Source #
Define the behavior for the instance selection.
Mirrors OverlapMode, but does not have a SourceText field.
Constructors
| NoOverlap | This instance must not overlap another |
| Overlappable | Silently ignore this instance if you find a more specific one that matches the constraint you are trying to resolve |
| Overlapping | Silently ignore any more general instances that may be used to solve the constraint. |
| Overlaps | Equivalent to having both |
| Incoherent | Behave like Overlappable and Overlapping, and in addition pick an an arbitrary one if there are multiple matching candidates, and don't worry about later instantiation |
Instances
ClassDict pass
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
deriveFooClassand annotate it withClassDictinstead 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
deriveFooClassfunction; 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 = deriveFooClassis 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 # | |
| Data ClassDict Source # | |
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 # | |
| Show ClassDict Source # | |