[commit: ghc] ghc-8.2: Fix crash in isModuleInterpreted for HsBoot (fixes #13591) (f3ce368)

git at git.haskell.org git at git.haskell.org
Tue May 16 01:12:17 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : ghc-8.2
Link       : http://ghc.haskell.org/trac/ghc/changeset/f3ce36846bd3da3d957810f05d387d7699cd23e1/ghc

>---------------------------------------------------------------

commit f3ce36846bd3da3d957810f05d387d7699cd23e1
Author: Lennart Spitzner <lsp at informatik.uni-kiel.de>
Date:   Wed May 10 16:47:19 2017 +0200

    Fix crash in isModuleInterpreted for HsBoot (fixes #13591)
    
    Rename isModuleInterpreted to moduleIsBootOrNotObjectLinkable
    because a) there already is a moduleIsInterpreted function in
    the same module b) I have no idea if the (new) semantic of
    the bool returned matches some understanding of
    "is interpreted".
    
    (cherry picked from commit 1edee7a8b5ca24156cb6e21bde6d611a0ba63882)


>---------------------------------------------------------------

f3ce36846bd3da3d957810f05d387d7699cd23e1
 compiler/main/GHC.hs             |  2 +-
 compiler/main/InteractiveEval.hs | 14 +++++++-------
 ghc/GHCi/UI.hs                   |  2 +-
 3 files changed, 9 insertions(+), 9 deletions(-)

diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs
index 53e135c..0f7acbf 100644
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -112,7 +112,7 @@ module GHC (
         moduleIsInterpreted,
         getInfo,
         showModule,
-        isModuleInterpreted,
+        moduleIsBootOrNotObjectLinkable,
 
         -- ** Inspecting types and kinds
         exprType, TcRnExprMode(..),
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index 1fa2698..0d83b48 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -31,7 +31,7 @@ module InteractiveEval (
         typeKind,
         parseName,
         showModule,
-        isModuleInterpreted,
+        moduleIsBootOrNotObjectLinkable,
         parseExpr, compileParsedExpr,
         compileExpr, dynCompileExpr,
         compileExprRemote, compileParsedExprRemote,
@@ -901,17 +901,17 @@ dynCompileExpr expr = do
 showModule :: GhcMonad m => ModSummary -> m String
 showModule mod_summary =
     withSession $ \hsc_env -> do
-        interpreted <- isModuleInterpreted mod_summary
+        interpreted <- moduleIsBootOrNotObjectLinkable mod_summary
         let dflags = hsc_dflags hsc_env
         return (showModMsg dflags (hscTarget dflags) interpreted mod_summary)
 
-isModuleInterpreted :: GhcMonad m => ModSummary -> m Bool
-isModuleInterpreted mod_summary = withSession $ \hsc_env ->
+moduleIsBootOrNotObjectLinkable :: GhcMonad m => ModSummary -> m Bool
+moduleIsBootOrNotObjectLinkable mod_summary = withSession $ \hsc_env ->
   case lookupHpt (hsc_HPT hsc_env) (ms_mod_name mod_summary) of
         Nothing       -> panic "missing linkable"
-        Just mod_info -> return (not obj_linkable)
-                      where
-                         obj_linkable = isObjectLinkable (expectJust "showModule" (hm_linkable mod_info))
+        Just mod_info -> return $ case hm_linkable mod_info of
+          Nothing       -> True
+          Just linkable -> not (isObjectLinkable linkable)
 
 ----------------------------------------------------------------------------
 -- RTTI primitives
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs
index 44f0935..a509f28 100644
--- a/ghc/GHCi/UI.hs
+++ b/ghc/GHCi/UI.hs
@@ -1801,7 +1801,7 @@ modulesLoadedMsg ok mods = do
   dflags <- getDynFlags
   unqual <- GHC.getPrintUnqual
   let mod_name mod = do
-        is_interpreted <- GHC.isModuleInterpreted mod
+        is_interpreted <- GHC.moduleIsBootOrNotObjectLinkable mod
         return $ if is_interpreted
                   then ppr (GHC.ms_mod mod)
                   else ppr (GHC.ms_mod mod)



More information about the ghc-commits mailing list