[commit: ghc] ghc-8.0: Avoid find_tycon panic if datacon is not in scope (694e0f3)

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


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/694e0f3a0803072687fab6e3a5792627f5761bd2/ghc

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

commit 694e0f3a0803072687fab6e3a5792627f5761bd2
Author: Adam Gundry <adam at well-typed.com>
Date:   Sat Jun 18 12:27:47 2016 +0200

    Avoid find_tycon panic if datacon is not in scope
    
    When using TH to splice expressions involving record field construction,
    the parent datacon may not be in scope.  We shouldn't panic about this,
    because we will be renaming Exact RdrNames which don't require any
    disambiguation.
    
    Test Plan: new test th/T12130
    
    Reviewers: austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2321
    
    GHC Trac Issues: #12130
    
    (cherry picked from commit 4d71cc89b4e9648f3fbb29c8fcd25d725616e265)


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

694e0f3a0803072687fab6e3a5792627f5761bd2
 compiler/rename/RnPat.hs      |  7 ++++---
 testsuite/tests/th/T12130.hs  |  8 ++++++++
 testsuite/tests/th/T12130a.hs | 17 +++++++++++++++++
 testsuite/tests/th/all.T      |  2 ++
 4 files changed, 31 insertions(+), 3 deletions(-)

diff --git a/compiler/rename/RnPat.hs b/compiler/rename/RnPat.hs
index 51ddea9..f1b61e3 100644
--- a/compiler/rename/RnPat.hs
+++ b/compiler/rename/RnPat.hs
@@ -636,7 +636,7 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot })
     find_tycon :: GlobalRdrEnv -> Name {- DataCon -} -> Maybe Name {- TyCon -}
     -- Return the parent *type constructor* of the data constructor
     -- (that is, the parent of the data constructor),
-    -- or 'Nothing' if it is a pattern synonym.
+    -- or 'Nothing' if it is a pattern synonym or not in scope.
     -- That's the parent to use for looking up record fields.
     find_tycon env con
       | Just (AConLike (RealDataCon dc)) <- wiredInNameTyThing_maybe con
@@ -648,8 +648,9 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot })
           ParentIs p -> Just p
           _          -> Nothing
 
-      | otherwise
-      = pprPanic "find_tycon" (ppr con $$ ppr (lookupGRE_Name env con))
+      | otherwise = Nothing
+        -- This can happen if the datacon is not in scope
+        -- and we are in a TH splice (Trac #12130)
 
     dup_flds :: [[RdrName]]
         -- Each list represents a RdrName that occurred more than once
diff --git a/testsuite/tests/th/T12130.hs b/testsuite/tests/th/T12130.hs
new file mode 100644
index 0000000..7ab7492
--- /dev/null
+++ b/testsuite/tests/th/T12130.hs
@@ -0,0 +1,8 @@
+{-# Language TemplateHaskell #-}
+{-# Language DisambiguateRecordFields #-}
+
+module T12130 where
+
+import T12130a hiding (Block)
+
+b = $(block)
diff --git a/testsuite/tests/th/T12130a.hs b/testsuite/tests/th/T12130a.hs
new file mode 100644
index 0000000..f393967
--- /dev/null
+++ b/testsuite/tests/th/T12130a.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module T12130a where
+
+import Language.Haskell.TH
+
+data Block = Block
+    { blockSelector :: ()
+    }
+
+block :: Q Exp
+block =
+    [| Block {
+         -- Using record syntax is neccesary to trigger the bug.
+         blockSelector = ()
+       }
+    |]
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 864fa74..2e7a6ba 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -408,3 +408,5 @@ test('T11680', normal, compile_fail, ['-v0'])
 test('T11809', normal, compile, ['-v0'])
 test('T11797', normal, compile, ['-v0 -dsuppress-uniques'])
 test('T11941', normal, compile_fail, ['-v0'])
+test('T12130', extra_clean(['T12130a.hi','T12130a.o']),
+              multimod_compile, ['T12130', '-v0 ' + config.ghc_th_way_flags])



More information about the ghc-commits mailing list