Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC
Commits:
-
7f35ad18
by Alan Zimmerman at 2025-04-21T16:24:44+01:00
-
b5ae074e
by Alan Zimmerman at 2025-04-21T17:07:28+01:00
11 changed files:
- compiler/GHC/Parser/PreProcess.hs
- compiler/GHC/Parser/PreProcess/Lexer.x
- compiler/GHC/Parser/PreProcess/Macro.hs
- compiler/GHC/Parser/PreProcess/ParsePP.hs
- compiler/GHC/Parser/PreProcess/ParserM.hs
- testsuite/tests/ghc-cpp/all.T
- utils/check-cpp/Lexer.x
- utils/check-cpp/Macro.hs
- utils/check-cpp/ParsePP.hs
- utils/check-cpp/ParserM.hs
- utils/check-cpp/PreProcess.hs
Changes:
... | ... | @@ -254,7 +254,7 @@ processCpp ss = do |
254 | 254 | Right (CppDefine name args def) -> do
|
255 | 255 | ppDefine (MacroName name args) def
|
256 | 256 | Right (CppIf cond) -> do
|
257 | - val <- cppIf cond
|
|
257 | + val <- cppCond cond
|
|
258 | 258 | ar <- pushAccepting val
|
259 | 259 | acceptStateChange ar
|
260 | 260 | Right (CppIfdef name) -> do
|
... | ... | @@ -270,7 +270,7 @@ processCpp ss = do |
270 | 270 | ar <- setAccepting (not accepting)
|
271 | 271 | acceptStateChange ar
|
272 | 272 | Right (CppElIf cond) -> do
|
273 | - val <- cppIf cond
|
|
273 | + val <- cppCond cond
|
|
274 | 274 | ar <- setAccepting val
|
275 | 275 | acceptStateChange ar
|
276 | 276 | Right CppEndif -> do
|
... | ... | @@ -2,11 +2,12 @@ |
2 | 2 | module GHC.Parser.PreProcess.Lexer (lex_tok, lexCppTokenStream ) where
|
3 | 3 | |
4 | 4 | import GHC.Parser.PreProcess.ParserM (
|
5 | - St, init_pos,
|
|
5 | + St(..), init_pos,
|
|
6 | 6 | ParserM (..), Action, mkTv, Token(..), start_code,
|
7 | 7 | setStartCode,
|
8 | 8 | show_pos, position,
|
9 | - AlexInput(..), alexGetByte)
|
|
9 | + AlexInput(..), alexGetByte,
|
|
10 | + alexInputPrevChar)
|
|
10 | 11 | import qualified GHC.Parser.PreProcess.ParserM as ParserM (input)
|
11 | 12 | import Control.Monad
|
12 | 13 | import GHC.Prelude
|
... | ... | @@ -92,17 +93,20 @@ words :- |
92 | 93 | <0> "xor" { mkTv TXor }
|
93 | 94 | <0> "xor_eq" { mkTv TXorEq }
|
94 | 95 | ----------------------------------------
|
95 | - <0> [a-zA-Z_][a-zA-Z0-9_]*\( { mkTv TIdentifierLParen }
|
|
96 | - <0> [a-zA-Z_][a-zA-Z0-9_]* { mkTv TIdentifier }
|
|
97 | - <0> \-? [0-9][0-9]* { mkTv TInteger }
|
|
98 | - <0> \" [^\"]* \" { mkTv (TString . tail . init) }
|
|
99 | - <0> () { begin other }
|
|
96 | + <0> [a-zA-Z_][a-zA-Z0-9_]*\( / { inDirective } { mkTv TIdentifierLParen }
|
|
97 | + <0> [a-zA-Z_][a-zA-Z0-9_]* { mkTv TIdentifier }
|
|
98 | + <0> \-? [0-9][0-9]* { mkTv TInteger }
|
|
99 | + <0> \" [^\"]* \" { mkTv (TString . tail . init) }
|
|
100 | + <0> () { begin other }
|
|
100 | 101 | |
101 | 102 | <other> .+ { \i -> do {setStartCode 0;
|
102 | 103 | mkTv TOther i} }
|
103 | 104 | |
104 | 105 | {
|
105 | 106 | |
107 | +inDirective :: AlexAccPred Bool
|
|
108 | +inDirective flag _ _ _ = flag
|
|
109 | + |
|
106 | 110 | begin :: Int -> Action
|
107 | 111 | begin sc _str =
|
108 | 112 | do setStartCode sc
|
... | ... | @@ -110,7 +114,7 @@ begin sc _str = |
110 | 114 | |
111 | 115 | get_tok :: ParserM Token
|
112 | 116 | get_tok = ParserM $ \i st ->
|
113 | - case alexScan i (start_code st) of
|
|
117 | + case alexScanUser (scanning_directive st) i (start_code st) of
|
|
114 | 118 | AlexEOF -> Right (i, st, TEOF "")
|
115 | 119 | AlexError _ -> Left ("Lexical error at " ++ show_pos (position i))
|
116 | 120 | AlexSkip i' _ -> case get_tok of
|
1 | 1 | module GHC.Parser.PreProcess.Macro (
|
2 | 2 | -- process,
|
3 | - cppIf,
|
|
3 | + cppCond,
|
|
4 | 4 | -- get rid of warnings for tests
|
5 | 5 | m1,
|
6 | 6 | m2,
|
... | ... | @@ -46,8 +46,8 @@ import GHC.Prelude |
46 | 46 | -- ---------------------------------------------------------------------
|
47 | 47 | |
48 | 48 | -- We evaluate to an Int, which we convert to a bool
|
49 | -cppIf :: String -> PP Bool
|
|
50 | -cppIf str = do
|
|
49 | +cppCond :: String -> PP Bool
|
|
50 | +cppCond str = do
|
|
51 | 51 | s <- getPpState
|
52 | 52 | let
|
53 | 53 | expanded = expand (pp_defines s) str
|
... | ... | @@ -62,7 +62,7 @@ expand :: MacroDefines -> String -> String |
62 | 62 | expand s str = expanded
|
63 | 63 | where
|
64 | 64 | -- TODO: repeat until re-expand or fixpoint
|
65 | - toks = case cppLex str of
|
|
65 | + toks = case cppLex False str of
|
|
66 | 66 | Left err -> error $ "expand:" ++ show (err, str)
|
67 | 67 | Right tks -> tks
|
68 | 68 | expanded = combineToks $ map t_str $ expandToks s toks
|
... | ... | @@ -81,7 +81,7 @@ doExpandToks ed _ [] = (ed, []) |
81 | 81 | doExpandToks ed s (TIdentifierLParen n: ts) =
|
82 | 82 | -- TIdentifierLParen has no meaning here (only in a #define), so
|
83 | 83 | -- restore it to its constituent tokens
|
84 | - doExpandToks ed s (TIdentifier n:TOpenParen "(":ts)
|
|
84 | + doExpandToks ed s (TIdentifier (init n):TOpenParen "(":ts)
|
|
85 | 85 | doExpandToks _ s (TIdentifier "defined" : ts) = (True, rest)
|
86 | 86 | -- See Note: [defined unary operator] below
|
87 | 87 | where
|
... | ... | @@ -268,13 +268,13 @@ isOther _ = True |
268 | 268 | -- ---------------------------------------------------------------------
|
269 | 269 | |
270 | 270 | m1 :: Either String [Token]
|
271 | -m1 = cppLex "`"
|
|
271 | +m1 = cppLex False "`"
|
|
272 | 272 | |
273 | 273 | m2 :: Either String [Token]
|
274 | -m2 = cppLex "hello(5)"
|
|
274 | +m2 = cppLex False "hello(5)"
|
|
275 | 275 | |
276 | 276 | m3 :: Either String [Token]
|
277 | -m3 = cppLex "#define FOO(m1,m2,m) ((m1) < 1 || (m1) == 1 && (m2) < 7 || (m1) == 1 && (m2) == 7 && (m) <= 0)"
|
|
277 | +m3 = cppLex True "#define FOO(m1,m2,m) ((m1) < 1 || (m1) == 1 && (m2) < 7 || (m1) == 1 && (m2) == 7 && (m) <= 0)"
|
|
278 | 278 | |
279 | 279 | -- Right [THash {t_str = "#"}
|
280 | 280 | -- ,TDefine {t_str = "define"}
|
... | ... | @@ -290,12 +290,12 @@ m3 = cppLex "#define FOO(m1,m2,m) ((m1) < 1 || (m1) == 1 && (m2) < 7 || (m1) = |
290 | 290 | -- ]
|
291 | 291 | |
292 | 292 | m4 :: Either String [Token]
|
293 | -m4 = cppLex "#if (m < 1)"
|
|
293 | +m4 = cppLex True "#if (m < 1)"
|
|
294 | 294 | |
295 | 295 | m5 :: Either String (Maybe [[Token]], [Token])
|
296 | 296 | m5 = do
|
297 | 297 | -- toks <- cppLex "(43,foo(a)) some other stuff"
|
298 | - toks <- cppLex "( ff(bar(),baz), 4 )"
|
|
298 | + toks <- cppLex False "( ff(bar(),baz), 4 )"
|
|
299 | 299 | return $ getExpandArgs toks
|
300 | 300 | |
301 | 301 | tt :: Either String ([[Char]], [Char])
|
... | ... | @@ -13,7 +13,7 @@ module GHC.Parser.PreProcess.ParsePP ( |
13 | 13 | import Data.List (intercalate)
|
14 | 14 | import GHC.Parser.Errors.Ppr ()
|
15 | 15 | import GHC.Parser.PreProcess.Lexer
|
16 | -import GHC.Parser.PreProcess.ParserM (Token (..), init_state)
|
|
16 | +import GHC.Parser.PreProcess.ParserM (Token (..), init_state, St(..))
|
|
17 | 17 | import GHC.Parser.PreProcess.State
|
18 | 18 | import GHC.Prelude
|
19 | 19 | |
... | ... | @@ -24,7 +24,7 @@ import GHC.Prelude |
24 | 24 | -- | Parse a CPP directive, using tokens from the CPP lexer
|
25 | 25 | parseDirective :: String -> Either String CppDirective
|
26 | 26 | parseDirective s =
|
27 | - case cppLex s of
|
|
27 | + case cppLex True s of
|
|
28 | 28 | Left e -> Left e
|
29 | 29 | Right toks ->
|
30 | 30 | case toks of
|
... | ... | @@ -48,7 +48,7 @@ combineToks ss = intercalate " " ss |
48 | 48 | |
49 | 49 | cppDefine :: [Token] -> Either String CppDirective
|
50 | 50 | cppDefine [] = Left "error:empty #define directive"
|
51 | -cppDefine (TIdentifierLParen n : ts) = Right $ CppDefine n args def
|
|
51 | +cppDefine (TIdentifierLParen n : ts) = Right $ CppDefine (init n) args def
|
|
52 | 52 | where
|
53 | 53 | (args, def) = getArgs ts
|
54 | 54 | cppDefine (TIdentifier n : ts) = Right $ CppDefine n Nothing ts
|
... | ... | @@ -102,8 +102,9 @@ parseDefineArgs acc ts = Left $ "malformed macro args, expecting identifier foll |
102 | 102 | |
103 | 103 | -- ---------------------------------------------------------------------
|
104 | 104 | |
105 | -cppLex :: String -> Either String [Token]
|
|
106 | -cppLex s = case lexCppTokenStream s init_state of
|
|
105 | +-- TODO: give this a better name
|
|
106 | +cppLex :: Bool -> String -> Either String [Token]
|
|
107 | +cppLex sd s = case lexCppTokenStream s (init_state {scanning_directive = sd}) of
|
|
107 | 108 | Left err -> Left err
|
108 | 109 | Right (_inp, _st, toks) -> Right toks
|
109 | 110 | |
... | ... | @@ -141,4 +142,5 @@ t2 = doATest "# if ((m1) < 1 || (m1) == 1 && (m2) < 7 || (m1) == 1 && (m2) == |
141 | 142 | t3 :: Either String CppDirective
|
142 | 143 | t3 = parseDirective "# if FOO == 4"
|
143 | 144 | |
144 | -t4 = cppLex "#define foo(X) X" |
|
145 | +t4 :: Either String [Token]
|
|
146 | +t4 = cppLex True "#define foo(X) X" |
... | ... | @@ -8,10 +8,9 @@ module GHC.Parser.PreProcess.ParserM ( |
8 | 8 | AlexInput (..),
|
9 | 9 | run_parser,
|
10 | 10 | -- Parser state
|
11 | - St,
|
|
11 | + St(..),
|
|
12 | 12 | init_state,
|
13 | 13 | StartCode,
|
14 | - start_code,
|
|
15 | 14 | setStartCode,
|
16 | 15 | -- Tokens
|
17 | 16 | Token (..),
|
... | ... | @@ -75,6 +74,7 @@ run_parser (ParserM f) = |
75 | 74 | data St = St
|
76 | 75 | { start_code :: !StartCode
|
77 | 76 | , brace_depth :: !Int
|
77 | + , scanning_directive :: !Bool
|
|
78 | 78 | }
|
79 | 79 | deriving (Show)
|
80 | 80 | type StartCode = Int
|
... | ... | @@ -84,6 +84,7 @@ init_state = |
84 | 84 | St
|
85 | 85 | { start_code = 0
|
86 | 86 | , brace_depth = 0
|
87 | + , scanning_directive = False
|
|
87 | 88 | }
|
88 | 89 | |
89 | 90 | -- Tokens
|
... | ... | @@ -9,8 +9,13 @@ def normalise_haskell_full_version( str ): |
9 | 9 | def normalise_haskell_pl1( str ):
|
10 | 10 | return re.sub(r'__GLASGOW_HASKELL_PATCHLEVEL1__.*\n', '__GLASGOW_HASKELL_PATCHLEVEL1__ XXX', str)
|
11 | 11 | |
12 | +# The MIN_VERSION_GLASGOW_HASKELL macro gets updated on every configure.
|
|
13 | +# Replace the RHS with a constant
|
|
14 | +def normalise_min_version_haskell( str ):
|
|
15 | + return re.sub(r'MIN_VERSION_GLASGOW_HASKELL.*\n', 'MIN_VERSION_GLASGOW_HASKELL XXX', str)
|
|
16 | + |
|
12 | 17 | test('GhcCpp01',
|
13 | 18 | # normal,
|
14 | - [normalise_errmsg_fun(normalise_haskell_full_version, normalise_haskell_pl1)],
|
|
19 | + [normalise_errmsg_fun(normalise_haskell_full_version, normalise_haskell_pl1,normalise_min_version_haskell)],
|
|
15 | 20 | compile,
|
16 | 21 | ['-ddump-ghc-cpp -dkeep-comments']) |
... | ... | @@ -2,14 +2,16 @@ |
2 | 2 | module Lexer (lex_tok, lexCppTokenStream ) where
|
3 | 3 | |
4 | 4 | import ParserM (
|
5 | - St, init_pos,
|
|
5 | + St(..), init_pos,
|
|
6 | 6 | ParserM (..), Action, mkTv, Token(..), start_code,
|
7 | 7 | setStartCode,
|
8 | 8 | show_pos, position,
|
9 | - AlexInput(..), alexGetByte)
|
|
9 | + AlexInput(..), alexGetByte,
|
|
10 | + alexInputPrevChar)
|
|
10 | 11 | -- import qualified ParserM as ParserM (input)
|
11 | 12 | import Control.Monad
|
12 | 13 | |
14 | + |
|
13 | 15 | -- The lexer is based on
|
14 | 16 | -- https://timsong-cpp.github.io/cppwp/n4140/lex.pptoken
|
15 | 17 | }
|
... | ... | @@ -90,17 +92,20 @@ words :- |
90 | 92 | <0> "xor" { mkTv TXor }
|
91 | 93 | <0> "xor_eq" { mkTv TXorEq }
|
92 | 94 | ----------------------------------------
|
93 | - <0> [a-zA-Z_][a-zA-Z0-9_]*\( { mkTv TIdentifierLParen }
|
|
94 | - <0> [a-zA-Z_][a-zA-Z0-9_]* { mkTv TIdentifier }
|
|
95 | - <0> \-? [0-9][0-9]* { mkTv TInteger }
|
|
96 | - <0> \" [^\"]* \" { mkTv (TString . tail . init) }
|
|
97 | - <0> () { begin other }
|
|
95 | + <0> [a-zA-Z_][a-zA-Z0-9_]*\( / { inDirective } { mkTv TIdentifierLParen }
|
|
96 | + <0> [a-zA-Z_][a-zA-Z0-9_]* { mkTv TIdentifier }
|
|
97 | + <0> \-? [0-9][0-9]* { mkTv TInteger }
|
|
98 | + <0> \" [^\"]* \" { mkTv (TString . tail . init) }
|
|
99 | + <0> () { begin other }
|
|
98 | 100 | |
99 | 101 | <other> .+ { \i -> do {setStartCode 0;
|
100 | 102 | mkTv TOther i} }
|
101 | 103 | |
102 | 104 | {
|
103 | 105 | |
106 | +inDirective :: AlexAccPred Bool
|
|
107 | +inDirective flag _ _ _ = flag
|
|
108 | + |
|
104 | 109 | begin :: Int -> Action
|
105 | 110 | begin sc _str =
|
106 | 111 | do setStartCode sc
|
... | ... | @@ -108,7 +113,7 @@ begin sc _str = |
108 | 113 | |
109 | 114 | get_tok :: ParserM Token
|
110 | 115 | get_tok = ParserM $ \i st ->
|
111 | - case alexScan i (start_code st) of
|
|
116 | + case alexScanUser (scanning_directive st) i (start_code st) of
|
|
112 | 117 | AlexEOF -> Right (i, st, TEOF "")
|
113 | 118 | AlexError _ -> Left ("Lexical error at " ++ show_pos (position i))
|
114 | 119 | AlexSkip i' _ -> case get_tok of
|
1 | 1 | module Macro (
|
2 | 2 | -- process,
|
3 | - cppIf,
|
|
3 | + cppCond,
|
|
4 | 4 | -- get rid of warnings for tests
|
5 | 5 | -- m0,
|
6 | 6 | m1,
|
... | ... | @@ -45,8 +45,8 @@ import State |
45 | 45 | -- ---------------------------------------------------------------------
|
46 | 46 | |
47 | 47 | -- We evaluate to an Int, which we convert to a bool
|
48 | -cppIf :: String -> PP Bool
|
|
49 | -cppIf str = do
|
|
48 | +cppCond :: String -> PP Bool
|
|
49 | +cppCond str = do
|
|
50 | 50 | s <- getPpState
|
51 | 51 | let
|
52 | 52 | expanded = expand (pp_defines s) str
|
... | ... | @@ -61,7 +61,7 @@ expand :: MacroDefines -> String -> String |
61 | 61 | expand s str = expanded
|
62 | 62 | where
|
63 | 63 | -- TODO: repeat until re-expand or fixpoint
|
64 | - toks = case cppLex str of
|
|
64 | + toks = case cppLex False str of
|
|
65 | 65 | Left err -> error $ "expand:" ++ show (err, str)
|
66 | 66 | Right tks -> tks
|
67 | 67 | expanded = combineToks $ map t_str $ expandToks s toks
|
... | ... | @@ -80,7 +80,7 @@ doExpandToks ed _ [] = (ed, []) |
80 | 80 | doExpandToks ed s (TIdentifierLParen n: ts) =
|
81 | 81 | -- TIdentifierLParen has no meaning here (only in a #define), so
|
82 | 82 | -- restore it to its constituent tokens
|
83 | - doExpandToks ed s (TIdentifier n:TOpenParen "(":ts)
|
|
83 | + doExpandToks ed s (TIdentifier (init n):TOpenParen "(":ts)
|
|
84 | 84 | doExpandToks _ s (TIdentifier "defined" : ts) = (True, rest)
|
85 | 85 | -- See Note: [defined unary operator] below
|
86 | 86 | where
|
... | ... | @@ -267,13 +267,13 @@ isOther _ = True |
267 | 267 | -- ---------------------------------------------------------------------
|
268 | 268 | |
269 | 269 | m1 :: Either String [Token]
|
270 | -m1 = cppLex "`"
|
|
270 | +m1 = cppLex False "`"
|
|
271 | 271 | |
272 | 272 | m2 :: Either String [Token]
|
273 | -m2 = cppLex "hello(5)"
|
|
273 | +m2 = cppLex False "hello(5)"
|
|
274 | 274 | |
275 | 275 | m3 :: Either String [Token]
|
276 | -m3 = cppLex "#define FOO(m1,m2,m) ((m1) < 1 || (m1) == 1 && (m2) < 7 || (m1) == 1 && (m2) == 7 && (m) <= 0)"
|
|
276 | +m3 = cppLex True "#define FOO(m1,m2,m) ((m1) < 1 || (m1) == 1 && (m2) < 7 || (m1) == 1 && (m2) == 7 && (m) <= 0)"
|
|
277 | 277 | |
278 | 278 | -- Right [THash {t_str = "#"}
|
279 | 279 | -- ,TDefine {t_str = "define"}
|
... | ... | @@ -289,12 +289,12 @@ m3 = cppLex "#define FOO(m1,m2,m) ((m1) < 1 || (m1) == 1 && (m2) < 7 || (m1) = |
289 | 289 | -- ]
|
290 | 290 | |
291 | 291 | m4 :: Either String [Token]
|
292 | -m4 = cppLex "#if (m < 1)"
|
|
292 | +m4 = cppLex True "#if (m < 1)"
|
|
293 | 293 | |
294 | 294 | m5 :: Either String (Maybe [[Token]], [Token])
|
295 | 295 | m5 = do
|
296 | 296 | -- toks <- cppLex "(43,foo(a)) some other stuff"
|
297 | - toks <- cppLex "( ff(bar(),baz), 4 )"
|
|
297 | + toks <- cppLex False "( ff(bar(),baz), 4 )"
|
|
298 | 298 | return $ getExpandArgs toks
|
299 | 299 | |
300 | 300 | tt :: Either String ([[Char]], [Char])
|
... | ... | @@ -12,7 +12,7 @@ module ParsePP ( |
12 | 12 | import Data.List
|
13 | 13 | import GHC.Parser.Errors.Ppr ()
|
14 | 14 | import Lexer
|
15 | -import ParserM (Token (..), init_state)
|
|
15 | +import ParserM (Token (..), init_state, St(..))
|
|
16 | 16 | import State
|
17 | 17 | |
18 | 18 | -- import Debug.Trace
|
... | ... | @@ -24,7 +24,7 @@ import State |
24 | 24 | -- | Parse a CPP directive, using tokens from the CPP lexer
|
25 | 25 | parseDirective :: String -> Either String CppDirective
|
26 | 26 | parseDirective s =
|
27 | - case cppLex s of
|
|
27 | + case cppLex True s of
|
|
28 | 28 | Left e -> Left e
|
29 | 29 | Right toks ->
|
30 | 30 | case toks of
|
... | ... | @@ -48,7 +48,7 @@ combineToks ss = intercalate " " ss |
48 | 48 | |
49 | 49 | cppDefine :: [Token] -> Either String CppDirective
|
50 | 50 | cppDefine [] = Left "error:empty #define directive"
|
51 | -cppDefine (TIdentifierLParen n : ts) = Right $ CppDefine n args def
|
|
51 | +cppDefine (TIdentifierLParen n : ts) = Right $ CppDefine (init n) args def
|
|
52 | 52 | where
|
53 | 53 | (args, def) = getArgs ts
|
54 | 54 | cppDefine (TIdentifier n : ts) = Right $ CppDefine n Nothing ts
|
... | ... | @@ -102,8 +102,9 @@ parseDefineArgs acc ts = Left $ "malformed macro args, expecting identifier foll |
102 | 102 | |
103 | 103 | -- ---------------------------------------------------------------------
|
104 | 104 | |
105 | -cppLex :: String -> Either String [Token]
|
|
106 | -cppLex s = case lexCppTokenStream s init_state of
|
|
105 | +-- TODO: give this a better name
|
|
106 | +cppLex :: Bool -> String -> Either String [Token]
|
|
107 | +cppLex sd s = case lexCppTokenStream s (init_state {scanning_directive = sd}) of
|
|
107 | 108 | Left err -> Left err
|
108 | 109 | Right (_inp, _st, toks) -> Right toks
|
109 | 110 | |
... | ... | @@ -141,4 +142,4 @@ t2 = doATest "# if ((m1) < 1 || (m1) == 1 && (m2) < 7 || (m1) == 1 && (m2) == |
141 | 142 | t3 :: Either String CppDirective
|
142 | 143 | t3 = parseDirective "# if FOO == 4"
|
143 | 144 | |
144 | -t4 = cppLex "#define foo(X) X" |
|
145 | +t4 = cppLex True "#define foo(X) X" |
... | ... | @@ -8,7 +8,7 @@ module ParserM ( |
8 | 8 | AlexInput (..),
|
9 | 9 | run_parser,
|
10 | 10 | -- Parser state
|
11 | - St,
|
|
11 | + St(..),
|
|
12 | 12 | init_state,
|
13 | 13 | StartCode,
|
14 | 14 | start_code,
|
... | ... | @@ -75,6 +75,7 @@ run_parser (ParserM f) = |
75 | 75 | data St = St
|
76 | 76 | { start_code :: !StartCode
|
77 | 77 | , brace_depth :: !Int
|
78 | + , scanning_directive :: !Bool
|
|
78 | 79 | }
|
79 | 80 | deriving (Show)
|
80 | 81 | type StartCode = Int
|
... | ... | @@ -84,6 +85,7 @@ init_state = |
84 | 85 | St
|
85 | 86 | { start_code = 0
|
86 | 87 | , brace_depth = 0
|
88 | + , scanning_directive = False
|
|
87 | 89 | }
|
88 | 90 | |
89 | 91 | -- Tokens
|
... | ... | @@ -281,7 +281,7 @@ processCpp ss = do |
281 | 281 | Right (CppDefine name args def) -> do
|
282 | 282 | ppDefine (MacroName name args) def
|
283 | 283 | Right (CppIf cond) -> do
|
284 | - val <- cppIf cond
|
|
284 | + val <- cppCond cond
|
|
285 | 285 | ar <- pushAccepting val
|
286 | 286 | acceptStateChange ar
|
287 | 287 | Right (CppIfdef name) -> do
|
... | ... | @@ -297,7 +297,7 @@ processCpp ss = do |
297 | 297 | ar <- setAccepting (not accepting)
|
298 | 298 | acceptStateChange ar
|
299 | 299 | Right (CppElIf cond) -> do
|
300 | - val <- cppIf cond
|
|
300 | + val <- cppCond cond
|
|
301 | 301 | ar <- setAccepting val
|
302 | 302 | acceptStateChange ar
|
303 | 303 | Right CppEndif -> do
|