Commit 0d9ed3e1 by Zachary Snow

updated CLI to support include dirs and multiple files

parent 7e37fe43
...@@ -41,11 +41,12 @@ The interface for this tool has not yet been finalized. Currently, running `sv2v ...@@ -41,11 +41,12 @@ The interface for this tool has not yet been finalized. Currently, running `sv2v
path/to/file.sv` will output the converted file to `stdout`. path/to/file.sv` will output the converted file to `stdout`.
``` ```
sv2v [OPTIONS] [FILE] sv2v [OPTIONS] [FILES]
Common flags: Common flags:
-e --exclude=CONV conversion to exclude (always, interface, logic); can -e --exclude=CONV conversion to exclude (always, interface, logic); can
be specified multiple times be specified multiple times
-i --incdir=DIR add directory to include search path
-? --help Display help message -? --help Display help message
-V --version Print version information -V --version Print version information
--numeric-version Print just the version number --numeric-version Print just the version number
......
...@@ -17,7 +17,8 @@ data Exclude ...@@ -17,7 +17,8 @@ data Exclude
data Job = Job data Job = Job
{ exclude :: [Exclude] { exclude :: [Exclude]
, file :: FilePath , files :: [FilePath]
, incdir :: [FilePath]
} deriving (Show, Typeable, Data) } deriving (Show, Typeable, Data)
defaultJob :: Job defaultJob :: Job
...@@ -26,7 +27,8 @@ defaultJob = Job ...@@ -26,7 +27,8 @@ defaultJob = Job
&= help &= help
("conversion to exclude (always, interface, logic)" ("conversion to exclude (always, interface, logic)"
++ "; can be specified multiple times") ++ "; can be specified multiple times")
, file = def &= args &= typFile , files = def &= args &= typ "FILES"
, incdir = def &= typDir &= help "add directory to include search path"
} }
&= program "sv2v" &= program "sv2v"
&= summary "sv2v v0.0.1, (C) Zachary Snow 2019, Tom Hawkins, 2011-2015" &= summary "sv2v v0.0.1, (C) Zachary Snow 2019, Tom Hawkins, 2011-2015"
......
...@@ -6,17 +6,12 @@ module Language.SystemVerilog.Parser ...@@ -6,17 +6,12 @@ module Language.SystemVerilog.Parser
) where ) where
import Language.SystemVerilog.AST import Language.SystemVerilog.AST
import Language.SystemVerilog.Parser.Lex
import Language.SystemVerilog.Parser.Parse import Language.SystemVerilog.Parser.Parse
import Language.SystemVerilog.Parser.Preprocess import Language.SystemVerilog.Parser.Preprocess
import Control.Monad.State
import qualified Data.Map.Strict as Map
-- parses a file given a table of predefined macros and the file name -- parses a file given a table of predefined macros and the file name
parseFile :: [(String, String)] -> FilePath -> IO AST parseFile :: [String] -> [(String, String)] -> FilePath -> IO AST
parseFile env file = do parseFile includePaths env file =
let initialEnv = Map.map alexScanTokens $ Map.fromList env loadFile file >>=
let initialState = PP initialEnv [] preprocess includePaths env >>=
ast <- evalStateT (loadFile file) initialState return . descriptions
return $ descriptions ast
...@@ -5,13 +5,15 @@ ...@@ -5,13 +5,15 @@
-} -}
module Language.SystemVerilog.Parser.Preprocess module Language.SystemVerilog.Parser.Preprocess
( loadFile ( loadFile
, preprocess
, PP (..) , PP (..)
) where ) where
import Control.Monad.State import Control.Monad.State
import Data.List (intercalate) import Data.List (intercalate)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import System.FilePath (replaceFileName) import System.FilePath (dropFileName)
import System.Directory (findFile)
import Language.SystemVerilog.Parser.Lex import Language.SystemVerilog.Parser.Lex
import Language.SystemVerilog.Parser.Tokens import Language.SystemVerilog.Parser.Tokens
...@@ -23,9 +25,6 @@ isNewline (Token t _ _) = t == Spe_Newline ...@@ -23,9 +25,6 @@ isNewline (Token t _ _) = t == Spe_Newline
unskippableDirectives :: [String] unskippableDirectives :: [String]
unskippableDirectives = ["else", "elsif", "endif", "ifdef", "ifndef"] unskippableDirectives = ["else", "elsif", "endif", "ifdef", "ifndef"]
preprocess :: [Token] -> (StateT PP IO) [Token]
preprocess tokens = pp tokens >>= return . combineNumbers
-- a bit of a hack to allow things like: `WIDTH'b0 -- a bit of a hack to allow things like: `WIDTH'b0
combineNumbers :: [Token] -> [Token] combineNumbers :: [Token] -> [Token]
combineNumbers (Token Lit_number size pos : Token Lit_number ('\'' : num) _ : tokens) = combineNumbers (Token Lit_number size pos : Token Lit_number ('\'' : num) _ : tokens) =
...@@ -33,6 +32,16 @@ combineNumbers (Token Lit_number size pos : Token Lit_number ('\'' : num) _ : to ...@@ -33,6 +32,16 @@ combineNumbers (Token Lit_number size pos : Token Lit_number ('\'' : num) _ : to
combineNumbers (token : tokens) = token : combineNumbers tokens combineNumbers (token : tokens) = token : combineNumbers tokens
combineNumbers [] = [] combineNumbers [] = []
includeSearch :: FilePath -> FilePath -> (StateT PP IO) FilePath
includeSearch base file = do
includePaths <- gets ppIncludePaths
let directories = dropFileName base : includePaths
result <- lift $ findFile directories file
case result of
Just path -> return path
Nothing ->
error $ "Could not find file " ++ file ++ " included from " ++ base
data Cond data Cond
= CurrentlyTrue = CurrentlyTrue
| PreviouslyTrue | PreviouslyTrue
...@@ -42,6 +51,7 @@ data Cond ...@@ -42,6 +51,7 @@ data Cond
data PP = PP data PP = PP
{ ppEnv :: Map.Map String [Token] { ppEnv :: Map.Map String [Token]
, ppCondStack :: [Cond] , ppCondStack :: [Cond]
, ppIncludePaths :: [FilePath]
} deriving (Eq, Show) } deriving (Eq, Show)
pp :: [Token] -> (StateT PP IO) [Token] pp :: [Token] -> (StateT PP IO) [Token]
...@@ -81,10 +91,9 @@ pp (Token Spe_Directive str pos : tokens) = do ...@@ -81,10 +91,9 @@ pp (Token Spe_Directive str pos : tokens) = do
"include" -> do "include" -> do
let file = init $ tail $ tokenString $ head tokens let file = init $ tail $ tokenString $ head tokens
let Position basePath _ _ = pos let Position basePath _ _ = pos
let filePath = replaceFileName basePath file filePath <- includeSearch basePath file
includedTokens <- loadFile filePath includedTokens <- lift $ loadFile filePath
remainingTokens <- pp $ tail tokens pp $ includedTokens ++ tail tokens
return $ includedTokens ++ remainingTokens
"ifdef" -> do "ifdef" -> do
let name = tokenString $ head tokens let name = tokenString $ head tokens
...@@ -163,14 +172,19 @@ pp (token : tokens) = do ...@@ -163,14 +172,19 @@ pp (token : tokens) = do
then return tokens' then return tokens'
else return $ token : tokens' else return $ token : tokens'
-- loads, lexes, and preprocesses the file at the given path -- loads and lexes the file at the given path
loadFile :: FilePath -> (StateT PP IO) [Token] loadFile :: FilePath -> IO [Token]
loadFile file = do loadFile file = do
content <- lift $ readFile file content <- readFile file
preprocess $ let tokens = alexScanTokens content
map relocate $ return $ map relocate tokens
alexScanTokens $
content
where where
relocate :: Token -> Token relocate :: Token -> Token
relocate (Token t s (Position _ l c)) = Token t s $ Position file l c relocate (Token t s (Position _ l c)) = Token t s $ Position file l c
preprocess :: [String] -> [(String, String)] -> [Token] -> IO [Token]
preprocess includePaths env tokens = do
let initialEnv = Map.map alexScanTokens $ Map.fromList env
let initialState = PP initialEnv [] includePaths
res <- evalStateT (pp tokens) initialState
return $ combineNumbers res
...@@ -7,7 +7,7 @@ ...@@ -7,7 +7,7 @@
import System.IO import System.IO
import System.Exit import System.Exit
import Job (readJob, file, exclude) import Job (readJob, files, exclude, incdir)
import Convert (convert) import Convert (convert)
import Language.SystemVerilog.Parser import Language.SystemVerilog.Parser
...@@ -15,8 +15,9 @@ main :: IO () ...@@ -15,8 +15,9 @@ main :: IO ()
main = do main = do
job <- readJob job <- readJob
-- parse the input file -- parse the input file
let filePath = file job let includePaths = incdir job
ast <- parseFile [] filePath asts <- mapM (parseFile includePaths []) (files job)
let ast = concat asts
-- convert the file -- convert the file
let ast' = convert (exclude job) ast let ast' = convert (exclude job) ast
-- print the converted file out -- print the converted file out
......
...@@ -27,6 +27,7 @@ executable sv2v ...@@ -27,6 +27,7 @@ executable sv2v
base, base,
cmdargs, cmdargs,
containers, containers,
directory,
filepath, filepath,
mtl mtl
other-modules: other-modules:
......
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