[commit: ghc] ghc-8.0: Fix renamer panic (8736625)

git at git.haskell.org git at git.haskell.org
Mon Jul 25 18:36:50 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/8736625f143d55616e76ff660d476ce4a9cdb2d9/ghc

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

commit 8736625f143d55616e76ff660d476ce4a9cdb2d9
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Jun 24 08:59:20 2016 +0100

    Fix renamer panic
    
    This patch fixes Trac #12216 and #12127.  The 'combine' function
    in 'imp_occ_env' in RnNames.filterImports checked for an empty
    field-selector list, which was (a) unnecessary and (b) wrong.
    
    I've elaborated the comments.
    
    This does NOT fix #11959 which is related but not the same
    (it concerns bundling of pattern synonyms).
    
    (cherry picked from commit 393928db9fc35ef8bdeb241c051224a6c4bdf749)


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

8736625f143d55616e76ff660d476ce4a9cdb2d9
 compiler/rename/RnNames.hs                         | 22 +++++++++++++++-------
 testsuite/tests/rename/should_compile/T12127.hs    |  3 +++
 .../should_compile/{DodgyA.hs => T12127a.hs}       |  6 +++---
 testsuite/tests/rename/should_compile/all.T        |  4 ++++
 4 files changed, 25 insertions(+), 10 deletions(-)

diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index bcb247a..a284d3a 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -742,8 +742,15 @@ The situation is made more complicated by associated types. E.g.
      instance C Bool where { data T Int = T3 }
 Then M's export_avails are (recall the AvailTC invariant from Avails.hs)
   C(C,T), T(T,T1,T2,T3)
-Notice that T appears *twice*, once as a child and once as a parent.
-From this we construct the imp_occ_env
+Notice that T appears *twice*, once as a child and once as a parent. From
+this list we construt a raw list including
+   T -> (T, T( T1, T2, T3 ), Nothing)
+   T -> (C, C( C, T ),       Nothing)
+and we combine these (in function 'combine' in 'imp_occ_env' in
+'filterImports') to get
+   T  -> (T,  T(T,T1,T2,T3), Just C)
+
+So the overall imp_occ_env is
    C  -> (C,  C(C,T),        Nothing)
    T  -> (T,  T(T,T1,T2,T3), Just C)
    T1 -> (T1, T(T1,T2,T3),   Nothing)   -- similarly T2,T3
@@ -796,12 +803,13 @@ filterImports iface decl_spec (Just (want_hiding, L l import_items))
     imp_occ_env = mkOccEnv_C combine [ (nameOccName n, (n, a, Nothing))
                                      | a <- all_avails, n <- availNames a]
       where
-        -- See example in Note [Dealing with imports]
-        -- 'combine' is only called for associated types which appear twice
-        -- in the all_avails. In the example, we combine
+        -- See Note [Dealing with imports]
+        -- 'combine' is only called for associated data types which appear
+        -- twice in the all_avails. In the example, we combine
         --    T(T,T1,T2,T3) and C(C,T)  to give   (T, T(T,T1,T2,T3), Just C)
-        combine (name1, a1@(AvailTC p1 _ []), mp1)
-                (name2, a2@(AvailTC p2 _ []), mp2)
+        -- NB: the AvailTC can have fields as well as data constructors (Trac #12127)
+        combine (name1, a1@(AvailTC p1 _ _), mp1)
+                (name2, a2@(AvailTC p2 _ _), mp2)
           = ASSERT( name1 == name2 && isNothing mp1 && isNothing mp2 )
             if p1 == name1 then (name1, a1, Just p2)
                            else (name1, a2, Just p1)
diff --git a/testsuite/tests/rename/should_compile/T12127.hs b/testsuite/tests/rename/should_compile/T12127.hs
new file mode 100644
index 0000000..749e406
--- /dev/null
+++ b/testsuite/tests/rename/should_compile/T12127.hs
@@ -0,0 +1,3 @@
+module T12127 where
+
+import T12127a( T(..), C(..) )
diff --git a/testsuite/tests/rename/should_compile/DodgyA.hs b/testsuite/tests/rename/should_compile/T12127a.hs
similarity index 50%
copy from testsuite/tests/rename/should_compile/DodgyA.hs
copy to testsuite/tests/rename/should_compile/T12127a.hs
index 39cb3ec..53c1b7e 100644
--- a/testsuite/tests/rename/should_compile/DodgyA.hs
+++ b/testsuite/tests/rename/should_compile/T12127a.hs
@@ -1,9 +1,9 @@
 {-# LANGUAGE TypeFamilies #-}
 
-module DodgyA(C(..), X(..)) where
+module T12127a where
 
 class C a where
-  data X a
+  data T a
 
 instance C Int where
-  data X Int = X1 Bool
+  data T Int = MkT { x, y :: Int }
diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T
index cfad164..79106c0 100644
--- a/testsuite/tests/rename/should_compile/all.T
+++ b/testsuite/tests/rename/should_compile/all.T
@@ -237,3 +237,7 @@ test('T11662',
      [extra_clean(['T11662_A.hi', 'T11662_A.o'])],
      multimod_compile,
      ['T11662', '-v0'])
+test('T12127',
+     [extra_clean(['T12127a.hi', 'T12127a.o'])],
+     multimod_compile,
+     ['T12127', '-v0'])



More information about the ghc-commits mailing list