magic-tyfams-0.1.1.0: Write plugins for magic type families with ease

Safe HaskellNone
LanguageHaskell2010

Plugin.MagicTyFam

Contents

Synopsis

Documentation

magicTyFamPlugin Source #

Arguments

:: String

package

-> String

module

-> String

identifier

-> ([Type] -> Maybe Type) 
-> Plugin 

Generate a plugin that solves instances of the type family pointed at by the three strings, via the function.

Semantics

withStuckSemantics :: ([Type] -> Maybe Type) -> [Type] -> Maybe Type Source #

Ensure that your resulting type family preserves the stuckness property, namely that it is stuck if any of its children are stuck.

You can use isTyFamFree instead of withStuckSemantics if you want tigher control over when your magic type family should be stuck.

isTyFamFree :: Type -> Bool #

Check that a type does not contain any type family applications.

Low level stuff

solveWanteds :: ([Type] -> Maybe Type) -> TyCon -> [Ct] -> TcPluginM [Ct] Source #

solveWanteds f tyfam cts finds all instaces of tyfam inside the wanted constraints cts, and evaluates them via f. The result is a set of CNonCanonical constraints, which should be emitted as the second parameter of TcPluginOk.

loadTyCon Source #

Arguments

:: String

package

-> String

module

-> String

identifier

-> TcPluginM TyCon 

Get your hands on the type constructor for your type family.

Error messages

type family WhenStuck (expr :: k) (b :: k) :: k where ... Source #

Type family for observing stuckness of a constraint. This can be used to construct error messages helpfully pointing out that your plugin isn't enabled. For example:

type family MyMagicFam a b c where
  MyMagicFam a b c =
    WhenStuck (MyMagicFamImpl a b c)
              (TypeError ('Text "The plugin isn't enabled!"))

type family MyMagicFam a b c where

and now solve MyMagicFamImpl via magicTyFamPlugin. The error message will only appear when MyMagicFamImpl is stuck, which is to say, if your plugin isn't enabled.

Equations

WhenStuck (_ AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind AnythingOfAnyKind) b = b 
WhenStuck a b = a 

Re-exports

data Plugin #

Plugin is the compiler plugin data type. Try to avoid constructing one of these directly, and just modify some fields of defaultPlugin instead: this is to try and preserve source-code compatibility when we add fields to this.

Nonetheless, this API is preliminary and highly likely to change in the future.

data TyCon #

TyCons represent type constructors. Type constructors are introduced by things such as:

1) Data declarations: data Foo = ... creates the Foo type constructor of kind *

2) Type synonyms: type Foo = ... creates the Foo type constructor

3) Newtypes: newtype Foo a = MkFoo ... creates the Foo type constructor of kind * -> *

4) Class declarations: class Foo where creates the Foo type constructor of kind *

This data type also encodes a number of primitive, built in type constructors such as those for function and tuple types.

Instances
Eq TyCon 
Instance details

Defined in TyCon

Methods

(==) :: TyCon -> TyCon -> Bool #

(/=) :: TyCon -> TyCon -> Bool #

Data TyCon 
Instance details

Defined in TyCon

Methods

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

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

toConstr :: TyCon -> Constr #

dataTypeOf :: TyCon -> DataType #

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

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

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

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

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

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

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

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

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

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

NamedThing TyCon 
Instance details

Defined in TyCon

Uniquable TyCon 
Instance details

Defined in TyCon

Methods

getUnique :: TyCon -> Unique #

Outputable TyCon 
Instance details

Defined in TyCon

Methods

ppr :: TyCon -> SDoc #

pprPrec :: Rational -> TyCon -> SDoc #

data Type #

Instances
Data Type 
Instance details

Defined in TyCoRep

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable Type 
Instance details

Defined in TyCoRep

Methods

ppr :: Type -> SDoc #

pprPrec :: Rational -> Type -> SDoc #