Commit 12c57ecc by Zachary Snow

preprocessor cleanup and extended test coverage

parent 2885e21c
...@@ -38,14 +38,14 @@ data PP = PP ...@@ -38,14 +38,14 @@ data PP = PP
, ppIncludePaths :: [FilePath] -- folders to search for includes , ppIncludePaths :: [FilePath] -- folders to search for includes
, ppMacroStack :: [[(String, String)]] -- arguments for in-progress macro expansions , ppMacroStack :: [[(String, String)]] -- arguments for in-progress macro expansions
, ppIncludeStack :: [(FilePath, Env)] -- in-progress includes for loop detection , ppIncludeStack :: [(FilePath, Env)] -- in-progress includes for loop detection
} deriving (Eq, Show) }
-- keeps track of the state of an if-else cascade level -- keeps track of the state of an if-else cascade level
data Cond data Cond
= CurrentlyTrue -- an active if/elsif/else branch (condition is met) = CurrentlyTrue -- an active if/elsif/else branch (condition is met)
| PreviouslyTrue -- an inactive else/elsif block due to an earlier if/elsif | PreviouslyTrue -- an inactive else/elsif block due to an earlier if/elsif
| NeverTrue -- an inactive if/elsif block; a subsequent else will be met | NeverTrue -- an inactive if/elsif block; a subsequent else will be met
deriving (Eq, Show) deriving Eq
-- update a Cond for an `else block, where this block is active if and only if -- update a Cond for an `else block, where this block is active if and only if
-- no previous block was active -- no previous block was active
...@@ -288,8 +288,7 @@ takeThrough :: Char -> PPS String ...@@ -288,8 +288,7 @@ takeThrough :: Char -> PPS String
takeThrough goal = do takeThrough goal = do
str <- getInput str <- getInput
if null str if null str
then lexicalError $ then lexicalError $ "unexpected end of input, looking for " ++ show goal
"unexpected end of input, looking for " ++ (show goal)
else do else do
ch <- takeChar ch <- takeChar
if ch == goal if ch == goal
...@@ -366,24 +365,23 @@ takeMacroDefinition = do ...@@ -366,24 +365,23 @@ takeMacroDefinition = do
dropSpaces dropSpaces
body <- takeUntilNewline body <- takeUntilNewline
argsWithDefaults <- mapM splitArg args argsWithDefaults <- mapM splitArg args
if null args return (body, argsWithDefaults)
then lexicalError "macros cannot have 0 args"
else return (body, argsWithDefaults)
where where
splitArg :: String -> PPS (String, Maybe String) splitArg :: String -> PPS (String, Maybe String)
splitArg [] = lexicalError "macro defn. empty argument" splitArg [] = lexicalError "macro definition missing argument name"
splitArg str = do splitArg str =
let (name, rest) = span isIdentChar str if null name then
if null name || not (all isIdentChar name) then lexicalError $ "invalid macro definition argument: " ++ show str
lexicalError $ "invalid macro arg name: " ++ show name
else if null rest then else if null rest then
return (name, Nothing) return (name, Nothing)
else do else if leadCh /= '=' then
let leadCh : after = dropWhile isWhitespaceChar rest lexicalError $ "bad char after argument name: " ++ show leadCh
let value = dropWhile isWhitespaceChar after else
if leadCh /= '=' return (name, Just value)
then lexicalError $ "bad char after arg name: " ++ (show leadCh) where
else return (name, Just value) (name, rest) = span isIdentChar str
leadCh : after = dropWhile isWhitespaceChar rest
value = dropWhile isWhitespaceChar after
-- commas and right parens are forbidden outside matched pairs of: (), [], {}, -- commas and right parens are forbidden outside matched pairs of: (), [], {},
-- "", except to delimit arguments or end the list of arguments; see 22.5.1 -- "", except to delimit arguments or end the list of arguments; see 22.5.1
...@@ -393,7 +391,7 @@ takeMacroArguments = do ...@@ -393,7 +391,7 @@ takeMacroArguments = do
leadCh <- takeChar leadCh <- takeChar
if leadCh == '(' if leadCh == '('
then argLoop >>= mapM preprocessString then argLoop >>= mapM preprocessString
else lexicalError $ "expected begining of macro arguments, but found " else lexicalError $ "expected beginning of macro arguments, but found "
++ show leadCh ++ show leadCh
where where
argLoop :: PPS [String] argLoop :: PPS [String]
...@@ -466,12 +464,10 @@ dropWhitespace = do ...@@ -466,12 +464,10 @@ dropWhitespace = do
str <- getInput str <- getInput
case str of case str of
ch : chs -> ch : chs ->
if isWhitespaceChar ch when (isWhitespaceChar ch) $ do
then do
advancePosition ch advancePosition ch
setInput chs setInput chs
dropWhitespace dropWhitespace
else return ()
[] -> return () [] -> return ()
-- directives that must always be processed even if the current code block is -- directives that must always be processed even if the current code block is
...@@ -617,7 +613,7 @@ handleString = do ...@@ -617,7 +613,7 @@ handleString = do
[] -> lexicalError "unterminated string literal" [] -> lexicalError "unterminated string literal"
-- preprocess a "backtick string", which begins and ends with a backtick -- preprocess a "backtick string", which begins and ends with a backtick
-- followed by a slash (`"), and withing which macros can be invoked as normal; -- followed by a slash (`"), and within which macros can be invoked as normal;
-- otherwise, normal string literal rules apply, except that unescaped quotes -- otherwise, normal string literal rules apply, except that unescaped quotes
-- are forbidden, and backticks must be escaped using a backslash to avoid being -- are forbidden, and backticks must be escaped using a backslash to avoid being
-- interpreted as a macro or marking the end of a string -- interpreted as a macro or marking the end of a string
...@@ -733,9 +729,8 @@ handleDirective macrosOnly = do ...@@ -733,9 +729,8 @@ handleDirective macrosOnly = do
setFilePath filename setFilePath filename
let newPos = Position filename lineNumber 0 let newPos = Position filename lineNumber 0
setPosition newPos setPosition newPos
if 0 <= levelNumber && levelNumber <= 2 when (levelNumber < 0 || 2 < levelNumber) $
then return () lexicalError "line directive invalid level number"
else lexicalError "line directive invalid level number"
"include" -> do "include" -> do
lineLookahead lineLookahead
...@@ -884,9 +879,7 @@ advancePosition _ = do ...@@ -884,9 +879,7 @@ advancePosition _ = do
-- advances position for multiple characters -- advances position for multiple characters
advancePositions :: String -> PPS () advancePositions :: String -> PPS ()
advancePositions str = do advancePositions = mapM_ advancePosition
_ <- mapM advancePosition str
return ()
-- update the given position based on the movement of the given character -- update the given position based on the movement of the given character
advance :: Position -> Char -> Position advance :: Position -> Char -> Position
...@@ -897,16 +890,13 @@ advance (Position f l c) _ = Position f l (c + 1) ...@@ -897,16 +890,13 @@ advance (Position f l c) _ = Position f l (c + 1)
pushChar :: Char -> Position -> PPS () pushChar :: Char -> Position -> PPS ()
pushChar c p = do pushChar c p = do
condStack <- getCondStack condStack <- getCondStack
if any (/= CurrentlyTrue) condStack when (all (== CurrentlyTrue) condStack) $ do
then return ()
else do
output <- getOutput output <- getOutput
setOutput $ (c, p) : output setOutput $ (c, p) : output
-- adds a sequence of characters all at the same given position -- adds a sequence of characters all at the same given position
pushChars :: String -> Position -> PPS () pushChars :: String -> Position -> PPS ()
pushChars s p = do pushChars s p = mapM_ (flip pushChar p) s
_ <- mapM (flip pushChar p) s
return ()
-- search for a pattern in the input and remove remove characters up to and -- search for a pattern in the input and remove remove characters up to and
-- including the first occurrence of the pattern -- including the first occurrence of the pattern
......
// pattern: Reached EOF while looking for: "\*/"
/*
// pattern: Parse error: unexpected token '`'
module top;
``
endmodule
// pattern: unexpected end of input, looking for '>'
`include <foo
// pattern: bad char after argument name: '#'
`define MACRO(a#)
// pattern: invalid macro definition argument: "#"
`define MACRO(#)
// pattern: macro definition missing argument name
`define MACRO()
// pattern: illegal macro name: define
`define define
// pattern: too many macro arguments given
`define MACRO(a, b)
`MACRO(x, y, z)
// pattern: expected beginning of macro arguments, but found 'a'
`define MACRO(a)
`MACRO asdf
// pattern: unexpected end of input
`define MACRO(a)
`MACRO
// pattern: too few macro arguments given
`define MACRO(a, b)
`MACRO(x)
// pattern: compiler directives are forbidden inside strings
`"asdf `line`"
// pattern: unterminated backtick string
`"
// pattern: unterminated string literal
"
// pattern: `else directive outside of an `if/`endif block
`else
// pattern: `elsif directive outside of an `if/`endif block
`elsif
module top;
`define PRINT(str) initial $display(`"str`");
`PRINT(a)
`PRINT(\\)
endmodule
`define A
`undefineall
`ifndef A
module top;
initial $display("hi");
endmodule
`endif
module top;
initial $display("hi");
endmodule
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment