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

Safe HaskellNone
LanguageHaskell2010

Data.Constraint.Deriving.DeriveAll

Synopsis

Documentation

data DeriveAll Source #

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 [].

DeriveAllBut [String]

Specify a list of class names to ignore.

Instances
Eq DeriveAll Source # 
Instance details

Defined in Data.Constraint.Deriving.DeriveAll

Data DeriveAll Source # 
Instance details

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 # 
Instance details

Defined in Data.Constraint.Deriving.DeriveAll

Show DeriveAll Source # 
Instance details

Defined in Data.Constraint.Deriving.DeriveAll

type family DeriveContext (t :: Type) :: Constraint Source #

This type family is used to impose constraints on type parameters when looking up type instances for the DeriveAll core plugin.

DeriveAll uses only those instances that satisfy the specified constraint. If the constraint is not specified, it is assumed to be `()`.

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.