ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Tc.Plugin

Description

This module provides an interface for typechecker plugins to access select functions of the TcM, principally those to do with reading parts of the state.

Synopsis

Basic TcPluginM functionality

data TcPluginM a #

Instances

Instances details
Monad TcPluginM 
Instance details

Defined in GHC.Tc.Types

Methods

(>>=) :: TcPluginM a -> (a -> TcPluginM b) -> TcPluginM b #

(>>) :: TcPluginM a -> TcPluginM b -> TcPluginM b #

return :: a -> TcPluginM a #

Functor TcPluginM 
Instance details

Defined in GHC.Tc.Types

Methods

fmap :: (a -> b) -> TcPluginM a -> TcPluginM b #

(<$) :: a -> TcPluginM b -> TcPluginM a #

MonadFail TcPluginM 
Instance details

Defined in GHC.Tc.Types

Methods

fail :: String -> TcPluginM a #

Applicative TcPluginM 
Instance details

Defined in GHC.Tc.Types

Methods

pure :: a -> TcPluginM a #

(<*>) :: TcPluginM (a -> b) -> TcPluginM a -> TcPluginM b #

liftA2 :: (a -> b -> c) -> TcPluginM a -> TcPluginM b -> TcPluginM c #

(*>) :: TcPluginM a -> TcPluginM b -> TcPluginM b #

(<*) :: TcPluginM a -> TcPluginM b -> TcPluginM a #

tcPluginIO :: IO a -> TcPluginM a Source #

Perform some IO, typically to interact with an external tool.

tcPluginTrace :: String -> SDoc -> TcPluginM () Source #

Output useful for debugging the compiler.

Finding Modules and Names

data FindResult #

Constructors

Found ModLocation Module 
NoPackage Unit 
FoundMultiple [(Module, ModuleOrigin)] 
NotFound 

Fields

Looking up Names in the typechecking environment

Getting the TcM state

getEnvs :: TcPluginM (TcGblEnv, TcLclEnv) Source #

getFamInstEnvs :: TcPluginM (FamInstEnv, FamInstEnv) Source #

matchFam :: TyCon -> [Type] -> TcPluginM (Maybe (TcCoercion, TcType)) Source #

Type variables

Zonking

zonkCt :: Ct -> TcPluginM Ct Source #

Creating constraints

newWanted :: CtLoc -> PredType -> TcPluginM CtEvidence Source #

Create a new wanted constraint.

newDerived :: CtLoc -> PredType -> TcPluginM CtEvidence Source #

Create a new derived constraint.

newGiven :: CtLoc -> PredType -> EvExpr -> TcPluginM CtEvidence Source #

Create a new given constraint, with the supplied evidence. This must not be invoked from tcPluginInit or tcPluginStop, or it will panic.

newCoercionHole :: PredType -> TcPluginM CoercionHole Source #

Create a fresh coercion hole.

Manipulating evidence bindings

newEvVar :: PredType -> TcPluginM EvVar Source #

Create a fresh evidence variable.

setEvBind :: EvBind -> TcPluginM () Source #

Bind an evidence variable. This must not be invoked from tcPluginInit or tcPluginStop, or it will panic.