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

Commits:

5 changed files:

Changes:

  • compiler/GHC/Runtime/Eval.hs
    ... ... @@ -78,7 +78,7 @@ import GHC.Core.Type hiding( typeKind )
    78 78
     import qualified GHC.Core.Type as Type
    
    79 79
     
    
    80 80
     import GHC.Iface.Env       ( newInteractiveBinder )
    
    81
    -import GHC.Iface.Load      ( loadSrcInterface )
    
    81
    +import GHC.Iface.Load      ( loadInterfaceForModule )
    
    82 82
     import GHC.Tc.Utils.TcType
    
    83 83
     import GHC.Tc.Types.Constraint
    
    84 84
     import GHC.Tc.Types.Origin
    
    ... ... @@ -843,7 +843,7 @@ mkTopLevEnv hsc_env modl
    843 843
                           $ fmap (foldr plusGlobalRdrEnv emptyGlobalRdrEnv)
    
    844 844
                           $ forM imports $ \iface_import -> do
    
    845 845
                             let ImpUserSpec spec details = tcIfaceImport iface_import
    
    846
    -                        iface <- loadSrcInterface (text "imported by GHCi") (moduleName $ is_mod spec) (is_isboot spec) (is_pkg_qual spec)
    
    846
    +                        iface <- loadInterfaceForModule (text "imported by GHCi") (is_mod spec)
    
    847 847
                             pure $ case details of
    
    848 848
                               ImpUserAll -> importsFromIface hsc_env iface spec Nothing
    
    849 849
                               ImpUserEverythingBut ns -> importsFromIface hsc_env iface spec (Just ns)
    

  • testsuite/tests/ghci/scripts/GhciPackageRename.hs
    1
    +module GhciPackageRename where
    
    2
    +
    
    3
    +foo :: Map k v
    
    4
    +foo = empty
    \ No newline at end of file

  • testsuite/tests/ghci/scripts/GhciPackageRename.script
    1
    +:l GhciPackageRename.hs
    
    2
    +-- Test that Data.Map is available as Prelude
    
    3
    +:t fromList
    
    4
    +
    
    5
    +-- Test using a Map function
    
    6
    +fromList [(1,"a"), (2,"b")]
    \ No newline at end of file

  • testsuite/tests/ghci/scripts/GhciPackageRename.stdout
    1
    +fromList
    
    2
    +  :: ghc-internal:GHC.Internal.Classes.Ord k => [(k, a)] -> Map k a
    
    3
    +fromList [(1,"a"),(2,"b")]

  • testsuite/tests/ghci/scripts/all.T
    ... ... @@ -386,3 +386,9 @@ test('T13869', extra_files(['T13869a.hs', 'T13869b.hs']), ghci_script, ['T13869.
    386 386
     test('ListTuplePunsPpr', normal, ghci_script, ['ListTuplePunsPpr.script'])
    
    387 387
     test('ListTuplePunsPprNoAbbrevTuple', [expect_broken(23135), limit_stdout_lines(13)], ghci_script, ['ListTuplePunsPprNoAbbrevTuple.script'])
    
    388 388
     test('T24459', normal, ghci_script, ['T24459.script'])
    
    389
    +
    
    390
    +# Test package renaming in GHCi session
    
    391
    +test('GhciPackageRename',
    
    392
    +     [extra_hc_opts("-hide-all-packages -package 'containers (Data.Map as Prelude)'")],
    
    393
    +     ghci_script,
    
    394
    +     ['GhciPackageRename.script'])