Commit 5dcbce5f by Zachary Snow

fix conversion of casts to structs containing multidimensional fields

parent e7fc1e61
...@@ -35,6 +35,7 @@ ...@@ -35,6 +35,7 @@
necessary because of calls to functions which reference non-local data necessary because of calls to functions which reference non-local data
* Fixed signed `struct` fields being converted to unsigned expressions when * Fixed signed `struct` fields being converted to unsigned expressions when
accessed directly accessed directly
* Fixed conversion of casts using structs containing multi-dimensional fields
## v0.0.9 ## v0.0.9
......
...@@ -5,7 +5,7 @@ ...@@ -5,7 +5,7 @@
- Conversion for flattening variables with multiple packed dimensions - Conversion for flattening variables with multiple packed dimensions
- -
- This removes one packed dimension per identifier per pass. This works fine - This removes one packed dimension per identifier per pass. This works fine
- because all conversions are repeatedly applied. - because this conversion is repeatedly applied.
- -
- We previously had a very complex conversion which used `generate` to make - We previously had a very complex conversion which used `generate` to make
- flattened and unflattened versions of the array as necessary. This has now - flattened and unflattened versions of the array as necessary. This has now
...@@ -28,6 +28,7 @@ module Convert.MultiplePacked (convert) where ...@@ -28,6 +28,7 @@ module Convert.MultiplePacked (convert) where
import Convert.ExprUtils import Convert.ExprUtils
import Control.Monad ((>=>)) import Control.Monad ((>=>))
import Data.Bifunctor (first)
import Data.Tuple (swap) import Data.Tuple (swap)
import Data.Maybe (isJust) import Data.Maybe (isJust)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
...@@ -59,30 +60,34 @@ traverseDeclM (Param s t ident e) = do ...@@ -59,30 +60,34 @@ traverseDeclM (Param s t ident e) = do
traverseDeclExprsM traverseExprM $ Param s t' ident e traverseDeclExprsM traverseExprM $ Param s t' ident e
traverseDeclM other = traverseDeclExprsM traverseExprM other traverseDeclM other = traverseDeclExprsM traverseExprM other
-- write down the given declaration and then flatten it
traverseTypeM :: Type -> [Range] -> Identifier -> Scoper TypeInfo Type traverseTypeM :: Type -> [Range] -> Identifier -> Scoper TypeInfo Type
traverseTypeM t a ident = do traverseTypeM t a ident = do
tScoped <- scopeType t tScoped <- scopeType t
insertElem ident (tScoped, a) insertElem ident (tScoped, a)
t' <- case t of return $ flattenType t
Struct pk fields rs -> do
fields' <- flattenFields fields -- flatten the innermost dimension of the given type, and any types it contains
return $ Struct pk fields' rs flattenType :: Type -> Type
Union pk fields rs -> do flattenType t =
fields' <- flattenFields fields tf $ if length ranges <= 1
return $ Union pk fields' rs then ranges
_ -> return t else rangesFlat
let (tf, rs) = typeRanges t'
if length rs <= 1
then return t'
else do
let r1 : r2 : rest = rs
let rs' = (combineRanges r1 r2) : rest
return $ tf rs'
where where
flattenFields fields = do (tf, ranges) = case t of
let (fieldTypes, fieldNames) = unzip fields Struct pk fields rs ->
fieldTypes' <- mapM (\x -> traverseTypeM x [] "") fieldTypes (Struct pk fields', rs)
return $ zip fieldTypes' fieldNames where fields' = flattenFields fields
Union pk fields rs ->
(Union pk fields', rs)
where fields' = flattenFields fields
_ -> typeRanges t
r1 : r2 : rest = ranges
rangesFlat = combineRanges r1 r2 : rest
-- flatten the types in a given list of struct/union fields
flattenFields :: [Field] -> [Field]
flattenFields = map $ first flattenType
traverseModuleItemM :: ModuleItem -> Scoper TypeInfo ModuleItem traverseModuleItemM :: ModuleItem -> Scoper TypeInfo ModuleItem
traverseModuleItemM (Instance m p x rs l) = do traverseModuleItemM (Instance m p x rs l) = do
...@@ -266,6 +271,8 @@ convertExpr scopes = ...@@ -266,6 +271,8 @@ convertExpr scopes =
len = lenOuter len = lenOuter
range' = (base, len) range' = (base, len)
one = RawNum 1 one = RawNum 1
rewriteExpr (Cast (Left t) expr) =
Cast (Left $ flattenType t) expr
rewriteExpr other = rewriteExpr other =
rewriteExprLowPrec other rewriteExprLowPrec other
......
module top;
typedef struct packed {
logic [2][3] x;
} S;
S s;
initial s = S'('1);
endmodule
module top;
reg [5:0] s;
initial s = 1'sb1;
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