Commit 454afa97 by Zachary Snow

major array pack and flatten update (closes #48)

- dimensions flattening conversion only flattens packed dimensions
- conversion for packing arrays when necessary (preserves memories)
- added coverage for array with multiple packed dimensions
- test runner no longer forbids multi-dim accesses after conversion
- Decl and subordinate types derive Ord
parent 087841a2
...@@ -24,10 +24,10 @@ import qualified Convert.IntTypes ...@@ -24,10 +24,10 @@ import qualified Convert.IntTypes
import qualified Convert.KWArgs import qualified Convert.KWArgs
import qualified Convert.Logic import qualified Convert.Logic
import qualified Convert.LogOp import qualified Convert.LogOp
import qualified Convert.MultiplePacked
import qualified Convert.NamedBlock import qualified Convert.NamedBlock
import qualified Convert.NestPI import qualified Convert.NestPI
import qualified Convert.Package import qualified Convert.Package
import qualified Convert.PackedArray
import qualified Convert.ParamType import qualified Convert.ParamType
import qualified Convert.RemoveComments import qualified Convert.RemoveComments
import qualified Convert.Return import qualified Convert.Return
...@@ -40,6 +40,7 @@ import qualified Convert.Struct ...@@ -40,6 +40,7 @@ import qualified Convert.Struct
import qualified Convert.Typedef import qualified Convert.Typedef
import qualified Convert.UnbasedUnsized import qualified Convert.UnbasedUnsized
import qualified Convert.Unique import qualified Convert.Unique
import qualified Convert.UnpackedArray
import qualified Convert.Unsigned import qualified Convert.Unsigned
type Phase = [AST] -> [AST] type Phase = [AST] -> [AST]
...@@ -57,7 +58,7 @@ phases excludes = ...@@ -57,7 +58,7 @@ phases excludes =
, Convert.IntTypes.convert , Convert.IntTypes.convert
, Convert.KWArgs.convert , Convert.KWArgs.convert
, Convert.LogOp.convert , Convert.LogOp.convert
, Convert.PackedArray.convert , Convert.MultiplePacked.convert
, Convert.DimensionQuery.convert , Convert.DimensionQuery.convert
, Convert.ParamType.convert , Convert.ParamType.convert
, Convert.SizeCast.convert , Convert.SizeCast.convert
...@@ -69,6 +70,7 @@ phases excludes = ...@@ -69,6 +70,7 @@ phases excludes =
, Convert.Typedef.convert , Convert.Typedef.convert
, Convert.UnbasedUnsized.convert , Convert.UnbasedUnsized.convert
, Convert.Unique.convert , Convert.Unique.convert
, Convert.UnpackedArray.convert
, Convert.Unsigned.convert , Convert.Unsigned.convert
, Convert.Package.convert , Convert.Package.convert
, Convert.Enum.convert , Convert.Enum.convert
......
...@@ -15,7 +15,7 @@ import Convert.Traverse ...@@ -15,7 +15,7 @@ import Convert.Traverse
import Language.SystemVerilog.AST import Language.SystemVerilog.AST
type TypeMap = Map.Map Identifier Type type TypeMap = Map.Map Identifier Type
type CastSet = Set.Set (Expr, Signing) type CastSet = Set.Set (Expr, Signing)
type ST = StateT TypeMap (Writer CastSet) type ST = StateT TypeMap (Writer CastSet)
......
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
- Conversion for any unpacked array which must be packed because it is: A) a
- port; B) is bound to a port; or C) is assigned a value in a single
- assignment.
-
- The scoped nature of declarations makes this challenging. While scoping is
- obeyed in general, any of a set of *equivalent* declarations within a module
- is packed, all of the declarations are packed. This is because we only record
- the declaration that needs to be packed when a relevant usage is encountered.
-}
module Convert.UnpackedArray (convert) where
import Control.Monad.State
import Control.Monad.Writer
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Convert.Traverse
import Language.SystemVerilog.AST
type DeclMap = Map.Map Identifier Decl
type DeclSet = Set.Set Decl
type ST = StateT DeclMap (Writer DeclSet)
convert :: [AST] -> [AST]
convert = map $ traverseDescriptions convertDescription
convertDescription :: Description -> Description
convertDescription description =
traverseModuleItems (traverseDecls $ packDecl declsToPack) description'
where
(description', declsToPack) = runWriter $
scopedConversionM traverseDeclM traverseModuleItemM traverseStmtM
Map.empty description
-- collects and converts multi-dimensional packed-array declarations
traverseDeclM :: Decl -> ST Decl
traverseDeclM (orig @ (Variable dir _ x _ me)) = do
modify $ Map.insert x orig
() <- if dir /= Local || me /= Nothing
then lift $ tell $ Set.singleton orig
else return ()
return orig
traverseDeclM (orig @ (Param _ _ _ _)) =
return orig
traverseDeclM (orig @ (ParamType _ _ _)) =
return orig
-- pack the given decls marked for packing
packDecl :: DeclSet -> Decl -> Decl
packDecl decls (orig @ (Variable d t x a me)) = do
if Set.member orig decls
then do
let (tf, rs) = typeRanges t
let t' = tf $ a ++ rs
Variable d t' x [] me
else orig
packDecl _ (orig @ Param{}) = orig
packDecl _ (orig @ ParamType{}) = orig
traverseModuleItemM :: ModuleItem -> ST ModuleItem
traverseModuleItemM item =
traverseModuleItemM' item
>>= traverseLHSsM traverseLHSM
>>= traverseExprsM traverseExprM
traverseModuleItemM' :: ModuleItem -> ST ModuleItem
traverseModuleItemM' (Instance a b c d bindings) = do
bindings' <- mapM collectBinding bindings
return $ Instance a b c d bindings'
where
collectBinding :: PortBinding -> ST PortBinding
collectBinding (y, Just (Ident x)) = do
flatUsageM x
return (y, Just (Ident x))
collectBinding other = return other
traverseModuleItemM' other = return other
traverseStmtM :: Stmt -> ST Stmt
traverseStmtM stmt =
traverseStmtLHSsM traverseLHSM stmt >>=
traverseStmtExprsM traverseExprM
traverseExprM :: Expr -> ST Expr
traverseExprM = return
traverseLHSM :: LHS -> ST LHS
traverseLHSM (LHSIdent x) = do
flatUsageM x
return $ LHSIdent x
traverseLHSM other = return other
flatUsageM :: Identifier -> ST ()
flatUsageM x = do
declMap <- get
case Map.lookup x declMap of
Just decl -> lift $ tell $ Set.singleton decl
Nothing -> return ()
...@@ -23,7 +23,7 @@ data Decl ...@@ -23,7 +23,7 @@ data Decl
= Param ParamScope Type Identifier Expr = Param ParamScope Type Identifier Expr
| ParamType ParamScope Identifier (Maybe Type) | ParamType ParamScope Identifier (Maybe Type)
| Variable Direction Type Identifier [Range] (Maybe Expr) | Variable Direction Type Identifier [Range] (Maybe Expr)
deriving Eq deriving (Eq, Ord)
instance Show Decl where instance Show Decl where
showList l _ = unlines' $ map show l showList l _ = unlines' $ map show l
...@@ -36,7 +36,7 @@ data Direction ...@@ -36,7 +36,7 @@ data Direction
| Output | Output
| Inout | Inout
| Local | Local
deriving Eq deriving (Eq, Ord)
instance Show Direction where instance Show Direction where
show Input = "input" show Input = "input"
...@@ -47,7 +47,7 @@ instance Show Direction where ...@@ -47,7 +47,7 @@ instance Show Direction where
data ParamScope data ParamScope
= Parameter = Parameter
| Localparam | Localparam
deriving Eq deriving (Eq, Ord)
instance Show ParamScope where instance Show ParamScope where
show Parameter = "parameter" show Parameter = "parameter"
......
...@@ -69,10 +69,10 @@ executable sv2v ...@@ -69,10 +69,10 @@ executable sv2v
Convert.KWArgs Convert.KWArgs
Convert.Logic Convert.Logic
Convert.LogOp Convert.LogOp
Convert.MultiplePacked
Convert.NamedBlock Convert.NamedBlock
Convert.NestPI Convert.NestPI
Convert.Package Convert.Package
Convert.PackedArray
Convert.ParamType Convert.ParamType
Convert.RemoveComments Convert.RemoveComments
Convert.Return Convert.Return
...@@ -82,10 +82,11 @@ executable sv2v ...@@ -82,10 +82,11 @@ executable sv2v
Convert.StmtBlock Convert.StmtBlock
Convert.Stream Convert.Stream
Convert.Struct Convert.Struct
Convert.Typedef
Convert.Traverse Convert.Traverse
Convert.Typedef
Convert.UnbasedUnsized Convert.UnbasedUnsized
Convert.Unique Convert.Unique
Convert.UnpackedArray
Convert.Unsigned Convert.Unsigned
-- sv2v CLI modules -- sv2v CLI modules
Job Job
......
module top;
logic [2:0][3:0] arr [1:0];
initial begin
for (int i = 0; i <= 1; i++) begin
for (int j = 0; j <= 2; j++) begin
for (int k = 0; k <= 3; k++) begin
$display("%b", arr[i][j][k]);
arr[i][j][k] = 1'(i+j+k);
$display("%b", arr[i][j][k]);
end
end
end
end
endmodule
module top;
reg arr [1:0][2:0][3:0];
initial begin : block_name
integer i, j, k;
for (i = 0; i <= 1; i++) begin
for (j = 0; j <= 2; j++) begin
for (k = 0; k <= 3; k++) begin
$display("%b", arr[i][j][k]);
arr[i][j][k] = i+j+k;
$display("%b", arr[i][j][k]);
end
end
end
end
endmodule
...@@ -60,8 +60,6 @@ assertConverts() { ...@@ -60,8 +60,6 @@ assertConverts() {
PATTERNS="\$bits\|\$dimensions\|\$unpacked_dimensions\|\$left\|\$right\|\$low\|\$high\|\$increment\|\$size" PATTERNS="\$bits\|\$dimensions\|\$unpacked_dimensions\|\$left\|\$right\|\$low\|\$high\|\$increment\|\$size"
echo "$filtered" | grep "$PATTERNS" > /dev/null echo "$filtered" | grep "$PATTERNS" > /dev/null
assertFalse "conversion of $ac_file still contains dimension queries" $? assertFalse "conversion of $ac_file still contains dimension queries" $?
echo "$filtered" | grep "\]\[" > /dev/null
assertFalse "conversion of $ac_file still contains multi-dim arrays" $?
echo "$filtered" | egrep "\s(int\|bit\|logic\|byte\|struct\|enum\|longint\|shortint)\s" echo "$filtered" | egrep "\s(int\|bit\|logic\|byte\|struct\|enum\|longint\|shortint)\s"
assertFalse "conversion of $ac_file still contains SV types" $? assertFalse "conversion of $ac_file still contains SV types" $?
echo "$filtered" | grep "[^$]unsigned" > /dev/null echo "$filtered" | grep "[^$]unsigned" > /dev/null
......
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