Copyright | (C) 2015-2016 University of Twente |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Extensions |
|
Synopsis
- newWanted :: CtLoc -> PredType -> TcPluginM CtEvidence
- newGiven :: CtLoc -> PredType -> EvTerm -> TcPluginM CtEvidence
- newDerived :: CtLoc -> PredType -> TcPluginM CtEvidence
- evByFiat :: String -> Type -> Type -> EvTerm
- lookupModule :: ModuleName -> FastString -> TcPluginM Module
- lookupName :: Module -> OccName -> TcPluginM Name
- tracePlugin :: String -> TcPlugin -> TcPlugin
- flattenGivens :: [Ct] -> [Ct]
- mkSubst :: Ct -> Maybe (TcTyVar, TcType)
- mkSubst' :: [Ct] -> [(TcTyVar, TcType)]
- substType :: [(TcTyVar, TcType)] -> TcType -> TcType
- substCt :: [(TcTyVar, TcType)] -> Ct -> Ct
Create new constraints
newGiven :: CtLoc -> PredType -> EvTerm -> TcPluginM CtEvidence Source #
Create a new [G]iven constraint, with the supplied evidence. This must not
be invoked from tcPluginInit
or tcPluginStop
, or it will panic.
newDerived :: CtLoc -> PredType -> TcPluginM CtEvidence Source #
Create a new [D]erived constraint.
Creating evidence
:: String | Name the coercion should have |
-> Type | The LHS of the equivalence relation (~) |
-> Type | The RHS of the equivalence relation (~) |
-> EvTerm |
The EvTerm
equivalent for unsafeCoerce
Lookup
:: ModuleName | Name of the module |
-> FastString | Name of the package containing the module |
-> TcPluginM Module |
Find a module
Trace state of the plugin
tracePlugin :: String -> TcPlugin -> TcPlugin Source #
Print out extra information about the initialisation, stop, and every run
of the plugin when -ddump-tc-trace
is enabled.
Substitutions (GHC 8.4+)
flattenGivens :: [Ct] -> [Ct] Source #
Flattens evidence of constraints by substituting each others equalities.
NB: Should only be used on [G]iven constraints!
NB: Doesn't flatten under binders
NB: Only available on GHC 8.4+
mkSubst :: Ct -> Maybe (TcTyVar, TcType) Source #
Create simple substitution from type equalities
NB: Only available on GHC 8.4+
mkSubst' :: [Ct] -> [(TcTyVar, TcType)] Source #
Create flattened substitutions from type equalities, i.e. the substitutions have been applied to each others right hand sides.
NB: Only available on GHC 8.4+