Commit f44e3e80 by Zachary Snow

add option to skip preprocessing

parent f5881919
...@@ -77,8 +77,9 @@ Preprocessing: ...@@ -77,8 +77,9 @@ Preprocessing:
-D --define=NAME[=VALUE] Define a macro for preprocessing -D --define=NAME[=VALUE] Define a macro for preprocessing
--siloed Lex input files separately, so macros from --siloed Lex input files separately, so macros from
earlier files are not defined in later files earlier files are not defined in later files
--skip-preprocessor Disable preprocessor
Conversion: Conversion:
-E --exclude=CONV Exclude a particular conversion (always, -E --exclude=CONV Exclude a particular conversion (always, assert,
interface, or logic) interface, or logic)
-v --verbose Retain certain conversion artifacts -v --verbose Retain certain conversion artifacts
Other: Other:
......
...@@ -26,6 +26,7 @@ data Job = Job ...@@ -26,6 +26,7 @@ data Job = Job
, incdir :: [FilePath] , incdir :: [FilePath]
, define :: [String] , define :: [String]
, siloed :: Bool , siloed :: Bool
, skipPreprocessor :: Bool
, exclude :: [Exclude] , exclude :: [Exclude]
, verbose :: Bool , verbose :: Bool
} deriving (Show, Typeable, Data) } deriving (Show, Typeable, Data)
...@@ -45,8 +46,10 @@ defaultJob = Job ...@@ -45,8 +46,10 @@ defaultJob = Job
&= help "Define a macro for preprocessing" &= help "Define a macro for preprocessing"
, siloed = nam_ "siloed" &= help ("Lex input files separately, so" , siloed = nam_ "siloed" &= help ("Lex input files separately, so"
++ " macros from earlier files are not defined in later files") ++ " macros from earlier files are not defined in later files")
, skipPreprocessor = nam_ "skip-preprocessor" &= help "Disable preprocessor"
, exclude = nam_ "exclude" &= name "E" &= typ "CONV" , exclude = nam_ "exclude" &= name "E" &= typ "CONV"
&= help "Exclude a particular conversion (always, assert, interface, or logic)" &= help ("Exclude a particular conversion (always, assert, interface,"
++ " or logic)")
&= groupname "Conversion" &= groupname "Conversion"
, verbose = nam "verbose" &= help "Retain certain conversion artifacts" , verbose = nam "verbose" &= help "Retain certain conversion artifacts"
} }
......
...@@ -11,29 +11,30 @@ import qualified Data.Map.Strict as Map ...@@ -11,29 +11,30 @@ import qualified Data.Map.Strict as Map
import Language.SystemVerilog.AST (AST) import Language.SystemVerilog.AST (AST)
import Language.SystemVerilog.Parser.Lex (lexStr) import Language.SystemVerilog.Parser.Lex (lexStr)
import Language.SystemVerilog.Parser.Parse (parse) import Language.SystemVerilog.Parser.Parse (parse)
import Language.SystemVerilog.Parser.Preprocess (preprocess, Env) import Language.SystemVerilog.Parser.Preprocess (preprocess, annotate, Env)
import Language.SystemVerilog.Parser.Tokens (Position(..), tokenPosition) import Language.SystemVerilog.Parser.Tokens (Position(..), tokenPosition)
-- parses a compilation unit given include search paths and predefined macros -- parses a compilation unit given include search paths and predefined macros
parseFiles :: [FilePath] -> [(String, String)] -> Bool -> [FilePath] -> IO (Either String [AST]) parseFiles :: [FilePath] -> [(String, String)] -> Bool -> Bool -> [FilePath] -> IO (Either String [AST])
parseFiles includePaths defines siloed paths = do parseFiles includePaths defines siloed skipPreprocessor paths = do
let env = Map.map (\a -> (a, [])) $ Map.fromList defines let env = Map.map (\a -> (a, [])) $ Map.fromList defines
runExceptT (parseFiles' includePaths env siloed paths) runExceptT (parseFiles' includePaths env siloed skipPreprocessor paths)
-- parses a compilation unit given include search paths and predefined macros -- parses a compilation unit given include search paths and predefined macros
parseFiles' :: [FilePath] -> Env -> Bool -> [FilePath] -> ExceptT String IO [AST] parseFiles' :: [FilePath] -> Env -> Bool -> Bool -> [FilePath] -> ExceptT String IO [AST]
parseFiles' _ _ _ [] = return [] parseFiles' _ _ _ _ [] = return []
parseFiles' includePaths env siloed (path : paths) = do parseFiles' includePaths env siloed skipPreprocessor (path : paths) = do
(ast, envEnd) <- parseFile' includePaths env path (ast, envEnd) <- parseFile' includePaths env skipPreprocessor path
let envNext = if siloed then env else envEnd let envNext = if siloed then env else envEnd
asts <- parseFiles' includePaths envNext siloed paths asts <- parseFiles' includePaths envNext siloed skipPreprocessor paths
return $ ast : asts return $ ast : asts
-- parses a file given include search paths, a table of predefined macros, and -- parses a file given include search paths, a table of predefined macros, and
-- the file path -- the file path
parseFile' :: [String] -> Env -> FilePath -> ExceptT String IO (AST, Env) parseFile' :: [String] -> Env -> Bool -> FilePath -> ExceptT String IO (AST, Env)
parseFile' includePaths env path = do parseFile' includePaths env skipPreprocessor path = do
preResult <- liftIO $ preprocess includePaths env path let runner = if skipPreprocessor then annotate else preprocess
preResult <- liftIO $ runner includePaths env path
(contents, env') <- liftEither preResult (contents, env') <- liftEither preResult
result <- liftIO $ uncurry lexStr $ unzip contents result <- liftIO $ uncurry lexStr $ unzip contents
tokens <- liftEither result tokens <- liftEither result
......
...@@ -9,6 +9,7 @@ ...@@ -9,6 +9,7 @@
-} -}
module Language.SystemVerilog.Parser.Preprocess module Language.SystemVerilog.Parser.Preprocess
( preprocess ( preprocess
, annotate
, Env , Env
) where ) where
...@@ -66,6 +67,21 @@ preprocess includePaths env path = do ...@@ -66,6 +67,21 @@ preprocess includePaths env path = do
output = reverse $ ppOutput finalState output = reverse $ ppOutput finalState
env' = ppEnv finalState env' = ppEnv finalState
-- position annotator entrypoint used for files that don't need any
-- preprocessing
annotate :: [String] -> Env -> FilePath -> IO (Either String ([(Char, Position)], Env))
annotate _ env path = do
contents <-
if path == "-"
then getContents
else loadFile path
let positions = scanl advance (Position path 1 1) contents
return $ Right (zip contents positions, env)
where
advance :: Position -> Char -> Position
advance (Position f l _) '\n' = Position f (l + 1) 1
advance (Position f l c) _ = Position f l (c + 1)
-- read in the given file -- read in the given file
loadFile :: FilePath -> IO String loadFile :: FilePath -> IO String
loadFile path = do loadFile path = do
......
...@@ -8,7 +8,7 @@ import System.IO ...@@ -8,7 +8,7 @@ import System.IO
import System.Exit import System.Exit
import Data.List (elemIndex) import Data.List (elemIndex)
import Job (readJob, files, exclude, incdir, define, siloed) import Job (readJob, files, exclude, incdir, define, siloed, skipPreprocessor)
import Convert (convert) import Convert (convert)
import Language.SystemVerilog.Parser (parseFiles) import Language.SystemVerilog.Parser (parseFiles)
...@@ -23,7 +23,8 @@ main = do ...@@ -23,7 +23,8 @@ main = do
job <- readJob job <- readJob
-- parse the input files -- parse the input files
let defines = map splitDefine $ define job let defines = map splitDefine $ define job
result <- parseFiles (incdir job) defines (siloed job) (files job) result <- parseFiles (incdir job) defines (siloed job)
(skipPreprocessor job) (files job)
case result of case result of
Left msg -> do Left msg -> do
hPutStr stderr $ msg ++ "\n" hPutStr stderr $ msg ++ "\n"
......
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