diff --git a/CHANGELOG.md b/CHANGELOG.md index b4cd8c1..059a6ab 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -5,6 +5,7 @@ * Added conversion of severity system tasks and elaboration system tasks (e.g., `$info`) into `$display` tasks that include source file and scope information; pass `-E SeverityTask` to disable this new conversion +* Added support for gate arrays and conversion for multidimensional gate arrays * Added parsing support for `not`, `strong`, `weak`, `nexttime`, and `s_nexttime` in assertion property expressions * Added `--bugpoint` utility for minimizing test cases for issue submission diff --git a/src/Convert/ImplicitNet.hs b/src/Convert/ImplicitNet.hs index 62e215f..ec8e6b1 100644 --- a/src/Convert/ImplicitNet.hs +++ b/src/Convert/ImplicitNet.hs @@ -54,12 +54,12 @@ traverseModuleItemM _ (Genvar x) = traverseModuleItemM defaultNetType orig@(Assign _ x _) = do needsLHS defaultNetType x return orig -traverseModuleItemM defaultNetType orig@(NInputGate _ _ x lhs exprs) = do +traverseModuleItemM defaultNetType orig@(NInputGate _ _ x _ lhs exprs) = do insertElem x () needsLHS defaultNetType lhs _ <- mapM (needsExpr defaultNetType) exprs return orig -traverseModuleItemM defaultNetType orig@(NOutputGate _ _ x lhss expr) = do +traverseModuleItemM defaultNetType orig@(NOutputGate _ _ x _ lhss expr) = do insertElem x () _ <- mapM (needsLHS defaultNetType) lhss needsExpr defaultNetType expr diff --git a/src/Convert/MultiplePacked.hs b/src/Convert/MultiplePacked.hs index b05d2c2..ebb8284 100644 --- a/src/Convert/MultiplePacked.hs +++ b/src/Convert/MultiplePacked.hs @@ -89,20 +89,32 @@ flattenType t = flattenFields :: [Field] -> [Field] flattenFields = map $ first flattenType +traverseInstanceRanges :: Identifier -> [Range] -> Scoper TypeInfo [Range] +traverseInstanceRanges x rs + | length rs <= 1 = return rs + | otherwise = do + let t = Implicit Unspecified rs + tScoped <- scopeType t + insertElem x (tScoped, []) + let r1 : r2 : rest = rs + return $ (combineRanges r1 r2) : rest + traverseModuleItemM :: ModuleItem -> Scoper TypeInfo ModuleItem traverseModuleItemM (Instance m p x rs l) = do -- converts multi-dimensional instances - rs' <- if length rs <= 1 - then return rs - else do - let t = Implicit Unspecified rs - tScoped <- scopeType t - insertElem x (tScoped, []) - let r1 : r2 : rest = rs - return $ (combineRanges r1 r2) : rest + rs' <- traverseInstanceRanges x rs traverseExprsM traverseExprM $ Instance m p x rs' l -traverseModuleItemM item = - traverseLHSsM traverseLHSM item >>= +traverseModuleItemM (NInputGate kw d x rs lhs exprs) = do + rs' <- traverseInstanceRanges x rs + traverseModuleItemM' $ NInputGate kw d x rs' lhs exprs +traverseModuleItemM (NOutputGate kw d x rs lhss expr) = do + rs' <- traverseInstanceRanges x rs + traverseModuleItemM' $ NOutputGate kw d x rs' lhss expr +traverseModuleItemM item = traverseModuleItemM' item + +traverseModuleItemM' :: ModuleItem -> Scoper TypeInfo ModuleItem +traverseModuleItemM' = + traverseLHSsM traverseLHSM >=> traverseExprsM traverseExprM -- combines two ranges into one flattened range diff --git a/src/Convert/Traverse.hs b/src/Convert/Traverse.hs index 1f5880e..2b90bda 100644 --- a/src/Convert/Traverse.hs +++ b/src/Convert/Traverse.hs @@ -606,16 +606,18 @@ traverseNodesM exprMapper declMapper typeMapper lhsMapper stmtMapper = return $ Instance m p' x rs' l' moduleItemMapper (Modport x l) = mapM modportDeclMapper l >>= return . Modport x - moduleItemMapper (NInputGate kw d x lhs exprs) = do + moduleItemMapper (NInputGate kw d x rs lhs exprs) = do d' <- exprMapper d exprs' <- mapM exprMapper exprs + rs' <- mapM (mapBothM exprMapper) rs lhs' <- lhsMapper lhs - return $ NInputGate kw d' x lhs' exprs' - moduleItemMapper (NOutputGate kw d x lhss expr) = do + return $ NInputGate kw d' x rs' lhs' exprs' + moduleItemMapper (NOutputGate kw d x rs lhss expr) = do d' <- exprMapper d + rs' <- mapM (mapBothM exprMapper) rs lhss' <- mapM lhsMapper lhss expr' <- exprMapper expr - return $ NOutputGate kw d' x lhss' expr' + return $ NOutputGate kw d' x rs' lhss' expr' moduleItemMapper (Genvar x) = return $ Genvar x moduleItemMapper (Generate items) = do items' <- mapM (traverseNestedGenItemsM genItemMapper) items @@ -768,12 +770,12 @@ traverseLHSsM mapper = traverseModuleItemLHSsM (Defparam lhs expr) = do lhs' <- mapper lhs return $ Defparam lhs' expr - traverseModuleItemLHSsM (NOutputGate kw d x lhss expr) = do + traverseModuleItemLHSsM (NOutputGate kw d x rs lhss expr) = do lhss' <- mapM mapper lhss - return $ NOutputGate kw d x lhss' expr - traverseModuleItemLHSsM (NInputGate kw d x lhs exprs) = do + return $ NOutputGate kw d x rs lhss' expr + traverseModuleItemLHSsM (NInputGate kw d x rs lhs exprs) = do lhs' <- mapper lhs - return $ NInputGate kw d x lhs' exprs + return $ NInputGate kw d x rs lhs' exprs traverseModuleItemLHSsM (AssertionItem (MIAssertion mx a)) = do converted <- traverseNestedStmtsM (traverseStmtLHSsM mapper) (Assertion a) diff --git a/src/Convert/UnnamedGenBlock.hs b/src/Convert/UnnamedGenBlock.hs index d6c05ce..42b31cd 100644 --- a/src/Convert/UnnamedGenBlock.hs +++ b/src/Convert/UnnamedGenBlock.hs @@ -33,9 +33,9 @@ initialState = ([], 1) traverseModuleItemM :: ModuleItem -> S ModuleItem traverseModuleItemM item@(Genvar x) = declaration x item -traverseModuleItemM item@(NInputGate _ _ x _ _) = declaration x item -traverseModuleItemM item@(NOutputGate _ _ x _ _) = declaration x item -traverseModuleItemM item@(Instance _ _ x _ _) = declaration x item +traverseModuleItemM item@(NInputGate _ _ x _ _ _) = declaration x item +traverseModuleItemM item@(NOutputGate _ _ x _ _ _) = declaration x item +traverseModuleItemM item@(Instance _ _ x _ _) = declaration x item traverseModuleItemM (MIPackageItem (Decl decl)) = traverseDeclM decl >>= return . MIPackageItem . Decl traverseModuleItemM (MIAttr attr item) = diff --git a/src/Language/SystemVerilog/AST/ModuleItem.hs b/src/Language/SystemVerilog/AST/ModuleItem.hs index fc19c47..7527cc8 100644 --- a/src/Language/SystemVerilog/AST/ModuleItem.hs +++ b/src/Language/SystemVerilog/AST/ModuleItem.hs @@ -43,8 +43,8 @@ data ModuleItem | Final Stmt | ElabTask Severity [Expr] | MIPackageItem PackageItem - | NInputGate NInputGateKW Expr Identifier LHS [Expr] - | NOutputGate NOutputGateKW Expr Identifier [LHS] Expr + | NInputGate NInputGateKW Expr Identifier [Range] LHS [Expr] + | NOutputGate NOutputGateKW Expr Identifier [Range] [LHS] Expr | AssertionItem AssertionItem deriving Eq @@ -60,10 +60,10 @@ instance Show ModuleItem where show (Initial s ) = printf "initial %s" (show s) show (Final s ) = printf "final %s" (show s) show (ElabTask s a) = printf "%s%s;" (show s) (show $ Args a []) - show (NInputGate kw d x lhs exprs) = - showGate kw d x $ show lhs : map show exprs - show (NOutputGate kw d x lhss expr) = - showGate kw d x $ (map show lhss) ++ [show expr] + show (NInputGate kw d x rs lhs exprs) = + showGate kw d x rs $ show lhs : map show exprs + show (NOutputGate kw d x rs lhss expr) = + showGate kw d x rs $ (map show lhss) ++ [show expr] show (AssertionItem i) = show i show (Instance m params i rs ports) = if null params @@ -81,12 +81,13 @@ showPort (i, arg) = then show arg else printf ".%s(%s)" i (show arg) -showGate :: Show k => k -> Expr -> Identifier -> [String] -> String -showGate kw d x args = - printf "%s %s%s(%s);" (show kw) delayStr nameStr (commas args) +showGate :: Show k => k -> Expr -> Identifier -> [Range] -> [String] -> String +showGate kw d x rs args = + printf "%s %s%s%s(%s);" (show kw) delayStr nameStr rsStr (commas args) where delayStr = if d == Nil then "" else showPad $ Delay d nameStr = showPad $ Ident x + rsStr = if null rs then "" else tail $ showRanges rs showModportDecl :: ModportDecl -> String showModportDecl (dir, ident, e) = diff --git a/src/Language/SystemVerilog/Parser/Parse.y b/src/Language/SystemVerilog/Parser/Parse.y index 93f7fec..965c940 100644 --- a/src/Language/SystemVerilog/Parser/Parse.y +++ b/src/Language/SystemVerilog/Parser/Parse.y @@ -719,8 +719,8 @@ NonGenerateModuleItem :: { [ModuleItem] } | "modport" ModportItems ";" { map (uncurry Modport) $2 } | NonDeclPackageItem { map MIPackageItem $1 } | TaskOrFunction { [MIPackageItem $1] } - | NInputGateKW NInputGates ";" { map (\(a, b, c, d) -> NInputGate $1 a b c d) $2 } - | NOutputGateKW NOutputGates ";" { map (\(a, b, c, d) -> NOutputGate $1 a b c d) $2 } + | NInputGateKW NInputGates ";" { map (\(a, b, c, d, e) -> NInputGate $1 a b c d e) $2 } + | NOutputGateKW NOutputGates ";" { map (\(a, b, c, d, e) -> NOutputGate $1 a b c d e) $2 } | AttributeInstance ModuleItem { map (addMIAttr $1) $2 } | AssertionItem { [AssertionItem $1] } @@ -852,23 +852,23 @@ AttrSpecs :: { [AttrSpec] } AttrSpec :: { AttrSpec } : Identifier OptAsgn { ($1, $2) } -NInputGates :: { [(Expr, Identifier, LHS, [Expr])] } +NInputGates :: { [(Expr, Identifier, [Range], LHS, [Expr])] } : NInputGate { [$1] } | NInputGates "," NInputGate { $1 ++ [$3]} -NOutputGates :: { [(Expr, Identifier, [LHS], Expr)] } +NOutputGates :: { [(Expr, Identifier, [Range], [LHS], Expr)] } : NOutputGate { [$1] } | NOutputGates "," NOutputGate { $1 ++ [$3]} -NInputGate :: { (Expr, Identifier, LHS, [Expr]) } - : DelayControlOrNil OptIdentifier "(" LHS "," Exprs ")" { ($1, $2, $4, $6) } -NOutputGate :: { (Expr, Identifier, [LHS], Expr) } - : DelayControlOrNil OptIdentifier "(" Exprs "," Expr ")" { ($1, $2, map toLHS $4, $6) } +NInputGate :: { (Expr, Identifier, [Range], LHS, [Expr]) } + : DelayControlOrNil OptGateName "(" LHS "," Exprs ")" { ($1, fst $2, snd $2, $4, $6) } +NOutputGate :: { (Expr, Identifier, [Range], [LHS], Expr) } + : DelayControlOrNil OptGateName "(" Exprs "," Expr ")" { ($1, fst $2, snd $2, map toLHS $4, $6) } DelayControlOrNil :: { Expr } : DelayControl { $1 } | {- empty -} { Nil } -OptIdentifier :: { Identifier } - : Identifier { $1 } - | {- empty -} { "" } +OptGateName :: { (Identifier, [Range]) } + : Identifier Dimensions { ($1, $2) } + | {- empty -} { ("", []) } NInputGateKW :: { NInputGateKW } : "and" { GateAnd } diff --git a/test/core/gate_array.sv b/test/core/gate_array.sv new file mode 100644 index 0000000..6304e1a --- /dev/null +++ b/test/core/gate_array.sv @@ -0,0 +1,13 @@ +module mod( + input logic input_a, input_b, + input logic [1:0] input_c, + input logic [1:0][2:0] input_d, + output logic [1:0] output_a, output_b, + output logic [1:0][2:0] output_c, + output logic [0:1][2:0] output_d +); + and gate_a[1:0] (output_a, input_a, input_c); + and gate_b[1:0] (output_b, input_a, input_b); + and gate_c[1:0][2:0] (output_c, input_a, input_d); + and gate_d[1:0][0:2] (output_d, input_b, input_d); +endmodule diff --git a/test/core/gate_array.v b/test/core/gate_array.v new file mode 100644 index 0000000..d9624d0 --- /dev/null +++ b/test/core/gate_array.v @@ -0,0 +1,12 @@ +module mod( + input input_a, input_b, + input [1:0] input_c, + input [5:0] input_d, + output [1:0] output_a, output_b, + output [5:0] output_c, output_d +); + and gate_a[1:0] (output_a, input_a, input_c); + and gate_b[1:0] (output_b, input_a, input_b); + and gate_c[5:0] (output_c, input_a, input_d); + and gate_d[5:0] (output_d, input_b, input_d); +endmodule diff --git a/test/core/gate_array_tb.v b/test/core/gate_array_tb.v new file mode 100644 index 0000000..0874777 --- /dev/null +++ b/test/core/gate_array_tb.v @@ -0,0 +1,25 @@ +module top; + wire input_a, input_b; + wire [1:0] input_c; + wire [5:0] input_d; + wire [1:0] output_a, output_b; + wire [5:0] output_c, output_d; + mod m( + input_a, input_b, input_c, input_d, + output_a, output_b, output_c, output_d + ); + integer i; + localparam bits = $bits({input_a, input_b, input_c, input_d }); + assign {input_a, input_b, input_c, input_d} = i; + initial begin + $monitor( + "%03d (%b, %b, %b, %b) -> (%b, %b, %b, %b)", + $time, + input_a, input_b, input_c, input_d, + output_a, output_b, output_c, output_d + ); + repeat(3) + for (i = 0; i < 2 ** bits; i = i + 1) + #1; + end +endmodule