summaryrefslogtreecommitdiff
path: root/ghc/compiler
diff options
context:
space:
mode:
authorsimonmar <unknown>2000-03-06 11:58:28 +0000
committersimonmar <unknown>2000-03-06 11:58:28 +0000
commit656b963de456a5888b840bc788e036ad575a3930 (patch)
treef3efbe452f6cee32a955d7643eaebb674b68965d /ghc/compiler
parent2add920879ae9107f8dffd6d2dbca174fb85fae3 (diff)
downloadhaskell-656b963de456a5888b840bc788e036ad575a3930.tar.gz
[project @ 2000-03-06 11:58:27 by simonmar]
Turn the panic in Lex.popContext into a parse error.
Diffstat (limited to 'ghc/compiler')
-rw-r--r--ghc/compiler/parser/Lex.lhs19
-rw-r--r--ghc/compiler/parser/ParseUtil.lhs12
2 files changed, 16 insertions, 15 deletions
diff --git a/ghc/compiler/parser/Lex.lhs b/ghc/compiler/parser/Lex.lhs
index b2f04b04ff..6d56a6de73 100644
--- a/ghc/compiler/parser/Lex.lhs
+++ b/ghc/compiler/parser/Lex.lhs
@@ -20,7 +20,7 @@ An example that provokes the error is
module Lex (
- ifaceParseErr,
+ ifaceParseErr, srcParseErr,
-- Monad for parser
Token(..), lexer, ParseResult(..), PState(..),
@@ -1250,10 +1250,10 @@ layoutOff buf s@(PState{ context = ctx }) =
POk s{ context = NoLayout:ctx } ()
popContext :: P ()
-popContext = \ buf s@(PState{ context = ctx }) ->
+popContext = \ buf s@(PState{ context = ctx, loc = loc }) ->
case ctx of
(_:tl) -> POk s{ context = tl } ()
- [] -> panic "Lex.popContext: empty context"
+ [] -> PFailed (srcParseErr buf loc)
{-
Note that if the name of the file we're processing ends
@@ -1295,4 +1295,17 @@ ifaceVersionErr hi_vers l toks
Nothing -> ptext SLIT("pre ghc-3.02 version")
Just v -> ptext SLIT("version") <+> integer v
+-----------------------------------------------------------------------------
+
+srcParseErr :: StringBuffer -> SrcLoc -> Message
+srcParseErr s l
+ = hcat [ppr l,
+ if null token
+ then ptext SLIT(": parse error (possibly incorrect indentation)")
+ else hcat [ptext SLIT(": parse error on input "),
+ char '`', text token, char '\'']
+ ]
+ where
+ token = lexemeToString s
+
\end{code}
diff --git a/ghc/compiler/parser/ParseUtil.lhs b/ghc/compiler/parser/ParseUtil.lhs
index c396e3f936..e26415e4d9 100644
--- a/ghc/compiler/parser/ParseUtil.lhs
+++ b/ghc/compiler/parser/ParseUtil.lhs
@@ -6,7 +6,6 @@
\begin{code}
module ParseUtil (
parseError -- String -> Pa
- , srcParseErr -- StringBuffer -> SrcLoc -> Message
, cbot -- a
, splitForConApp -- RdrNameHsType -> [RdrNameBangType]
-- -> P (RdrName, [RdrNameBangType])
@@ -71,17 +70,6 @@ parseError s =
getSrcLocP `thenP` \ loc ->
failMsgP (hcat [ppr loc, text ": ", text s])
-srcParseErr :: StringBuffer -> SrcLoc -> Message
-srcParseErr s l
- = hcat [ppr l,
- if null token
- then ptext SLIT(": parse error (possibly incorrect indentation)")
- else hcat [ptext SLIT(": parse error on input "),
- char '`', text token, char '\'']
- ]
- where
- token = lexemeToString s
-
cbot = panic "CCall:result_ty"
-----------------------------------------------------------------------------