Brandon Chinn pushed to branch wip/T21730-import at Glasgow Haskell Compiler / GHC

Commits:

6 changed files:

Changes:

  • compiler/GHC/Driver/Session/Inspect.hs
    ... ... @@ -132,7 +132,7 @@ availsToGlobalRdrEnv hsc_env mod avails
    132 132
           -- all the specified modules into the global interactive module
    
    133 133
         imp_spec = ImpSpec { is_decl = decl, is_item = ImpAll}
    
    134 134
         decl = ImpDeclSpec { is_mod = mod, is_as = moduleName mod,
    
    135
    -                         is_qual = False, is_implicit = False,
    
    135
    +                         is_qual = False,
    
    136 136
                              is_isboot = NotBoot, is_pkg_qual = NoPkgQual,
    
    137 137
                              is_dloc = srcLocSpan interactiveSrcLoc,
    
    138 138
                              is_level = NormalLevel }
    

  • compiler/GHC/Rename/Env.hs
    ... ... @@ -1982,7 +1982,6 @@ lookupQualifiedNameGHCi fos rdr_name
    1982 1982
                                  , is_as = moduleName mod
    
    1983 1983
                                  , is_pkg_qual = NoPkgQual
    
    1984 1984
                                  , is_qual = True
    
    1985
    -                             , is_implicit = False
    
    1986 1985
                                  , is_isboot = NotBoot
    
    1987 1986
                                  , is_dloc = noSrcSpan
    
    1988 1987
                                  , is_level = NormalLevel }
    

  • compiler/GHC/Rename/Names.hs
    ... ... @@ -391,7 +391,7 @@ rnImportDecl this_mod
    391 391
     
    
    392 392
         let imp_mod = mi_module iface
    
    393 393
             qual_mod_name = fmap unLoc as_mod `orElse` imp_mod_name
    
    394
    -        imp_spec  = ImpDeclSpec { is_mod = imp_mod, is_qual = qual_only, is_implicit = implicit,
    
    394
    +        imp_spec  = ImpDeclSpec { is_mod = imp_mod, is_qual = qual_only,
    
    395 395
                                       is_dloc = locA loc, is_as = qual_mod_name,
    
    396 396
                                       is_pkg_qual = pkg_qual, is_isboot = want_boot,
    
    397 397
                                       is_level = convImportLevel import_level }
    
    ... ... @@ -2105,7 +2105,6 @@ data ImportMap = ImportMap
    2105 2105
         -- ^ See [The ImportMap]
    
    2106 2106
         -- If loc :-> gres, then
    
    2107 2107
         --   'loc' = the end loc of the bestImport of each GRE in 'gres'
    
    2108
    -  , im_implicitImports :: Map ModuleName [GlobalRdrElt]
    
    2109 2108
       , im_generatedImports :: Map ModuleName [GlobalRdrElt]
    
    2110 2109
       }
    
    2111 2110
     
    
    ... ... @@ -2113,12 +2112,10 @@ mkImportMap :: [GlobalRdrElt] -> ImportMap
    2113 2112
     -- For each of a list of used GREs, find all the import decls that brought
    
    2114 2113
     -- it into scope; choose one of them (bestImport), and record
    
    2115 2114
     -- the RdrName in that import decl's entry in the ImportMap
    
    2116
    -mkImportMap = foldr insertImportMap $ ImportMap Map.empty Map.empty Map.empty
    
    2115
    +mkImportMap = foldr insertImportMap $ ImportMap Map.empty Map.empty
    
    2117 2116
     
    
    2118 2117
     insertImportMap :: GlobalRdrElt -> ImportMap -> ImportMap
    
    2119 2118
     insertImportMap gre@(GRE { gre_imp = imp_specs }) importMap
    
    2120
    -  | is_implicit best_imp_spec =
    
    2121
    -      importMap{im_implicitImports = insertElem (moduleName $ is_mod best_imp_spec) gre $ im_implicitImports importMap}
    
    2122 2119
       | RealSrcSpan importSpan _ <- is_dloc best_imp_spec =
    
    2123 2120
           importMap{im_imports = insertElem importSpan gre $ im_imports importMap}
    
    2124 2121
       | UnhelpfulSpan UnhelpfulGenerated <- is_dloc best_imp_spec =
    
    ... ... @@ -2141,7 +2138,6 @@ lookupImportMap (L srcSpan ImportDecl{ideclName = L _ modName}) importMap =
    2141 2138
       fromMaybe [] $
    
    2142 2139
         -- should match logic in insertImportMap
    
    2143 2140
         case locA srcSpan of
    
    2144
    -      _ | Just gres <- modName `Map.lookup` im_implicitImports importMap -> Just gres
    
    2145 2141
           RealSrcSpan realSrcSpan _ -> realSrcSpan `Map.lookup` im_imports importMap
    
    2146 2142
           UnhelpfulSpan UnhelpfulGenerated -> modName `Map.lookup` im_generatedImports importMap
    
    2147 2143
           _ -> Nothing
    

  • compiler/GHC/Runtime/Loader.hs
    ... ... @@ -354,7 +354,7 @@ lookupRdrNameInModuleForPlugins hsc_env mod_name rdr_name = do
    354 354
                     Just iface -> do
    
    355 355
                         -- Try and find the required name in the exports
    
    356 356
                         let decl_spec = ImpDeclSpec { is_mod = mod, is_as = mod_name, is_pkg_qual = NoPkgQual
    
    357
    -                                                , is_qual = False, is_implicit = False
    
    357
    +                                                , is_qual = False
    
    358 358
                                                     , is_dloc = noSrcSpan, is_isboot = NotBoot, is_level = SpliceLevel }
    
    359 359
                             imp_spec = ImpSpec decl_spec ImpAll
    
    360 360
                             env = mkGlobalRdrEnv
    

  • compiler/GHC/Tc/Utils/Backpack.hs
    ... ... @@ -633,7 +633,6 @@ mergeSignatures
    633 633
                                                 is_as       = mod_name,
    
    634 634
                                                 is_pkg_qual = NoPkgQual,
    
    635 635
                                                 is_qual     = False,
    
    636
    -                                            is_implicit = False,
    
    637 636
                                                 is_isboot   = NotBoot,
    
    638 637
                                                 is_dloc     = locA loc,
    
    639 638
                                                 is_level    = NormalLevel
    

  • compiler/GHC/Types/Name/Reader.hs
    ... ... @@ -1821,7 +1821,6 @@ shadowNames drop_only_qualified env new_gres = minusOccEnv_C_Ns do_shadowing env
    1821 1821
                                        , is_as = old_mod_name
    
    1822 1822
                                        , is_pkg_qual = NoPkgQual
    
    1823 1823
                                        , is_qual = True
    
    1824
    -                                   , is_implicit = False
    
    1825 1824
                                        , is_level = NormalLevel -- MP: Not 100% sure this is correct
    
    1826 1825
                                        , is_isboot = NotBoot
    
    1827 1826
                                        , is_dloc = greDefinitionSrcSpan old_gre }
    
    ... ... @@ -1984,7 +1983,6 @@ data ImpDeclSpec
    1984 1983
             is_as       :: !ModuleName, -- ^ Import alias, e.g. from @as M@ (or @Muggle@ if there is no @as@ clause)
    
    1985 1984
             is_pkg_qual :: !PkgQual,    -- ^ Was this a package import?
    
    1986 1985
             is_qual     :: !Bool,       -- ^ Was this import qualified?
    
    1987
    -        is_implicit :: !Bool,       -- ^ Was this import implicit? See Note [Implicit imports] in GHC.Hs.ImpExp
    
    1988 1986
             is_dloc     :: !SrcSpan,    -- ^ The location of the entire import declaration
    
    1989 1987
             is_isboot   :: !IsBootInterface, -- ^ Was this a SOURCE import?
    
    1990 1988
             is_level    :: !ImportLevel -- ^ Was this import level modified? splice/quote +-1
    
    ... ... @@ -1997,12 +1995,11 @@ instance NFData ImpDeclSpec where
    1997 1995
     
    
    1998 1996
     
    
    1999 1997
     instance Binary ImpDeclSpec where
    
    2000
    -  put_ bh (ImpDeclSpec mod as pkg_qual qual implicit _dloc isboot isstage) = do
    
    1998
    +  put_ bh (ImpDeclSpec mod as pkg_qual qual _dloc isboot isstage) = do
    
    2001 1999
         put_ bh mod
    
    2002 2000
         put_ bh as
    
    2003 2001
         put_ bh pkg_qual
    
    2004 2002
         put_ bh qual
    
    2005
    -    put_ bh implicit
    
    2006 2003
         put_ bh isboot
    
    2007 2004
         put_ bh (fromEnum isstage)
    
    2008 2005
     
    
    ... ... @@ -2011,10 +2008,9 @@ instance Binary ImpDeclSpec where
    2011 2008
         as <- get bh
    
    2012 2009
         pkg_qual <- get bh
    
    2013 2010
         qual <- get bh
    
    2014
    -    implicit <- get bh
    
    2015 2011
         isboot <- get bh
    
    2016 2012
         isstage <- toEnum <$> get bh
    
    2017
    -    return (ImpDeclSpec mod as pkg_qual qual implicit noSrcSpan isboot isstage)
    
    2013
    +    return (ImpDeclSpec mod as pkg_qual qual noSrcSpan isboot isstage)
    
    2018 2014
     
    
    2019 2015
     -- | Import Item Specification
    
    2020 2016
     --