Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

2 changed files:

Changes:

  • compiler/GHC/Runtime/Eval.hs
    ... ... @@ -23,7 +23,7 @@ module GHC.Runtime.Eval (
    23 23
             setupBreakpoint,
    
    24 24
             back, forward,
    
    25 25
             setContext, getContext,
    
    26
    -        mkTopLevEnv,
    
    26
    +        mkTopLevEnv, mkTopLevImportedEnv,
    
    27 27
             getNamesInScope,
    
    28 28
             getRdrNamesInScope,
    
    29 29
             moduleIsInterpreted,
    
    ... ... @@ -836,29 +836,36 @@ mkTopLevEnv hsc_env modl
    836 836
           Nothing -> pure $ Left "not a home module"
    
    837 837
           Just details ->
    
    838 838
              case mi_top_env (hm_iface details) of
    
    839
    -                (IfaceTopEnv exports imports) -> do
    
    840
    -                  imports_env <-
    
    841
    -                        runInteractiveHsc hsc_env
    
    842
    -                      $ ioMsgMaybe $ hoistTcRnMessage $ runTcInteractive hsc_env
    
    843
    -                      $ fmap (foldr plusGlobalRdrEnv emptyGlobalRdrEnv)
    
    844
    -                      $ forM imports $ \iface_import -> do
    
    845
    -                        let ImpUserSpec spec details = tcIfaceImport iface_import
    
    846
    -                        iface <- loadInterfaceForModule (text "imported by GHCi") (is_mod spec)
    
    847
    -                        pure $ case details of
    
    848
    -                          ImpUserAll -> importsFromIface hsc_env iface spec Nothing
    
    849
    -                          ImpUserEverythingBut ns -> importsFromIface hsc_env iface spec (Just ns)
    
    850
    -                          ImpUserExplicit x _parents_of_implicits ->
    
    851
    -                            -- TODO: Not quite right, is_explicit should refer to whether the user wrote A(..) or A(x,y).
    
    852
    -                            -- It is only used for error messages. It seems dubious even to add an import context to these GREs as
    
    853
    -                            -- they are not "imported" into the top-level scope of the REPL. I changed this for now so that
    
    854
    -                            -- the test case produce the same output as before.
    
    855
    -                            let spec' = ImpSpec { is_decl = spec, is_item = ImpSome { is_explicit = True, is_iloc = noSrcSpan } }
    
    856
    -                            in mkGlobalRdrEnv $ gresFromAvails hsc_env (Just spec') x
    
    839
    +                (IfaceTopEnv exports _imports) -> do
    
    840
    +                  imports_env <- mkTopLevImportedEnv hsc_env details
    
    857 841
                       let exports_env = mkGlobalRdrEnv $ gresFromAvails hsc_env Nothing (getDetOrdAvails exports)
    
    858 842
                       pure $ Right $ plusGlobalRdrEnv imports_env exports_env
    
    859 843
       where
    
    860 844
         hpt = hsc_HPT hsc_env
    
    861 845
     
    
    846
    +-- | Make the top-level environment with all bindings imported by this module.
    
    847
    +-- Exported bindings from this module are not included in the result.
    
    848
    +mkTopLevImportedEnv :: HscEnv -> HomeModInfo -> IO GlobalRdrEnv
    
    849
    +mkTopLevImportedEnv hsc_env details = do
    
    850
    +    runInteractiveHsc hsc_env
    
    851
    +  $ ioMsgMaybe $ hoistTcRnMessage $ runTcInteractive hsc_env
    
    852
    +  $ fmap (foldr plusGlobalRdrEnv emptyGlobalRdrEnv)
    
    853
    +  $ forM imports $ \iface_import -> do
    
    854
    +    let ImpUserSpec spec details = tcIfaceImport iface_import
    
    855
    +    iface <- loadInterfaceForModule (text "imported by GHCi") (is_mod spec)
    
    856
    +    pure $ case details of
    
    857
    +      ImpUserAll -> importsFromIface hsc_env iface spec Nothing
    
    858
    +      ImpUserEverythingBut ns -> importsFromIface hsc_env iface spec (Just ns)
    
    859
    +      ImpUserExplicit x _parents_of_implicits ->
    
    860
    +        -- TODO: Not quite right, is_explicit should refer to whether the user wrote A(..) or A(x,y).
    
    861
    +        -- It is only used for error messages. It seems dubious even to add an import context to these GREs as
    
    862
    +        -- they are not "imported" into the top-level scope of the REPL. I changed this for now so that
    
    863
    +        -- the test case produce the same output as before.
    
    864
    +        let spec' = ImpSpec { is_decl = spec, is_item = ImpSome { is_explicit = True, is_iloc = noSrcSpan } }
    
    865
    +        in mkGlobalRdrEnv $ gresFromAvails hsc_env (Just spec') x
    
    866
    +  where
    
    867
    +    IfaceTopEnv _ imports = mi_top_env (hm_iface details)
    
    868
    +
    
    862 869
     -- | Get the interactive evaluation context, consisting of a pair of the
    
    863 870
     -- set of modules from which we take the full top-level scope, and the set
    
    864 871
     -- of modules from which we take just the exports respectively.
    

  • compiler/GHC/Types/Name/Occurrence.hs
    ... ... @@ -92,6 +92,7 @@ module GHC.Types.Name.Occurrence (
    92 92
             plusOccEnv, plusOccEnv_C,
    
    93 93
             extendOccEnv_Acc, filterOccEnv, delListFromOccEnv, delFromOccEnv,
    
    94 94
             alterOccEnv, minusOccEnv, minusOccEnv_C, minusOccEnv_C_Ns,
    
    95
    +        sizeOccEnv,
    
    95 96
             pprOccEnv, forceOccEnv,
    
    96 97
             intersectOccEnv_C,
    
    97 98
     
    
    ... ... @@ -803,6 +804,10 @@ minusOccEnv_C_Ns f (MkOccEnv as) (MkOccEnv bs) =
    803 804
                then Nothing
    
    804 805
                else Just m
    
    805 806
     
    
    807
    +sizeOccEnv :: OccEnv a -> Int
    
    808
    +sizeOccEnv (MkOccEnv as) =
    
    809
    +  nonDetStrictFoldUFM (\ m !acc -> acc + sizeUFM m) 0 as
    
    810
    +
    
    806 811
     instance Outputable a => Outputable (OccEnv a) where
    
    807 812
         ppr x = pprOccEnv ppr x
    
    808 813