Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
- data TcPluginM a
- tcPluginIO :: IO a -> TcPluginM a
- tcPluginTrace :: String -> SDoc -> TcPluginM ()
- unsafeTcPluginTcM :: TcM a -> TcPluginM a
- data FindResult
- = Found ModLocation Module
- | NoPackage PackageKey
- | FoundMultiple [(Module, ModuleOrigin)]
- | NotFound {
- fr_paths :: [FilePath]
- fr_pkg :: Maybe PackageKey
- fr_mods_hidden :: [PackageKey]
- fr_pkgs_hidden :: [PackageKey]
- fr_suggestions :: [ModuleSuggestion]
- findImportedModule :: ModuleName -> Maybe FastString -> 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
- getEnvs :: TcPluginM (TcGblEnv, TcLclEnv)
- getInstEnvs :: TcPluginM InstEnvs
- getFamInstEnvs :: TcPluginM (FamInstEnv, FamInstEnv)
- matchFam :: TyCon -> [Type] -> TcPluginM (Maybe (TcCoercion, TcType))
- newFlexiTyVar :: Kind -> TcPluginM TcTyVar
- isTouchableTcPluginM :: TcTyVar -> TcPluginM Bool
- zonkTcType :: TcType -> TcPluginM TcType
- zonkCt :: Ct -> TcPluginM Ct
Basic TcPluginM functionality
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
Finding Modules and Names
data FindResult Source
The result of searching for an imported module.
Found ModLocation Module | The module was found |
NoPackage PackageKey | The requested package was not found |
FoundMultiple [(Module, ModuleOrigin)] | _Error_: both in multiple packages |
NotFound | Not found |
|
Looking up Names in the typechecking environment
tcLookupGlobal :: Name -> TcPluginM TyThing Source
tcLookupTyCon :: Name -> TcPluginM TyCon Source
tcLookupClass :: Name -> TcPluginM Class Source
tcLookupId :: Name -> TcPluginM Id Source
Getting the TcM state
Type variables
newFlexiTyVar :: Kind -> TcPluginM TcTyVar Source
Zonking
zonkTcType :: TcType -> TcPluginM TcType Source