Commit 04d65bb3 by Zachary Snow

added --write directory mode with one file per module

parent 911243da
...@@ -6,6 +6,8 @@ ...@@ -6,6 +6,8 @@
automatically load modules and interfaces used in the design that are not automatically load modules and interfaces used in the design that are not
found in the provided input files found in the provided input files
* Added `--top` for pruning unneeded modules during conversion * Added `--top` for pruning unneeded modules during conversion
* Added `--write path/to/dir/` for creating an output `.v` in the specified
preexisting directory for each module in the converted result
* The `string` data type is now dropped from parameters and localparams * The `string` data type is now dropped from parameters and localparams
* Added support for passing through `sequence` and `property` declarations * Added support for passing through `sequence` and `property` declarations
......
...@@ -104,9 +104,11 @@ Conversion: ...@@ -104,9 +104,11 @@ Conversion:
-E --exclude=CONV Exclude a particular conversion (Always, Assert, -E --exclude=CONV Exclude a particular conversion (Always, Assert,
Interface, Logic, or UnbasedUnsized) Interface, Logic, or UnbasedUnsized)
-v --verbose Retain certain conversion artifacts -v --verbose Retain certain conversion artifacts
-w --write=MODE/FILE How to write output; default is 'stdout'; use -w --write=MODE/FILE/DIR How to write output; default is 'stdout'; use
'adjacent' to create a .v file next to each input; 'adjacent' to create a .v file next to each input;
use a path ending in .v to write to a file use a path ending in .v to write to a file; use a
path to an existing directory to create a .v within
for each converted module
--top=NAME Remove uninstantiated modules except the given --top=NAME Remove uninstantiated modules except the given
top module; can be used multiple times top module; can be used multiple times
Other: Other:
......
...@@ -8,6 +8,7 @@ ...@@ -8,6 +8,7 @@
module Job where module Job where
import Control.Monad (when)
import Data.Char (toLower) import Data.Char (toLower)
import Data.List (isPrefixOf, isSuffixOf) import Data.List (isPrefixOf, isSuffixOf)
import Data.Version (showVersion) import Data.Version (showVersion)
...@@ -15,6 +16,7 @@ import GitHash (giDescribe, tGitInfoCwdTry) ...@@ -15,6 +16,7 @@ import GitHash (giDescribe, tGitInfoCwdTry)
import qualified Paths_sv2v (version) import qualified Paths_sv2v (version)
import System.IO (stderr, hPutStr) import System.IO (stderr, hPutStr)
import System.Console.CmdArgs import System.Console.CmdArgs
import System.Directory (doesDirectoryExist)
import System.Environment (getArgs, withArgs) import System.Environment (getArgs, withArgs)
import System.Exit (exitFailure) import System.Exit (exitFailure)
...@@ -31,6 +33,7 @@ data Write ...@@ -31,6 +33,7 @@ data Write
= Stdout = Stdout
| Adjacent | Adjacent
| File FilePath | File FilePath
| Directory FilePath
deriving (Typeable, Data) deriving (Typeable, Data)
data Job = Job data Job = Job
...@@ -75,10 +78,12 @@ defaultJob = Job ...@@ -75,10 +78,12 @@ defaultJob = Job
++ " Logic, or UnbasedUnsized)") ++ " Logic, or UnbasedUnsized)")
, verbose = nam "verbose" &= help "Retain certain conversion artifacts" , verbose = nam "verbose" &= help "Retain certain conversion artifacts"
, write = Stdout &= ignore -- parsed from the flexible flag below , write = Stdout &= ignore -- parsed from the flexible flag below
, writeRaw = "s" &= name "write" &= name "w" &= explicit &= typ "MODE/FILE" , writeRaw = "s" &= name "write" &= name "w" &= explicit
&= typ "MODE/FILE/DIR"
&= help ("How to write output; default is 'stdout'; use 'adjacent' to" &= help ("How to write output; default is 'stdout'; use 'adjacent' to"
++ " create a .v file next to each input; use a path ending in .v" ++ " create a .v file next to each input; use a path ending in .v"
++ " to write to a file") ++ " to write to a file; use a path to an existing directory to"
++ " create a .v within for each converted module")
, top = def &= name "top" &= explicit &= typ "NAME" , top = def &= name "top" &= explicit &= typ "NAME"
&= help ("Remove uninstantiated modules except the given top module;" &= help ("Remove uninstantiated modules except the given top module;"
++ " can be used multiple times") ++ " can be used multiple times")
...@@ -108,9 +113,13 @@ parseWrite w | w `matches` "stdout" = return Stdout ...@@ -108,9 +113,13 @@ parseWrite w | w `matches` "stdout" = return Stdout
parseWrite w | w `matches` "adjacent" = return Adjacent parseWrite w | w `matches` "adjacent" = return Adjacent
parseWrite w | ".v" `isSuffixOf` w = return $ File w parseWrite w | ".v" `isSuffixOf` w = return $ File w
parseWrite w | otherwise = do parseWrite w | otherwise = do
hPutStr stderr $ "invalid --write " ++ show w isDir <- doesDirectoryExist w
++ ", expected stdout, adjacent, or a path ending in .v" when (not isDir) $ do
exitFailure hPutStr stderr $ "invalid --write " ++ show w ++ ", expected stdout,"
++ " adjacent, a path ending in .v, or a path to an existing"
++ " directory"
exitFailure
return $ Directory w
matches :: String -> String -> Bool matches :: String -> String -> Bool
matches = isPrefixOf . map toLower matches = isPrefixOf . map toLower
...@@ -142,11 +151,16 @@ readJob = do ...@@ -142,11 +151,16 @@ readJob = do
>>= flagRename "-e" "-E" >>= flagRename "-e" "-E"
withArgs strs' $ cmdArgs defaultJob withArgs strs' $ cmdArgs defaultJob
>>= setWrite . setSuccinct >>= setWrite . setSuccinct
where
setWrite :: Job -> IO Job setWrite :: Job -> IO Job
setWrite job = do setWrite job = do
w <- parseWrite $ writeRaw job w <- parseWrite $ writeRaw job
return $ job { write = w } case (w, passThrough job) of
setSuccinct :: Job -> Job (Directory{}, True) -> do
setSuccinct job | verbose job = job { exclude = Succinct : exclude job } hPutStr stderr "can't use --pass-through when writing to a dir"
setSuccinct job | otherwise = job exitFailure
_ -> return $ job { write = w }
setSuccinct :: Job -> Job
setSuccinct job | verbose job = job { exclude = Succinct : exclude job }
setSuccinct job | otherwise = job
...@@ -6,6 +6,7 @@ ...@@ -6,6 +6,7 @@
import System.IO (hPrint, hPutStrLn, stderr, stdout) import System.IO (hPrint, hPutStrLn, stderr, stdout)
import System.Exit (exitFailure, exitSuccess) import System.Exit (exitFailure, exitSuccess)
import System.FilePath (combine, splitExtension)
import Control.Monad (when, zipWithM_) import Control.Monad (when, zipWithM_)
import Control.Monad.Except (runExceptT) import Control.Monad.Except (runExceptT)
...@@ -50,7 +51,18 @@ rewritePath path = do ...@@ -50,7 +51,18 @@ rewritePath path = do
return $ base ++ ".v" return $ base ++ ".v"
where where
ext = ".sv" ext = ".sv"
(base, end) = splitAt (length path - length ext) path (base, end) = splitExtension path
splitModules :: FilePath -> AST -> [(FilePath, String)]
splitModules dir (PackageItem (Decl CommentDecl{}) : ast) =
splitModules dir ast
splitModules dir (description : ast) =
(path, output) : splitModules dir ast
where
Part _ _ Module _ name _ _ = description
path = combine dir $ name ++ ".v"
output = show description ++ "\n"
splitModules _ [] = []
writeOutput :: Write -> [FilePath] -> [AST] -> IO () writeOutput :: Write -> [FilePath] -> [AST] -> IO ()
writeOutput _ [] [] = writeOutput _ [] [] =
...@@ -63,6 +75,9 @@ writeOutput Adjacent inPaths asts = do ...@@ -63,6 +75,9 @@ writeOutput Adjacent inPaths asts = do
outPaths <- mapM rewritePath inPaths outPaths <- mapM rewritePath inPaths
let results = map (++ "\n") $ map show asts let results = map (++ "\n") $ map show asts
zipWithM_ writeFile outPaths results zipWithM_ writeFile outPaths results
writeOutput (Directory d) _ asts = do
let (outPaths, outputs) = unzip $ splitModules d $ concat asts
zipWithM_ writeFile outPaths outputs
main :: IO () main :: IO ()
main = do main = do
......
...@@ -2,6 +2,7 @@ ...@@ -2,6 +2,7 @@
clearArtifacts() { clearArtifacts() {
rm -f one.v two.v rm -f one.v two.v
rm -rf dirout
} }
createArtifacts() { createArtifacts() {
...@@ -81,12 +82,40 @@ test_file() { ...@@ -81,12 +82,40 @@ test_file() {
clearArtifacts clearArtifacts
} }
test_directory() {
runAndCapture *.sv
expected="$stdout"
rm -f dirout/*
mkdir -p dirout
runAndCapture --pass-through --write dirout *.sv
assertFalse "directory conversion should succeed" $result
assertNull "stdout should be empty" "$stdout"
assertEquals "stderr should have expected message" \
"can't use --pass-through when writing to a dir" \
"$stderr"
runAndCapture --write dirout *.sv
assertTrue "directory conversion should succeed" $result
assertNull "stdout should be empty" "$stdout"
assertNull "stderr should be empty" "$stderr"
assertTrue "one.v should exist" "[ -f dirout/one.v ]"
assertTrue "two.v should exist" "[ -f dirout/two.v ]"
assertTrue "three.v should exist" "[ -f dirout/three.v ]"
actual=`cat dirout/*.v`
assertEquals "directory output should match combined" "$expected" "$actual"
clearArtifacts
}
test_unknown() { test_unknown() {
runAndCapture --write=unknown *.sv runAndCapture --write=unknown *.sv
assertFalse "unknown write mode should fail" $result assertFalse "unknown write mode should fail" $result
assertNull "stdout should be empty" "$stdout" assertNull "stdout should be empty" "$stdout"
assertEquals "stderr should list valid write modes" \ assertEquals "stderr should list valid write modes" \
"invalid --write \"unknown\", expected stdout, adjacent, or a path ending in .v" \ "invalid --write \"unknown\", expected stdout, adjacent, a path ending in .v, or a path to an existing directory" \
"$stderr" "$stderr"
} }
......
package P;
typedef logic T;
endpackage
module three;
P::T x;
endmodule
module two; module two;
logic x; logic x;
endmodule 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