ghc-9.4.3: The GHC API
Safe HaskellSafe-Inferred
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 Source #

TcPluginM is the monad in which type-checking plugins operate.

Instances

Instances details
MonadFail TcPluginM Source # 
Instance details

Defined in GHC.Tc.Types

Methods

fail :: String -> TcPluginM a Source #

Applicative TcPluginM Source # 
Instance details

Defined in GHC.Tc.Types

Methods

pure :: a -> TcPluginM a Source #

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

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

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

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

Functor TcPluginM Source # 
Instance details

Defined in GHC.Tc.Types

Methods

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

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

Monad TcPluginM Source # 
Instance details

Defined in GHC.Tc.Types

Methods

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

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

return :: a -> TcPluginM a Source #

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.

unsafeTcPluginTcM :: TcM a -> TcPluginM a Source #

This function provides an escape for direct access to the TcM monad. It should not be used lightly, and the provided TcPluginM API should be favoured instead.

Finding Modules and Names

data FindResult Source #

The result of searching for an imported module.

NB: FindResult manages both user source-import lookups (which can result in GenModule) as well as direct imports for interfaces (which always result in InstalledModule).

Constructors

Found ModLocation Module

The module was found

NoPackage Unit

The requested unit was not found

FoundMultiple [(Module, ModuleOrigin)]

_Error_: both in multiple packages

NotFound

Not found

Fields

Looking up Names in the typechecking environment

Getting the TcM state

Type variables

Zonking

Creating constraints

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

Create a new Wanted constraint with the given CtLoc.

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

Create a new given constraint, with the supplied evidence.

This should only be invoked within tcPluginSolve.

newCoercionHole :: PredType -> TcPluginM CoercionHole Source #

Create a fresh coercion hole. This should only be invoked within tcPluginSolve.

Manipulating evidence bindings

newEvVar :: PredType -> TcPluginM EvVar Source #

Create a fresh evidence variable.

This should only be invoked within tcPluginSolve.

setEvBind :: EvBindsVar -> EvBind -> TcPluginM () Source #

Bind an evidence variable.

This should only be invoked within tcPluginSolve.