Skip to content
Snippets Groups Projects
Unverified Commit d8b79d35 authored by Sylvain Henry's avatar Sylvain Henry Committed by GitHub
Browse files

Fix after PkgQual refactoring (#1429)

parent a0938c6c
No related branches found
No related tags found
5 merge requests!38Make --no-tmp-comp-dir the default,!37Adapt to latest xhtml version, various optimizations,!31Support HsToken in DataDecl and ClassDecl,!12Drop orphan instance when defined upstream.,!10Haddock interfaces produced from `.hi` files
......@@ -59,7 +59,6 @@ import GHC.Data.FastString (bytesFS, unpackFS)
import GHC.Driver.Ppr (showSDoc)
import GHC.HsToCore.Docs hiding (mkMaps)
import GHC.IORef (readIORef)
import GHC.Parser.Annotation (IsUnicodeSyntax (..))
import GHC.Stack (HasCallStack)
import GHC.Tc.Types hiding (IfM)
import GHC.Tc.Utils.Monad (finalSafeMode)
......@@ -72,14 +71,13 @@ import GHC.Types.Name.Reader (GlobalRdrEnv, greMangledName, lookupGlobalRdrEnv)
import GHC.Types.Name.Set (elemNameSet, mkNameSet)
import GHC.Types.SourceFile (HscSource (..))
import GHC.Types.SourceText (SourceText (..), sl_fs)
import GHC.Unit.Types
import qualified GHC.Types.SrcLoc as SrcLoc
import qualified GHC.Unit.Module as Module
import GHC.Unit.Module.ModSummary (msHsFilePath)
import GHC.Unit.Module.Warnings (WarningTxt (..), Warnings (..))
import GHC.Unit.State (PackageName (..), UnitState, lookupModuleInAllUnits)
import qualified GHC.Utils.Outputable as O
import GHC.Utils.Panic (pprPanic)
import GHC.HsToCore.Docs hiding (mkMaps)
import GHC.Unit.Module.Warnings
newtype IfEnv m = IfEnv
......@@ -351,8 +349,7 @@ mkAliasMap state impDecls =
-- them to the user. We should reuse that information;
-- or at least reuse the renamed imports, which know what
-- they import!
(fmap Module.fsToUnit $
fmap sl_fs $ ideclPkgQual impDecl)
(ideclPkgQual impDecl)
(case ideclName impDecl of SrcLoc.L _ name -> name),
alias))
impDecls
......@@ -395,11 +392,11 @@ unrestrictedModuleImports idecls =
-- Similar to GHC.lookupModule
-- ezyang: Not really...
lookupModuleDyn ::
UnitState -> Maybe Unit -> ModuleName -> Module
lookupModuleDyn _ (Just pkgId) mdlName =
Module.mkModule pkgId mdlName
lookupModuleDyn state Nothing mdlName =
case lookupModuleInAllUnits state mdlName of
UnitState -> PkgQual -> ModuleName -> Module
lookupModuleDyn state pkg_qual mdlName = case pkg_qual of
OtherPkg uid -> Module.mkModule (RealUnit (Definite uid)) mdlName
ThisPkg uid -> Module.mkModule (RealUnit (Definite uid)) mdlName
NoPkgQual -> case lookupModuleInAllUnits state mdlName of
(m,_):_ -> m
[] -> Module.mkModule Module.mainUnit mdlName
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment