[commit: ghc] master: Remove deprecated quasiquoter syntax. (399a5b4)

git at git.haskell.org git at git.haskell.org
Sun Nov 29 12:22:12 UTC 2015


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

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

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

commit 399a5b46591dfbee0499d6afa1bb80ad2fd52598
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date:   Fri Nov 27 16:16:39 2015 +0100

    Remove deprecated quasiquoter syntax.
    
    In spirit, this reverts 9ba922ee06b048774d7a82964867ff768a78126e
    
    The syntax has been deprecated with a warning since 2010.
    
    Reviewers: austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D1530


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

399a5b46591dfbee0499d6afa1bb80ad2fd52598
 compiler/parser/Lexer.x                           |  4 ----
 compiler/rename/RnSplice.hs                       | 19 -------------------
 testsuite/tests/quasiquotation/qq008/Test.hs      |  2 +-
 testsuite/tests/quasiquotation/qq008/qq008.stderr |  4 ----
 4 files changed, 1 insertion(+), 28 deletions(-)

diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index 9e57b4b..32f4254 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -383,10 +383,6 @@ $tab          { warnTab }
   "$("        / { ifExtension thEnabled } { token ITparenEscape }
   "$$("       / { ifExtension thEnabled } { token ITparenTyEscape }
 
--- For backward compatibility, accept the old dollar syntax
-  "[$" @varid "|"  / { ifExtension qqEnabled }
-                     { lex_quasiquote_tok }
-
   "[" @varid "|"  / { ifExtension qqEnabled }
                      { lex_quasiquote_tok }
 
diff --git a/compiler/rename/RnSplice.hs b/compiler/rename/RnSplice.hs
index 95c5462..2093312 100644
--- a/compiler/rename/RnSplice.hs
+++ b/compiler/rename/RnSplice.hs
@@ -46,7 +46,6 @@ import Var              ( Id )
 import THNames          ( quoteExpName, quotePatName, quoteDecName, quoteTypeName
                         , decsQTyConName, expQTyConName, patQTyConName, typeQTyConName, )
 import RnTypes          ( collectWildCards )
-import Util
 
 import {-# SOURCE #-} TcExpr   ( tcMonoExpr )
 import {-# SOURCE #-} TcSplice ( runMetaD, runMetaE, runMetaP, runMetaT, tcTopSpliceExpr )
@@ -373,17 +372,6 @@ rnSplice (HsQuasiQuote splice_name quoter q_loc quote)
         ; loc  <- getSrcSpanM
         ; splice_name' <- newLocalBndrRn (L loc splice_name)
 
-          -- Drop the leading "$" from the quoter name, if present
-          -- This is old-style syntax, now deprecated
-          -- NB: when removing this backward-compat, remove
-          --     the matching code in Lexer.x (around line 310)
-        ; let occ_str = occNameString (rdrNameOcc quoter)
-        ; quoter <- if ASSERT( not (null occ_str) )  -- Lexer ensures this
-                       head occ_str /= '$'
-                    then return quoter
-                    else do { addWarn (deprecatedDollar quoter)
-                            ; return (mkRdrUnqual (mkVarOcc (tail occ_str))) }
-
           -- Rename the quoter; akin to the HsVar case of rnExpr
         ; quoter' <- lookupOccRn quoter
         ; this_mod <- getModule
@@ -392,13 +380,6 @@ rnSplice (HsQuasiQuote splice_name quoter q_loc quote)
 
         ; return (HsQuasiQuote splice_name' quoter' q_loc quote, unitFV quoter') }
 
-deprecatedDollar :: RdrName -> SDoc
-deprecatedDollar quoter
-  = hang (ptext (sLit "Deprecated syntax:"))
-       2 (ptext (sLit "quasiquotes no longer need a dollar sign:")
-          <+> ppr quoter)
-
-
 ---------------------
 rnSpliceExpr :: HsSplice RdrName -> RnM (HsExpr Name, FreeVars)
 rnSpliceExpr splice
diff --git a/testsuite/tests/quasiquotation/qq008/Test.hs b/testsuite/tests/quasiquotation/qq008/Test.hs
index c04f427..fbaa80e 100644
--- a/testsuite/tests/quasiquotation/qq008/Test.hs
+++ b/testsuite/tests/quasiquotation/qq008/Test.hs
@@ -6,7 +6,7 @@ import QQ
 f :: [pq| foo |]    -- Expands to Int -> Int
 [pq| blah |]        -- Expands to f x = x
 
-h [pq| foo |] = f [$pq| blah |] * 8
+h [pq| foo |] = f [pq| blah |] * 8
 -- Expands to h (Just x) = f (x+1) * 8
 
 
diff --git a/testsuite/tests/quasiquotation/qq008/qq008.stderr b/testsuite/tests/quasiquotation/qq008/qq008.stderr
deleted file mode 100644
index b13e999..0000000
--- a/testsuite/tests/quasiquotation/qq008/qq008.stderr
+++ /dev/null
@@ -1,4 +0,0 @@
-
-Test.hs:9:19:
-    Warning: Deprecated syntax:
-               quasiquotes no longer need a dollar sign: $pq



More information about the ghc-commits mailing list