[commit: ghc] master: RnSplice's staging test should be applied for quotes in stage1. (eb0ed40)

git at git.haskell.org git at git.haskell.org
Sat May 9 08:25:21 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/eb0ed4030374af542c0a459480d32c8d4525e48d/ghc

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

commit eb0ed4030374af542c0a459480d32c8d4525e48d
Author: Edward Z. Yang <ezyang at cs.stanford.edu>
Date:   Mon May 4 17:28:11 2015 -0700

    RnSplice's staging test should be applied for quotes in stage1.
    
    Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
    
    Test Plan: validate
    
    Reviewers: simonpj, austin
    
    Subscribers: bgamari, thomie
    
    Differential Revision: https://phabricator.haskell.org/D878
    
    GHC Trac Issues: #10382


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

eb0ed4030374af542c0a459480d32c8d4525e48d
 compiler/rename/RnSplice.hs                | 17 ++++++-----------
 testsuite/tests/quotes/TH_localname.hs     |  3 +++
 testsuite/tests/quotes/TH_localname.stderr | 22 ++++++++++++++++++++++
 testsuite/tests/quotes/all.T               |  1 +
 4 files changed, 32 insertions(+), 11 deletions(-)

diff --git a/compiler/rename/RnSplice.hs b/compiler/rename/RnSplice.hs
index 4f55477..5d12720 100644
--- a/compiler/rename/RnSplice.hs
+++ b/compiler/rename/RnSplice.hs
@@ -35,11 +35,14 @@ import Control.Monad    ( unless, when )
 
 import {-# SOURCE #-} RnExpr   ( rnLExpr )
 
+import PrelNames        ( isUnboundName )
+import TcEnv            ( checkWellStaged )
+import DsMeta           ( liftName )
+
 #ifdef GHCI
 import ErrUtils         ( dumpIfSet_dyn_printer )
-import DsMeta           ( decsQTyConName, expQTyConName, patQTyConName, typeQTyConName, liftName )
-import PrelNames        ( isUnboundName )
-import TcEnv            ( checkWellStaged, tcMetaTy )
+import DsMeta           ( decsQTyConName, expQTyConName, patQTyConName, typeQTyConName, )
+import TcEnv            ( tcMetaTy )
 import Hooks
 import Var              ( Id )
 import DsMeta           ( quoteExpName, quotePatName, quoteDecName, quoteTypeName )
@@ -565,13 +568,6 @@ illegalUntypedSplice = ptext (sLit "Untyped splices may not appear in typed brac
 #endif
 
 checkThLocalName :: Name -> RnM ()
-#ifndef GHCI  /* GHCI and TH is off */
---------------------------------------
--- Check for cross-stage lifting
-checkThLocalName _name
-  = return ()
-
-#else         /* GHCI and TH is on */
 checkThLocalName name
   | isUnboundName name   -- Do not report two errors for
   = return ()            --   $(not_in_scope args)
@@ -637,7 +633,6 @@ check_cross_stage_lifting top_lvl name ps_var
           -- Update the pending splices
         ; ps <- readMutVar ps_var
         ; writeMutVar ps_var (pend_splice : ps) }
-#endif /* GHCI */
 
 {-
 Note [Keeping things alive for Template Haskell]
diff --git a/testsuite/tests/quotes/TH_localname.hs b/testsuite/tests/quotes/TH_localname.hs
new file mode 100644
index 0000000..5bc0e96
--- /dev/null
+++ b/testsuite/tests/quotes/TH_localname.hs
@@ -0,0 +1,3 @@
+module TH_localname where
+
+x = \y -> [| y |]
diff --git a/testsuite/tests/quotes/TH_localname.stderr b/testsuite/tests/quotes/TH_localname.stderr
new file mode 100644
index 0000000..a83c606
--- /dev/null
+++ b/testsuite/tests/quotes/TH_localname.stderr
@@ -0,0 +1,22 @@
+
+TH_localname.hs:3:11: error:
+    No instance for (Lift t0) arising from a use of ‘lift’
+    The type variable ‘t0’ is ambiguous
+    Relevant bindings include
+      y :: t0 (bound at TH_localname.hs:3:6)
+      x :: t0 -> ExpQ (bound at TH_localname.hs:3:1)
+    Note: there are several potential instances:
+      instance (Lift a, Lift b) => Lift (Either a b)
+        -- Defined in ‘Language.Haskell.TH.Syntax’
+      instance Lift a => Lift (Maybe a)
+        -- Defined in ‘Language.Haskell.TH.Syntax’
+      instance Lift Int16 -- Defined in ‘Language.Haskell.TH.Syntax’
+      ...plus 24 others
+    In the expression: lift y
+    In the expression:
+      [| y |]
+      pending(rn) [<y, lift y>]
+    In the expression:
+      \ y
+        -> [| y |]
+           pending(rn) [<y, lift y>]
diff --git a/testsuite/tests/quotes/all.T b/testsuite/tests/quotes/all.T
index 2688391..a3dfb8b 100644
--- a/testsuite/tests/quotes/all.T
+++ b/testsuite/tests/quotes/all.T
@@ -27,3 +27,4 @@ test('TH_reifyType2', normal, compile, [''])
 test('TH_repE1', normal, compile, [''])
 test('TH_repE3', normal, compile, [''])
 test('TH_abstractFamily', normal, compile_fail, [''])
+test('TH_localname', normal, compile_fail, [''])



More information about the ghc-commits mailing list