[commit: ghc] ghc-7.8: Fix #8759 by not panicking with TH and patsyns. (aa91cc2)

git at git.haskell.org git at git.haskell.org
Mon Feb 17 09:15:24 UTC 2014


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

On branch  : ghc-7.8
Link       : http://ghc.haskell.org/trac/ghc/changeset/aa91cc2ae5151f7e25dbc35f32ef966bc59c2e12/ghc

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

commit aa91cc2ae5151f7e25dbc35f32ef966bc59c2e12
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Sun Feb 9 12:31:01 2014 -0500

    Fix #8759 by not panicking with TH and patsyns.
    
    We should still have pattern synonyms in TH, though.
    
    (cherry picked from commit 6122efcabe6e08375f69ee19148ba3838c332559)


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

aa91cc2ae5151f7e25dbc35f32ef966bc59c2e12
 compiler/deSugar/DsMeta.hs       |    2 +-
 compiler/typecheck/TcSplice.lhs  |    3 +++
 testsuite/tests/th/T8759.hs      |   11 +++++++++++
 testsuite/tests/th/T8759.stderr  |    3 +++
 testsuite/tests/th/T8759a.hs     |    5 +++++
 testsuite/tests/th/T8759a.stderr |    4 ++++
 testsuite/tests/th/all.T         |    2 ++
 7 files changed, 29 insertions(+), 1 deletion(-)

diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs
index 56fba14..9ee5bc1 100644
--- a/compiler/deSugar/DsMeta.hs
+++ b/compiler/deSugar/DsMeta.hs
@@ -1238,7 +1238,7 @@ rep_bind (L _ (VarBind { var_id = v, var_rhs = e}))
         ; return (srcLocSpan (getSrcLoc v), ans) }
 
 rep_bind (L _ (AbsBinds {}))  = panic "rep_bind: AbsBinds"
-rep_bind (L _ (PatSynBind {})) = panic "rep_bind: PatSynBind"
+rep_bind (L _ dec@(PatSynBind {})) = notHandled "pattern synonyms" (ppr dec)
 -----------------------------------------------------------------------------
 -- Since everything in a Bind is mutually recursive we need rename all
 -- all the variables simultaneously. For example:
diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs
index b7e2699..0a47da1 100644
--- a/compiler/typecheck/TcSplice.lhs
+++ b/compiler/typecheck/TcSplice.lhs
@@ -70,6 +70,7 @@ import Class
 import Inst
 import TyCon
 import CoAxiom
+import PatSyn ( patSynId )
 import ConLike
 import DataCon
 import TcEvidence( TcEvBinds(..) )
@@ -1173,6 +1174,8 @@ reifyThing (AGlobal (AConLike (RealDataCon dc)))
         ; return (TH.DataConI (reifyName name) ty
                               (reifyName (dataConOrigTyCon dc)) fix)
         }
+reifyThing (AGlobal (AConLike (PatSynCon ps)))
+  = noTH (sLit "pattern synonyms") (ppr $ patSynId ps)
 
 reifyThing (ATcId {tct_id = id})
   = do  { ty1 <- zonkTcType (idType id) -- Make use of all the info we have, even
diff --git a/testsuite/tests/th/T8759.hs b/testsuite/tests/th/T8759.hs
new file mode 100644
index 0000000..298761a
--- /dev/null
+++ b/testsuite/tests/th/T8759.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE TemplateHaskell, PatternSynonyms #-}
+
+module T8759 where
+
+import Language.Haskell.TH
+
+pattern P = ()
+
+$( do info <- reify 'P
+      reportWarning (show info)
+      return [] )
diff --git a/testsuite/tests/th/T8759.stderr b/testsuite/tests/th/T8759.stderr
new file mode 100644
index 0000000..3b5474b
--- /dev/null
+++ b/testsuite/tests/th/T8759.stderr
@@ -0,0 +1,3 @@
+
+T8759.hs:9:4:
+    Can't represent pattern synonyms in Template Haskell: P
diff --git a/testsuite/tests/th/T8759a.hs b/testsuite/tests/th/T8759a.hs
new file mode 100644
index 0000000..3d8089c
--- /dev/null
+++ b/testsuite/tests/th/T8759a.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE TemplateHaskell, PatternSynonyms #-}
+
+module T8759a where
+
+foo = [d| pattern Q = False |]
diff --git a/testsuite/tests/th/T8759a.stderr b/testsuite/tests/th/T8759a.stderr
new file mode 100644
index 0000000..ff0fd49
--- /dev/null
+++ b/testsuite/tests/th/T8759a.stderr
@@ -0,0 +1,4 @@
+
+T8759a.hs:5:7:
+    pattern synonyms not (yet) handled by Template Haskell
+      pattern Q = False
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 5b064ba..3e88970 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -317,3 +317,5 @@ test('T8577',
      ['T8577', '-v0 ' + config.ghc_th_way_flags])
 test('T8633', normal, compile_and_run, [''])
 test('T8625', normal, ghci_script, ['T8625.script'])
+test('T8759', normal, compile_fail, ['-v0'])
+test('T8759a', normal, compile_fail, ['-v0'])
\ No newline at end of file



More information about the ghc-commits mailing list