Safe Haskell | None |
---|---|
Language | GHC2021 |
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
- data TcPluginM a
- tcPluginIO :: IO a -> TcPluginM a
- tcPluginTrace :: String -> SDoc -> TcPluginM ()
- unsafeTcPluginTcM :: TcM a -> TcPluginM a
- data FindResult
- = Found ModLocation Module
- | NoPackage Unit
- | FoundMultiple [(Module, ModuleOrigin)]
- | NotFound {
- fr_paths :: [FilePath]
- fr_pkg :: Maybe Unit
- fr_mods_hidden :: [Unit]
- fr_pkgs_hidden :: [Unit]
- fr_unusables :: [UnusableUnit]
- fr_suggestions :: [ModuleSuggestion]
- findImportedModule :: ModuleName -> PkgQual -> TcPluginM FindResult
- lookupOrig :: Module -> OccName -> TcPluginM Name
- tcLookupGlobal :: Name -> TcPluginM TyThing
- tcLookupTyCon :: Name -> TcPluginM TyCon
- tcLookupDataCon :: Name -> TcPluginM DataCon
- tcLookupClass :: Name -> TcPluginM Class
- tcLookup :: Name -> TcPluginM TcTyThing
- tcLookupId :: Name -> TcPluginM Id
- getTopEnv :: TcPluginM HscEnv
- getTargetPlatform :: TcPluginM Platform
- getEnvs :: TcPluginM (TcGblEnv, TcLclEnv)
- getInstEnvs :: TcPluginM InstEnvs
- getFamInstEnvs :: TcPluginM (FamInstEnv, FamInstEnv)
- matchFam :: TyCon -> [Type] -> TcPluginM (Maybe Reduction)
- newUnique :: TcPluginM Unique
- newFlexiTyVar :: Kind -> TcPluginM TcTyVar
- isTouchableTcPluginM :: TcTyVar -> TcPluginM Bool
- zonkTcType :: TcType -> TcPluginM TcType
- zonkCt :: Ct -> TcPluginM Ct
- newWanted :: CtLoc -> PredType -> TcPluginM CtEvidence
- newGiven :: EvBindsVar -> CtLoc -> PredType -> EvExpr -> TcPluginM CtEvidence
- newCoercionHole :: PredType -> TcPluginM CoercionHole
- newEvVar :: PredType -> TcPluginM EvVar
- setEvBind :: EvBindsVar -> EvBind -> TcPluginM ()
Basic TcPluginM functionality
TcPluginM
is the monad in which type-checking plugins operate.
tcPluginIO :: IO a -> TcPluginM a Source #
Perform some IO, typically to interact with an external tool.
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 Module
) as well as direct imports
for interfaces (which always result in InstalledModule
).
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 |
|
Looking up Names in the typechecking environment
Getting the TcM state
Type variables
Zonking
zonkTcType :: TcType -> TcPluginM TcType Source #
Confused by zonking? See Note [What is zonking?] in GHC.Tc.Zonk.Type.
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
.