Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- tcRnStmt :: HscEnv -> GhciLStmt GhcPs -> IO (Messages, Maybe ([Id], LHsExpr GhcTc, FixityEnv))
- tcRnExpr :: HscEnv -> TcRnExprMode -> LHsExpr GhcPs -> IO (Messages, Maybe Type)
- data TcRnExprMode
- tcRnType :: HscEnv -> ZonkFlexi -> Bool -> LHsType GhcPs -> IO (Messages, Maybe (Type, Kind))
- tcRnImportDecls :: HscEnv -> [LImportDecl GhcPs] -> IO (Messages, Maybe GlobalRdrEnv)
- tcRnLookupRdrName :: HscEnv -> Located RdrName -> IO (Messages, Maybe [Name])
- getModuleInterface :: HscEnv -> Module -> IO (Messages, Maybe ModIface)
- tcRnDeclsi :: HscEnv -> [LHsDecl GhcPs] -> IO (Messages, Maybe TcGblEnv)
- isGHCiMonad :: HscEnv -> String -> IO (Messages, Maybe Name)
- runTcInteractive :: HscEnv -> TcRn a -> IO (Messages, Maybe a)
- tcRnLookupName :: HscEnv -> Name -> IO (Messages, Maybe TyThing)
- tcRnGetInfo :: HscEnv -> Name -> IO (Messages, Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc))
- tcRnModule :: HscEnv -> ModSummary -> Bool -> HsParsedModule -> IO (Messages, Maybe TcGblEnv)
- tcRnModuleTcRnM :: HscEnv -> ModSummary -> HsParsedModule -> (Module, SrcSpan) -> TcRn TcGblEnv
- tcTopSrcDecls :: HsGroup GhcRn -> TcM (TcGblEnv, TcLclEnv)
- rnTopSrcDecls :: HsGroup GhcPs -> TcM (TcGblEnv, HsGroup GhcRn)
- checkBootDecl :: Bool -> TyThing -> TyThing -> Maybe SDoc
- checkHiBootIface' :: [ClsInst] -> TypeEnv -> [AvailInfo] -> ModDetails -> TcM [(Id, Id)]
- findExtraSigImports :: HscEnv -> HscSource -> ModuleName -> IO [(Maybe FastString, Located ModuleName)]
- implicitRequirements :: HscEnv -> [(Maybe FastString, Located ModuleName)] -> IO [(Maybe FastString, Located ModuleName)]
- checkUnitId :: UnitId -> TcM ()
- mergeSignatures :: HsParsedModule -> TcGblEnv -> ModIface -> TcRn TcGblEnv
- tcRnMergeSignatures :: HscEnv -> HsParsedModule -> TcGblEnv -> ModIface -> IO (Messages, Maybe TcGblEnv)
- instantiateSignature :: TcRn TcGblEnv
- tcRnInstantiateSignature :: HscEnv -> Module -> RealSrcSpan -> IO (Messages, Maybe TcGblEnv)
- loadUnqualIfaces :: HscEnv -> InteractiveContext -> TcM ()
- badReexportedBootThing :: DynFlags -> Bool -> Name -> Name -> SDoc
- checkBootDeclM :: Bool -> TyThing -> TyThing -> TcM ()
- missingBootThing :: Bool -> Name -> String -> SDoc
- getRenamedStuff :: TcGblEnv -> RenamedStuff
- type RenamedStuff = Maybe (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString)
Documentation
tcRnStmt :: HscEnv -> GhciLStmt GhcPs -> IO (Messages, Maybe ([Id], LHsExpr GhcTc, FixityEnv)) Source #
The returned [Id] is the list of new Ids bound by this statement. It can be used to extend the InteractiveContext via extendInteractiveContext.
The returned TypecheckedHsExpr is of type IO [ () ], a list of the bound values, coerced to ().
tcRnExpr :: HscEnv -> TcRnExprMode -> LHsExpr GhcPs -> IO (Messages, Maybe Type) Source #
tcRnExpr just finds the type of an expression
data TcRnExprMode Source #
How should we infer a type? See Note [TcRnExprMode]
TM_Inst | Instantiate the type fully (:type) |
TM_NoInst | Do not instantiate the type (:type +v) |
TM_Default | Default the type eagerly (:type +d) |
tcRnType :: HscEnv -> ZonkFlexi -> Bool -> LHsType GhcPs -> IO (Messages, Maybe (Type, Kind)) Source #
tcRnImportDecls :: HscEnv -> [LImportDecl GhcPs] -> IO (Messages, Maybe GlobalRdrEnv) Source #
tcRnLookupRdrName :: HscEnv -> Located RdrName -> IO (Messages, Maybe [Name]) Source #
Find all the Names that this RdrName could mean, in GHCi
getModuleInterface :: HscEnv -> Module -> IO (Messages, Maybe ModIface) Source #
ASSUMES that the module is either in the HomePackageTable
or is
a package module with an interface on disk. If neither of these is
true, then the result will be an error indicating the interface
could not be found.
tcRnGetInfo :: HscEnv -> Name -> IO (Messages, Maybe (TyThing, Fixity, [ClsInst], [FamInst], SDoc)) Source #
tcRnModule :: HscEnv -> ModSummary -> Bool -> HsParsedModule -> IO (Messages, Maybe TcGblEnv) Source #
Top level entry point for typechecker and renamer
tcRnModuleTcRnM :: HscEnv -> ModSummary -> HsParsedModule -> (Module, SrcSpan) -> TcRn TcGblEnv Source #
checkBootDecl :: Bool -> TyThing -> TyThing -> Maybe SDoc Source #
Compares the two things for equivalence between boot-file and normal
code. Returns Nothing
on success or Just "some helpful info for user"
failure. If the difference will be apparent to the user, Just empty
is
perfectly suitable.
checkHiBootIface' :: [ClsInst] -> TypeEnv -> [AvailInfo] -> ModDetails -> TcM [(Id, Id)] Source #
findExtraSigImports :: HscEnv -> HscSource -> ModuleName -> IO [(Maybe FastString, Located ModuleName)] Source #
findExtraSigImports
, but in a convenient form for GhcMake and
TcRnDriver.
implicitRequirements :: HscEnv -> [(Maybe FastString, Located ModuleName)] -> IO [(Maybe FastString, Located ModuleName)] Source #
checkUnitId :: UnitId -> TcM () Source #
Given a UnitId
, make sure it is well typed. This is because
unit IDs come from Cabal, which does not know if things are well-typed or
not; a component may have been filled with implementations for the holes
that don't actually fulfill the requirements.
INVARIANT: the UnitId is NOT a InstalledUnitId
mergeSignatures :: HsParsedModule -> TcGblEnv -> ModIface -> TcRn TcGblEnv Source #
tcRnMergeSignatures :: HscEnv -> HsParsedModule -> TcGblEnv -> ModIface -> IO (Messages, Maybe TcGblEnv) Source #
Top-level driver for signature merging (run after typechecking
an hsig
file).
tcRnInstantiateSignature :: HscEnv -> Module -> RealSrcSpan -> IO (Messages, Maybe TcGblEnv) Source #
Top-level driver for signature instantiation (run when compiling
an hsig
file.)
loadUnqualIfaces :: HscEnv -> InteractiveContext -> TcM () Source #
Compares two things for equivalence between boot-file and normal code, reporting an error if they don't match up.
getRenamedStuff :: TcGblEnv -> RenamedStuff Source #
Extract the renamed information from TcGblEnv.
type RenamedStuff = Maybe (HsGroup GhcRn, [LImportDecl GhcRn], Maybe [(LIE GhcRn, Avails)], Maybe LHsDocString) Source #