1
+ {-# LANGUAGE CPP #-}
1
2
{-# OPTIONS_HADDOCK hide #-}
2
3
-----------------------------------------------------------------------------
3
4
-- |
@@ -18,7 +19,7 @@ module Language.Haskell.Exts.ParseMonad(
18
19
-- * Generic Parsing
19
20
Parseable (.. ),
20
21
-- * Parsing
21
- P , ParseResult (.. ), atSrcLoc , LexContext (.. ),
22
+ P , ParseResult (.. ), atSrcLoc , LexContext (.. ), LayoutKind ( .. ),
22
23
ParseMode (.. ), defaultParseMode , fromParseResult ,
23
24
runParserWithMode , runParserWithModeComments , runParser ,
24
25
getSrcLoc , pushCurrentContext , popContext ,
@@ -51,6 +52,10 @@ import Data.Semigroup (Semigroup(..))
51
52
-- To avoid import warnings for Control.Applicative, Data.Monoid, and Data.Semigroup
52
53
import Prelude
53
54
55
+ #ifdef DEBUG
56
+ import Debug.Trace
57
+ #endif
58
+
54
59
-- | Class providing function for parsing at many different types.
55
60
--
56
61
-- Note that for convenience of implementation, the default methods have
@@ -115,22 +120,27 @@ instance ( Monoid m , Semigroup m) => Monoid (ParseResult m) where
115
120
data ParseStatus a = Ok ParseState a | Failed SrcLoc String
116
121
deriving Show
117
122
118
- data LexContext = NoLayout | Layout Int
123
+ data LayoutKind
124
+ = BindLayout
125
+ | StmtLayout
126
+ deriving (Eq , Ord , Show )
127
+
128
+ data LexContext = NoLayout | Layout LayoutKind Int
119
129
deriving (Eq ,Ord ,Show )
120
130
121
131
data ExtContext = CodeCtxt | HarpCtxt | TagCtxt | ChildCtxt
122
132
| CloseTagCtxt | CodeTagCtxt
123
133
deriving (Eq ,Ord ,Show )
124
134
125
135
type CtxtFlag = (Bool ,Bool )
126
- -- (True,_) = We're in a do context.
127
- -- (_, True)= Next token must be a virtual closing brace.
136
+ -- (True, _) = We're in a do context.
137
+ -- (_, True) = Next token must be a virtual closing brace.
128
138
129
139
type ParseState = ([LexContext ],[[KnownExtension ]],[ExtContext ],CtxtFlag ,[Comment ])
130
140
131
141
indentOfParseState :: ParseState -> Int
132
- indentOfParseState (Layout n: _,_,_,_,_) = n
133
- indentOfParseState _ = 0
142
+ indentOfParseState (Layout _ n: _,_,_,_,_) = n
143
+ indentOfParseState _ = 0
134
144
135
145
-- | Static parameters governing a parse.
136
146
-- Note that the various parse functions in "Language.Haskell.Exts.Parser"
@@ -278,30 +288,35 @@ getModuleName = P $ \_i _x _y _l _ch s m ->
278
288
-- (So if the source loc is not to the right of the current indent, an
279
289
-- empty list {} will be inserted.)
280
290
281
- pushCurrentContext :: P ()
282
- pushCurrentContext = do
291
+ pushCurrentContext :: LayoutKind -> P ()
292
+ pushCurrentContext layoutKind = do
283
293
lc <- getSrcLoc
284
294
indent <- currentIndent
285
295
dob <- pullDoStatus
286
296
let loc = srcColumn lc
287
297
when (dob && loc < indent
288
298
|| not dob && loc <= indent) pushCtxtFlag
289
- pushContext (Layout loc)
299
+ pushContext (Layout layoutKind loc)
290
300
291
301
currentIndent :: P Int
292
302
currentIndent = P $ \ _r _x _y _ _ stk _mode -> Ok stk (indentOfParseState stk)
293
303
294
304
pushContext :: LexContext -> P ()
295
305
pushContext ctxt =
296
- -- trace ("pushing lexical scope: " ++ show ctxt ++"\n") $
306
+ #ifdef DEBUG
307
+ trace (" pushing lexical scope: " ++ show ctxt) $
308
+ #endif
297
309
P $ \ _i _x _y _l _ (s, exts, e, p, c) _m -> Ok (ctxt: s, exts, e, p, c) ()
298
310
299
311
popContext :: P ()
300
312
popContext = P $ \ _i _x _y loc _ stk _m ->
301
- case stk of
302
- (_: s, exts, e, p, c) -> -- trace ("popping lexical scope, context now "++show s ++ "\n") $
303
- Ok (s, exts, e, p, c) ()
304
- ([] ,_,_,_,_) -> Failed loc " Unexpected }" -- error "Internal error: empty context in popContext"
313
+ case stk of
314
+ (_: s, exts, e, p, c) ->
315
+ #ifdef DEBUG
316
+ trace (" popping lexical scope, context now " ++ show s) $
317
+ #endif
318
+ Ok (s, exts, e, p, c) ()
319
+ ([] ,_,_,_,_) -> Failed loc " Unexpected }"
305
320
306
321
{-
307
322
-- HaRP/Hsx
@@ -323,9 +338,13 @@ getExtensions = P $ \_i _x _y _l _ s m ->
323
338
324
339
pushCtxtFlag :: P ()
325
340
pushCtxtFlag =
326
- P $ \ _i _x _y _l _ (s, exts, e, (d,c), cs) _m -> case c of
327
- False -> Ok (s, exts, e, (d,True ), cs) ()
328
- _ -> error " Internal error: context flag already pushed"
341
+ P $ \ _i _x _y _l _ (s, exts, e, (d,c), cs) _m ->
342
+ #ifdef DEBUG
343
+ trace " pushing context switch" $
344
+ #endif
345
+ case c of
346
+ False -> Ok (s, exts, e, (d,True ), cs) ()
347
+ _ -> error " Internal error: context flag already pushed"
329
348
330
349
pullDoStatus :: P Bool
331
350
pullDoStatus = P $ \ _i _x _y _l _ (s, exts, e, (d,c), cs) _m -> Ok (s,exts,e,(False ,c),cs) d
@@ -364,6 +383,9 @@ instance Fail.MonadFail (Lex r) where
364
383
getInput :: Lex r String
365
384
getInput = Lex $ \ cont -> P $ \ r -> runP (cont r) r
366
385
386
+ parserL :: P a -> Lex r a
387
+ parserL p = Lex (p >>= )
388
+
367
389
-- | Discard some input characters (these must not include tabs or newlines).
368
390
369
391
discard :: Int -> Lex r ()
@@ -480,16 +502,16 @@ setSrcLineL y = Lex $ \cont -> P $ \i x _ ->
480
502
runP (cont () ) i x y
481
503
482
504
pushContextL :: LexContext -> Lex a ()
483
- pushContextL ctxt = Lex $ \ cont -> P $ \ r x y loc ch (stk, exts, e, pst, cs) ->
484
- runP (cont () ) r x y loc ch (ctxt: stk, exts, e, pst, cs)
505
+ pushContextL = parserL . pushContext
485
506
486
507
popContextL :: String -> Lex a ()
487
- popContextL _ = Lex $ \ cont -> P $ \ r x y loc ch stk m -> case stk of
488
- (_: ctxt, exts, e, pst, cs) -> runP (cont () ) r x y loc ch (ctxt, exts, e, pst, cs) m
489
- ([] , _, _, _, _) -> Failed loc " Unexpected }"
508
+ popContextL _ = parserL popContext
490
509
491
510
pullCtxtFlag :: Lex a Bool
492
511
pullCtxtFlag = Lex $ \ cont -> P $ \ r x y loc ch (ct, exts, e, (d,c), cs) ->
512
+ #ifdef DEBUG
513
+ trace " pulling context switch" $
514
+ #endif
493
515
runP (cont c) r x y loc ch (ct, exts, e, (d,False ), cs)
494
516
495
517
0 commit comments