Skip to content

Commit

Permalink
warn on duplicate modules
Browse files Browse the repository at this point in the history
  • Loading branch information
zachjs committed Dec 15, 2024
1 parent 576a804 commit aa0a885
Show file tree
Hide file tree
Showing 6 changed files with 40 additions and 12 deletions.
1 change: 1 addition & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,7 @@
### Other Enhancements

* Improved error messages for invalid port or parameter bindings
* Added warning for modules or interfaces defined more than once
* `--write path/to/dir/` can now also be used with `--pass-through`

## v0.0.12
Expand Down
14 changes: 9 additions & 5 deletions src/Language/SystemVerilog/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,9 +19,11 @@ import Language.SystemVerilog.AST (AST)
import Language.SystemVerilog.Parser.Lex (lexStr)
import Language.SystemVerilog.Parser.Parse (parse)
import Language.SystemVerilog.Parser.Preprocess (preprocess, annotate, Env, Contents)
import Language.SystemVerilog.Parser.Tokens (Position)

type Output = (FilePath, AST)
type Strings = Set.Set String
type Positions = Map.Map String Position

data Config = Config
{ cfDefines :: [String]
Expand All @@ -36,7 +38,7 @@ data Context = Context
{ ctConfig :: Config
, ctEnv :: Env
, ctUsed :: Strings
, ctHave :: Strings
, ctHave :: Positions
}

-- parse CLI macro definitions into the internal macro environment format
Expand Down Expand Up @@ -70,15 +72,16 @@ parseFiles' context []
then return []
else parseFiles' context possibleFiles
where
missingParts = Set.toList $ ctUsed context Set.\\ ctHave context
missingParts = Set.toList $ ctUsed context Set.\\
(Map.keysSet $ ctHave context)
libdirs = cfLibraryPaths $ ctConfig context
lookupLibrary partName = ((partName, ) <$>) <$> lookupLibFile partName
lookupLibFile = liftIO . findFile libdirs . (++ ".sv")

-- load the files, but complain if an expected part is missing
parseFiles' context ((part, path) : files) = do
(context', ast) <- parseFile context path
let misdirected = not $ null part || Set.member part (ctHave context')
let misdirected = not $ null part || Map.member part (ctHave context')
when misdirected $ throwError $
"Expected to find module or interface " ++ show part ++ " in file "
++ show path ++ " selected from the library path."
Expand All @@ -89,9 +92,10 @@ parseFile :: Context -> FilePath -> ExceptT String IO (Context, AST)
parseFile context path = do
(context', contents) <- preprocessFile context path
tokens <- liftEither $ runExcept $ lexStr contents
(ast, used, have) <- parse (cfOversizedNumbers config) tokens
(ast, used, have') <-
parse (cfOversizedNumbers config) (ctHave context) tokens
let context'' = context' { ctUsed = used <> ctUsed context
, ctHave = have <> ctHave context }
, ctHave = have' }
return (context'', ast)
where config = ctConfig context

Expand Down
23 changes: 16 additions & 7 deletions src/Language/SystemVerilog/Parser/Parse.y
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ import Control.Monad.Except
import Control.Monad.State.Strict
import Data.Maybe (catMaybes, fromMaybe)
import System.IO (hPutStrLn, stderr)
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Language.SystemVerilog.AST
import Language.SystemVerilog.Parser.ParseDecl
Expand Down Expand Up @@ -1579,20 +1580,22 @@ data ParseData = ParseData
, pTokens :: [Token]
, pOversizedNumbers :: Bool
, pPartsUsed :: Strings
, pPartsHave :: Strings
, pPartsHave :: Positions
}

type ParseState = StateT ParseData (ExceptT String IO)
type Strings = Set.Set String
type Positions = Map.Map String Position

parse :: Bool -> [Token] -> ExceptT String IO (AST, Strings, Strings)
parse _ [] = return mempty
parse oversizedNumbers tokens = do
parse :: Bool -> Positions -> [Token]
-> ExceptT String IO (AST, Strings, Positions)
parse _ partsHave [] = return ([], Set.empty, partsHave)
parse oversizedNumbers partsHave tokens = do
(ast, finalState) <- runStateT parseMain initialState
return (ast, pPartsUsed finalState, pPartsHave finalState)
where
position = tokenPosition $ head tokens
initialState = ParseData position tokens oversizedNumbers mempty mempty
initialState = ParseData position tokens oversizedNumbers mempty partsHave

positionKeep :: (Token -> ParseState a) -> ParseState a
positionKeep cont = do
Expand Down Expand Up @@ -1885,8 +1888,14 @@ recordPartUsed item = return item

recordPartHave :: Identifier -> ParseState ()
recordPartHave partName = do
currPos <- gets pPosition
partsHave <- gets pPartsHave
let partsHave' = Set.insert partName partsHave
modify' $ \s -> s { pPartsHave = partsHave' }
case Map.lookup partName partsHave of
Nothing -> do
let partsHave' = Map.insert partName currPos partsHave
modify' $ \s -> s { pPartsHave = partsHave' }
Just prevPos ->
parseWarning currPos $ "Redefinition of " ++ show partName
++ ". Previously defined at " ++ show prevPos ++ "."

}
3 changes: 3 additions & 0 deletions test/warning/module_dupe_1.sv
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
module top;
logic x;
endmodule
3 changes: 3 additions & 0 deletions test/warning/module_dupe_2.sv
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
module top;
logic y;
endmodule
8 changes: 8 additions & 0 deletions test/warning/run.sh
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
NO_FILES_WARNING="Warning: No input files specified (try \`sv2v --help\`)"
INTERFACE_WARNING="Warning: Source includes an interface but the output is empty because there are no modules without any interface ports. Please convert interfaces alongside the modules that instantiate them."
PORT_CONN_ATTR_WARNING="attr.sv:6:11: Warning: Ignored port connection attributes (* foo *)(* bar *)."
DUPLICATE_MODULE_WARNING="module_dupe_2.sv:2:5: Warning: Redefinition of \"top\". Previously defined at module_dupe_1.sv:2:5."

test_default() {
runAndCapture \
Expand All @@ -28,6 +29,13 @@ test_port_conn_attr() {
assertEquals "stderr should should have warning" "$PORT_CONN_ATTR_WARNING" "$stderr"
}

test_duplicate_module() {
runAndCapture module_dupe_1.sv module_dupe_2.sv
assertTrue "conversion should succeed" $result
assertNotNull "stdout should not be empty" "$stdout"
assertEquals "stderr should should have warning" "$DUPLICATE_MODULE_WARNING" "$stderr"
}

no_modules_test() {
file=$1
warning="$2"
Expand Down

0 comments on commit aa0a885

Please sign in to comment.