Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/20548c92fb307fc012956c66efa9164843d921c7

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

commit 20548c92fb307fc012956c66efa9164843d921c7
Author: Geoffrey Mainland <[email protected]>
Date:   Thu Sep 29 12:31:49 2011 +0100

    Give a better error message for unterminated quasiquotations (fixes #5204).

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

 compiler/parser/Lexer.x |   15 ++++++++++-----
 1 files changed, 10 insertions(+), 5 deletions(-)

diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index ec11cd5..ea575fe 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -1418,18 +1418,18 @@ lex_quasiquote_tok span buf len = do
                 -- 'tail' drops the initial '[',
                 -- while the -1 drops the trailing '|'
   quoteStart <- getSrcLoc
-  quote <- lex_quasiquote ""
+  quote <- lex_quasiquote quoteStart ""
   end <- getSrcLoc
   return (L (mkRealSrcSpan (realSrcSpanStart span) end)
            (ITquasiQuote (mkFastString quoter,
                           mkFastString (reverse quote),
                           mkRealSrcSpan quoteStart end)))
 
-lex_quasiquote :: String -> P String
-lex_quasiquote s = do
+lex_quasiquote :: RealSrcLoc -> String -> P String
+lex_quasiquote start s = do
   i <- getInput
   case alexGetChar' i of
-    Nothing -> lit_error i
+    Nothing -> quasiquote_error start
 
     -- NB: The string "|]" terminates the quasiquote,
     -- with absolutely no escaping. See the extensive
@@ -1440,7 +1440,12 @@ lex_quasiquote s = do
         -> do { setInput i; return s }
 
     Just (c, i) -> do
-         setInput i; lex_quasiquote (c : s)
+         setInput i; lex_quasiquote start (c : s)
+
+quasiquote_error :: RealSrcLoc -> P a
+quasiquote_error start = do
+  (AI end buf) <- getInput
+  reportLexError start end buf "unterminated quasiquotation"
 
 -- 
-----------------------------------------------------------------------------
 -- Warnings



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to