Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- rnImports :: [(LImportDecl GhcPs, SDoc)] -> RnM ([LImportDecl GhcRn], GlobalRdrEnv, ImportAvails, AnyHpcUsage)
- getLocalNonValBinders :: MiniFixityEnv -> HsGroup GhcPs -> RnM ((TcGblEnv, TcLclEnv), NameSet)
- newRecordFieldLabel :: DuplicateRecordFields -> FieldSelectors -> [Name] -> LFieldOcc GhcPs -> RnM FieldLabel
- extendGlobalRdrEnvRn :: [GlobalRdrElt] -> MiniFixityEnv -> RnM (TcGblEnv, TcLclEnv)
- gresFromAvails :: HscEnv -> Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt]
- calculateAvails :: HomeUnit -> Set UnitId -> ModIface -> IsSafeImport -> IsBootInterface -> ImportedBy -> ImportAvails
- reportUnusedNames :: TcGblEnv -> HscSource -> RnM ()
- checkConName :: RdrName -> TcRn ()
- mkChildEnv :: [GlobalRdrElt] -> NameEnv [GlobalRdrElt]
- findChildren :: NameEnv [a] -> Name -> [a]
- findImportUsage :: [LImportDecl GhcRn] -> [GlobalRdrElt] -> [ImportDeclUsage]
- getMinimalImports :: [ImportDeclUsage] -> RnM [LImportDecl GhcRn]
- printMinimalImports :: HscSource -> [ImportDeclUsage] -> RnM ()
- renamePkgQual :: UnitEnv -> ModuleName -> Maybe FastString -> PkgQual
- renameRawPkgQual :: UnitEnv -> ModuleName -> RawPkgQual -> PkgQual
- classifyGREs :: [GlobalRdrElt] -> ([GlobalRdrElt], [FieldGlobalRdrElt])
- type ImportDeclUsage = (LImportDecl GhcRn, [GlobalRdrElt], [Name])
Documentation
rnImports :: [(LImportDecl GhcPs, SDoc)] -> RnM ([LImportDecl GhcRn], GlobalRdrEnv, ImportAvails, AnyHpcUsage) Source #
Process Import Decls. See rnImportDecl
for a description of what
the return types represent.
Note: Do the non SOURCE ones first, so that we get a helpful warning
for SOURCE ones that are unnecessary
getLocalNonValBinders :: MiniFixityEnv -> HsGroup GhcPs -> RnM ((TcGblEnv, TcLclEnv), NameSet) Source #
newRecordFieldLabel :: DuplicateRecordFields -> FieldSelectors -> [Name] -> LFieldOcc GhcPs -> RnM FieldLabel Source #
extendGlobalRdrEnvRn :: [GlobalRdrElt] -> MiniFixityEnv -> RnM (TcGblEnv, TcLclEnv) Source #
gresFromAvails :: HscEnv -> Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt] Source #
All the GlobalRdrElt
s associated with a collection of AvailInfo
s.
calculateAvails :: HomeUnit -> Set UnitId -> ModIface -> IsSafeImport -> IsBootInterface -> ImportedBy -> ImportAvails Source #
Calculate the ImportAvails
induced by an import of a particular
interface, but without imp_mods
.
checkConName :: RdrName -> TcRn () Source #
mkChildEnv :: [GlobalRdrElt] -> NameEnv [GlobalRdrElt] Source #
findChildren :: NameEnv [a] -> Name -> [a] Source #
findImportUsage :: [LImportDecl GhcRn] -> [GlobalRdrElt] -> [ImportDeclUsage] Source #
getMinimalImports :: [ImportDeclUsage] -> RnM [LImportDecl GhcRn] Source #
printMinimalImports :: HscSource -> [ImportDeclUsage] -> RnM () Source #
renamePkgQual :: UnitEnv -> ModuleName -> Maybe FastString -> PkgQual Source #
Rename raw package imports
renameRawPkgQual :: UnitEnv -> ModuleName -> RawPkgQual -> PkgQual Source #
Rename raw package imports
classifyGREs :: [GlobalRdrElt] -> ([GlobalRdrElt], [FieldGlobalRdrElt]) Source #
type ImportDeclUsage = (LImportDecl GhcRn, [GlobalRdrElt], [Name]) Source #