mirror of https://github.com/zachjs/sv2v.git
support parameterized class items depending on local generate scopes
- previously the overrides for parameterized data types could only reference data declarations at the module scope - their use within procedures is still allowed, but cannot currently refer to localparams declared within procedures - add procedure scope location accessors to allow scoped traversals to mark where injected items will end up in advance
This commit is contained in:
parent
108852060e
commit
3955c47e7a
|
|
@ -53,10 +53,12 @@ convert files =
|
|||
Map.elems packages'
|
||||
toPackageItems :: PackageItem -> [(Identifier, PackageItem)]
|
||||
toPackageItems item = map (, item) (piNames item)
|
||||
makeLocal :: PackageItem -> PackageItem
|
||||
makeLocal (Decl (Param _ t x e)) = Decl $ Param Localparam t x e
|
||||
makeLocal (Decl (ParamType _ x t)) = Decl $ ParamType Localparam x t
|
||||
makeLocal other = other
|
||||
|
||||
-- convert a parameter to a localparam
|
||||
makeLocal :: PackageItem -> PackageItem
|
||||
makeLocal (Decl (Param _ t x e)) = Decl $ Param Localparam t x e
|
||||
makeLocal (Decl (ParamType _ x t)) = Decl $ ParamType Localparam x t
|
||||
makeLocal other = other
|
||||
|
||||
-- utility for inserting package items into a set of module items as needed
|
||||
inject :: [PackageItem] -> [ModuleItem] -> [ModuleItem]
|
||||
|
|
@ -304,9 +306,7 @@ processItems topName packageName moduleItems = do
|
|||
|
||||
traverseTypeM :: Type -> Scope Type
|
||||
traverseTypeM (CSAlias p b x rs) = do
|
||||
scopeKeys <- bindingsScopeKeys b
|
||||
b' <- mapM traverseParamBindingM b
|
||||
x' <- lift $ resolveCSIdent p b' scopeKeys x
|
||||
x' <- resolveCSIdent' p b x
|
||||
return $ Alias x' rs
|
||||
traverseTypeM (PSAlias p x rs) = do
|
||||
x' <- resolvePSIdent' p x
|
||||
|
|
@ -322,9 +322,7 @@ processItems topName packageName moduleItems = do
|
|||
|
||||
traverseExprM :: Expr -> Scope Expr
|
||||
traverseExprM (CSIdent p b x) = do
|
||||
scopeKeys <- bindingsScopeKeys b
|
||||
b' <- mapM traverseParamBindingM b
|
||||
x' <- lift $ resolveCSIdent p b' scopeKeys x
|
||||
x' <- resolveCSIdent' p b x
|
||||
return $ Ident x'
|
||||
traverseExprM (PSIdent p x) = do
|
||||
x' <- resolvePSIdent' p x
|
||||
|
|
@ -369,6 +367,44 @@ processItems topName packageName moduleItems = do
|
|||
_ -> error $ "package " ++ show p ++ " references"
|
||||
++ " undeclared local \"" ++ p ++ "::" ++ x ++ "\""
|
||||
|
||||
-- wrapper resolving parameters and locally injecting the necessary
|
||||
-- class items into modules and interfaces
|
||||
resolveCSIdent'
|
||||
:: Identifier -> [ParamBinding] -> Identifier -> Scope Identifier
|
||||
resolveCSIdent' p b x = do
|
||||
scopeKeys <- bindingsScopeKeys b
|
||||
b' <- mapM traverseParamBindingM b
|
||||
x' <- lift $ resolveCSIdent p b' scopeKeys x
|
||||
let rootPkg = take (length x' - length x - 1) x'
|
||||
when (null packageName) (classScopeInject rootPkg x')
|
||||
return x'
|
||||
|
||||
-- inject the given class item and its dependencies into the local scope
|
||||
classScopeInject :: Identifier -> Identifier -> Scope ()
|
||||
classScopeInject rootPkg fullName = do
|
||||
(_, packages, _) <- lift get
|
||||
let (_, packageItems) = packages Map.! rootPkg
|
||||
let localPIs = Map.fromList $ concatMap toPIElem packageItems
|
||||
mapM_ injectIfMissing $
|
||||
addItems localPIs Set.empty
|
||||
[(Generate [], Set.singleton fullName)]
|
||||
where
|
||||
injectIfMissing :: ModuleItem -> Scope ()
|
||||
injectIfMissing (Generate []) = return ()
|
||||
injectIfMissing moduleItem = do
|
||||
let MIPackageItem packageItem = moduleItem
|
||||
let itemName : _ = piNames packageItem
|
||||
details <- lookupElemM itemName
|
||||
when (details == Nothing) $ do
|
||||
accesses <- procedureLocM
|
||||
let accesses' = accesses ++ [Access itemName Nil]
|
||||
if null accesses
|
||||
then insertElem itemName Declared
|
||||
else insertElem accesses' Declared
|
||||
injectItem moduleItem
|
||||
toPIElem :: PackageItem -> [(Identifier, PackageItem)]
|
||||
toPIElem item = map (, makeLocal item) (piNames item)
|
||||
|
||||
-- locate a package by name, processing its contents if necessary
|
||||
findPackage :: Identifier -> PackagesState Package
|
||||
findPackage packageName = do
|
||||
|
|
|
|||
|
|
@ -48,6 +48,8 @@ module Convert.Scoper
|
|||
, embedScopes
|
||||
, withinProcedure
|
||||
, withinProcedureM
|
||||
, procedureLoc
|
||||
, procedureLocM
|
||||
, isLoopVar
|
||||
, isLoopVarM
|
||||
, lookupLocalIdent
|
||||
|
|
@ -92,7 +94,7 @@ data Entry a = Entry
|
|||
data Scopes a = Scopes
|
||||
{ sCurrent :: [Tier]
|
||||
, sMapping :: Mapping a
|
||||
, sProcedure :: Bool
|
||||
, sProcedureLoc :: [Access]
|
||||
, sInjectedItems :: [ModuleItem]
|
||||
, sInjectedDecls :: [Decl]
|
||||
} deriving Show
|
||||
|
|
@ -133,10 +135,10 @@ exitScope :: Monad m => ScoperT a m ()
|
|||
exitScope = modify' $ \s -> s { sCurrent = init $ sCurrent s }
|
||||
|
||||
enterProcedure :: Monad m => ScoperT a m ()
|
||||
enterProcedure = modify' $ \s -> s { sProcedure = True }
|
||||
enterProcedure = modify' $ \s -> s { sProcedureLoc = map toAccess (sCurrent s) }
|
||||
|
||||
exitProcedure :: Monad m => ScoperT a m ()
|
||||
exitProcedure = modify' $ \s -> s { sProcedure = False }
|
||||
exitProcedure = modify' $ \s -> s { sProcedureLoc = [] }
|
||||
|
||||
exprToAccesses :: [Access] -> Expr -> Maybe [Access]
|
||||
exprToAccesses accesses (Ident x) =
|
||||
|
|
@ -302,20 +304,26 @@ lookupLocalIdent :: Scopes a -> Identifier -> LookupResult a
|
|||
lookupLocalIdent scopes ident = do
|
||||
(replacements, element) <- directResolve (sMapping scopes) accesses
|
||||
Just (accesses, replacements, element)
|
||||
where
|
||||
accesses = map toAccess (sCurrent scopes) ++ [Access ident Nil]
|
||||
toAccess :: Tier -> Access
|
||||
toAccess (Tier x "") = Access x Nil
|
||||
toAccess (Tier x y) = Access x (Ident y)
|
||||
where accesses = map toAccess (sCurrent scopes) ++ [Access ident Nil]
|
||||
|
||||
toAccess :: Tier -> Access
|
||||
toAccess (Tier x "") = Access x Nil
|
||||
toAccess (Tier x y) = Access x (Ident y)
|
||||
|
||||
lookupLocalIdentM :: Monad m => Identifier -> ScoperT a m (LookupResult a)
|
||||
lookupLocalIdentM = embedScopes lookupLocalIdent
|
||||
|
||||
withinProcedureM :: Monad m => ScoperT a m Bool
|
||||
withinProcedureM = gets sProcedure
|
||||
withinProcedureM = gets withinProcedure
|
||||
|
||||
withinProcedure :: Scopes a -> Bool
|
||||
withinProcedure = sProcedure
|
||||
withinProcedure = not . null . sProcedureLoc
|
||||
|
||||
procedureLocM :: Monad m => ScoperT a m [Access]
|
||||
procedureLocM = gets procedureLoc
|
||||
|
||||
procedureLoc :: Scopes a -> [Access]
|
||||
procedureLoc = sProcedureLoc
|
||||
|
||||
isLoopVar :: Scopes a -> Identifier -> Bool
|
||||
isLoopVar scopes x = any matches $ sCurrent scopes
|
||||
|
|
@ -379,7 +387,7 @@ runScoperT declMapper moduleItemMapper genItemMapper stmtMapper topName items =
|
|||
operation = do
|
||||
enterScope topName ""
|
||||
mapM wrappedModuleItemMapper items
|
||||
initialState = Scopes [] Map.empty False [] []
|
||||
initialState = Scopes [] Map.empty [] [] []
|
||||
|
||||
wrappedModuleItemMapper = scopeModuleItemT
|
||||
declMapper moduleItemMapper genItemMapper stmtMapper
|
||||
|
|
|
|||
|
|
@ -6,7 +6,7 @@ class P #(
|
|||
endclass
|
||||
|
||||
`define DUMP \
|
||||
initial begin \
|
||||
begin \
|
||||
a = '1; \
|
||||
b = '1; \
|
||||
c = '1; \
|
||||
|
|
@ -23,16 +23,45 @@ module top;
|
|||
P#(X, T)::Unit c;
|
||||
P#(.WIDTH(X))::Unit d;
|
||||
P#(.BASE(T))::Unit e;
|
||||
`DUMP
|
||||
// TODO: support local overrides
|
||||
// if (1) begin : blk
|
||||
// localparam X = 3;
|
||||
// localparam type T = logic [7:0];
|
||||
// P#()::Unit a;
|
||||
// P#(X)::Unit b;
|
||||
// P#(X, T)::Unit c;
|
||||
// P#(.WIDTH(X))::Unit d;
|
||||
// P#(.BASE(T))::Unit e;
|
||||
// `DUMP
|
||||
// end
|
||||
initial `DUMP
|
||||
if (1) begin : blk
|
||||
localparam X = 3;
|
||||
localparam type T = logic [7:0];
|
||||
P#()::Unit a;
|
||||
P#(X)::Unit b;
|
||||
P#(X, T)::Unit c;
|
||||
P#(.WIDTH(X))::Unit d;
|
||||
P#(.BASE(T))::Unit e;
|
||||
initial `DUMP
|
||||
end
|
||||
if (1) begin : route
|
||||
localparam X = 3;
|
||||
localparam type T = logic [7:0];
|
||||
initial begin
|
||||
begin
|
||||
P#()::Unit a;
|
||||
P#(X)::Unit b;
|
||||
P#(X, T)::Unit c;
|
||||
P#(.WIDTH(X))::Unit d;
|
||||
P#(.BASE(T))::Unit e;
|
||||
`DUMP
|
||||
end
|
||||
begin
|
||||
P#()::Unit a;
|
||||
P#(X)::Unit b;
|
||||
P#(X, T)::Unit c;
|
||||
P#(.WIDTH(X))::Unit d;
|
||||
P#(.BASE(T))::Unit e;
|
||||
`DUMP
|
||||
end
|
||||
begin
|
||||
P#()::Unit a;
|
||||
P#(X)::Unit b;
|
||||
P#(X, T)::Unit c;
|
||||
P#(.WIDTH(X))::Unit d;
|
||||
P#(.BASE(T))::Unit e;
|
||||
`DUMP
|
||||
end
|
||||
end
|
||||
end
|
||||
endmodule
|
||||
|
|
|
|||
|
|
@ -1,5 +1,5 @@
|
|||
`define DUMP \
|
||||
initial begin \
|
||||
begin \
|
||||
a = 1'sb1; \
|
||||
b = 1'sb1; \
|
||||
c = 1'sb1; \
|
||||
|
|
@ -14,16 +14,17 @@ module top;
|
|||
reg [63:0] c;
|
||||
reg [1:0] d;
|
||||
reg [31:0] e;
|
||||
`DUMP
|
||||
initial `DUMP
|
||||
generate
|
||||
// TODO: support local overrides
|
||||
// if (1) begin : blk
|
||||
// reg [0:0] a;
|
||||
// reg [2:0] b;
|
||||
// reg [23:0] c;
|
||||
// reg [2:0] d;
|
||||
// reg [7:0] e;
|
||||
// `DUMP
|
||||
// end
|
||||
if (1) begin : blk
|
||||
reg [0:0] a;
|
||||
reg [2:0] b;
|
||||
reg [23:0] c;
|
||||
reg [2:0] d;
|
||||
reg [7:0] e;
|
||||
initial
|
||||
repeat (4)
|
||||
`DUMP
|
||||
end
|
||||
endgenerate
|
||||
endmodule
|
||||
|
|
|
|||
Loading…
Reference in New Issue