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

Safe HaskellNone
LanguageHaskell2010

Data.Constraint.Deriving.ToInstance

Synopsis

Documentation

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:

  • fooNum should 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 Dict must 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 
Instances
Eq ToInstance Source # 
Instance details

Defined in Data.Constraint.Deriving.ToInstance

Data ToInstance Source # 
Instance details

Defined in Data.Constraint.Deriving.ToInstance

Methods

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

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

toConstr :: ToInstance -> Constr #

dataTypeOf :: ToInstance -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ToInstance Source # 
Instance details

Defined in Data.Constraint.Deriving.ToInstance

Show ToInstance Source # 
Instance details

Defined in Data.Constraint.Deriving.ToInstance

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 NoOverlap instance. However, it may be overlapped by Overlapping instances, and it may overlap Overlappable instances.

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 Overlapping and Overlappable flags.

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
Eq OverlapMode Source # 
Instance details

Defined in Data.Constraint.Deriving.CorePluginM

Data OverlapMode Source # 
Instance details

Defined in Data.Constraint.Deriving.CorePluginM

Methods

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

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

toConstr :: OverlapMode -> Constr #

dataTypeOf :: OverlapMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Read OverlapMode Source # 
Instance details

Defined in Data.Constraint.Deriving.CorePluginM

Show OverlapMode Source # 
Instance details

Defined in Data.Constraint.Deriving.CorePluginM

Semigroup OverlapMode Source # 
Instance details

Defined in Data.Constraint.Deriving.CorePluginM

Monoid OverlapMode Source # 
Instance details

Defined in Data.Constraint.Deriving.CorePluginM

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.