Commit 3955c47e by Zachary Snow

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
parent 10885206
...@@ -53,10 +53,12 @@ convert files = ...@@ -53,10 +53,12 @@ convert files =
Map.elems packages' Map.elems packages'
toPackageItems :: PackageItem -> [(Identifier, PackageItem)] toPackageItems :: PackageItem -> [(Identifier, PackageItem)]
toPackageItems item = map (, item) (piNames item) toPackageItems item = map (, item) (piNames item)
makeLocal :: PackageItem -> PackageItem
makeLocal (Decl (Param _ t x e)) = Decl $ Param Localparam t x e -- convert a parameter to a localparam
makeLocal (Decl (ParamType _ x t)) = Decl $ ParamType Localparam x t makeLocal :: PackageItem -> PackageItem
makeLocal other = other 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 -- utility for inserting package items into a set of module items as needed
inject :: [PackageItem] -> [ModuleItem] -> [ModuleItem] inject :: [PackageItem] -> [ModuleItem] -> [ModuleItem]
...@@ -304,9 +306,7 @@ processItems topName packageName moduleItems = do ...@@ -304,9 +306,7 @@ processItems topName packageName moduleItems = do
traverseTypeM :: Type -> Scope Type traverseTypeM :: Type -> Scope Type
traverseTypeM (CSAlias p b x rs) = do traverseTypeM (CSAlias p b x rs) = do
scopeKeys <- bindingsScopeKeys b x' <- resolveCSIdent' p b x
b' <- mapM traverseParamBindingM b
x' <- lift $ resolveCSIdent p b' scopeKeys x
return $ Alias x' rs return $ Alias x' rs
traverseTypeM (PSAlias p x rs) = do traverseTypeM (PSAlias p x rs) = do
x' <- resolvePSIdent' p x x' <- resolvePSIdent' p x
...@@ -322,9 +322,7 @@ processItems topName packageName moduleItems = do ...@@ -322,9 +322,7 @@ processItems topName packageName moduleItems = do
traverseExprM :: Expr -> Scope Expr traverseExprM :: Expr -> Scope Expr
traverseExprM (CSIdent p b x) = do traverseExprM (CSIdent p b x) = do
scopeKeys <- bindingsScopeKeys b x' <- resolveCSIdent' p b x
b' <- mapM traverseParamBindingM b
x' <- lift $ resolveCSIdent p b' scopeKeys x
return $ Ident x' return $ Ident x'
traverseExprM (PSIdent p x) = do traverseExprM (PSIdent p x) = do
x' <- resolvePSIdent' p x x' <- resolvePSIdent' p x
...@@ -369,6 +367,44 @@ processItems topName packageName moduleItems = do ...@@ -369,6 +367,44 @@ processItems topName packageName moduleItems = do
_ -> error $ "package " ++ show p ++ " references" _ -> error $ "package " ++ show p ++ " references"
++ " undeclared local \"" ++ p ++ "::" ++ x ++ "\"" ++ " 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 -- locate a package by name, processing its contents if necessary
findPackage :: Identifier -> PackagesState Package findPackage :: Identifier -> PackagesState Package
findPackage packageName = do findPackage packageName = do
......
...@@ -48,6 +48,8 @@ module Convert.Scoper ...@@ -48,6 +48,8 @@ module Convert.Scoper
, embedScopes , embedScopes
, withinProcedure , withinProcedure
, withinProcedureM , withinProcedureM
, procedureLoc
, procedureLocM
, isLoopVar , isLoopVar
, isLoopVarM , isLoopVarM
, lookupLocalIdent , lookupLocalIdent
...@@ -92,7 +94,7 @@ data Entry a = Entry ...@@ -92,7 +94,7 @@ data Entry a = Entry
data Scopes a = Scopes data Scopes a = Scopes
{ sCurrent :: [Tier] { sCurrent :: [Tier]
, sMapping :: Mapping a , sMapping :: Mapping a
, sProcedure :: Bool , sProcedureLoc :: [Access]
, sInjectedItems :: [ModuleItem] , sInjectedItems :: [ModuleItem]
, sInjectedDecls :: [Decl] , sInjectedDecls :: [Decl]
} deriving Show } deriving Show
...@@ -133,10 +135,10 @@ exitScope :: Monad m => ScoperT a m () ...@@ -133,10 +135,10 @@ exitScope :: Monad m => ScoperT a m ()
exitScope = modify' $ \s -> s { sCurrent = init $ sCurrent s } exitScope = modify' $ \s -> s { sCurrent = init $ sCurrent s }
enterProcedure :: Monad m => ScoperT a m () 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 :: Monad m => ScoperT a m ()
exitProcedure = modify' $ \s -> s { sProcedure = False } exitProcedure = modify' $ \s -> s { sProcedureLoc = [] }
exprToAccesses :: [Access] -> Expr -> Maybe [Access] exprToAccesses :: [Access] -> Expr -> Maybe [Access]
exprToAccesses accesses (Ident x) = exprToAccesses accesses (Ident x) =
...@@ -302,20 +304,26 @@ lookupLocalIdent :: Scopes a -> Identifier -> LookupResult a ...@@ -302,20 +304,26 @@ lookupLocalIdent :: Scopes a -> Identifier -> LookupResult a
lookupLocalIdent scopes ident = do lookupLocalIdent scopes ident = do
(replacements, element) <- directResolve (sMapping scopes) accesses (replacements, element) <- directResolve (sMapping scopes) accesses
Just (accesses, replacements, element) Just (accesses, replacements, element)
where where accesses = map toAccess (sCurrent scopes) ++ [Access ident Nil]
accesses = map toAccess (sCurrent scopes) ++ [Access ident Nil]
toAccess :: Tier -> Access toAccess :: Tier -> Access
toAccess (Tier x "") = Access x Nil toAccess (Tier x "") = Access x Nil
toAccess (Tier x y) = Access x (Ident y) toAccess (Tier x y) = Access x (Ident y)
lookupLocalIdentM :: Monad m => Identifier -> ScoperT a m (LookupResult a) lookupLocalIdentM :: Monad m => Identifier -> ScoperT a m (LookupResult a)
lookupLocalIdentM = embedScopes lookupLocalIdent lookupLocalIdentM = embedScopes lookupLocalIdent
withinProcedureM :: Monad m => ScoperT a m Bool withinProcedureM :: Monad m => ScoperT a m Bool
withinProcedureM = gets sProcedure withinProcedureM = gets withinProcedure
withinProcedure :: Scopes a -> Bool 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 a -> Identifier -> Bool
isLoopVar scopes x = any matches $ sCurrent scopes isLoopVar scopes x = any matches $ sCurrent scopes
...@@ -379,7 +387,7 @@ runScoperT declMapper moduleItemMapper genItemMapper stmtMapper topName items = ...@@ -379,7 +387,7 @@ runScoperT declMapper moduleItemMapper genItemMapper stmtMapper topName items =
operation = do operation = do
enterScope topName "" enterScope topName ""
mapM wrappedModuleItemMapper items mapM wrappedModuleItemMapper items
initialState = Scopes [] Map.empty False [] [] initialState = Scopes [] Map.empty [] [] []
wrappedModuleItemMapper = scopeModuleItemT wrappedModuleItemMapper = scopeModuleItemT
declMapper moduleItemMapper genItemMapper stmtMapper declMapper moduleItemMapper genItemMapper stmtMapper
......
...@@ -6,7 +6,7 @@ class P #( ...@@ -6,7 +6,7 @@ class P #(
endclass endclass
`define DUMP \ `define DUMP \
initial begin \ begin \
a = '1; \ a = '1; \
b = '1; \ b = '1; \
c = '1; \ c = '1; \
...@@ -23,16 +23,45 @@ module top; ...@@ -23,16 +23,45 @@ module top;
P#(X, T)::Unit c; P#(X, T)::Unit c;
P#(.WIDTH(X))::Unit d; P#(.WIDTH(X))::Unit d;
P#(.BASE(T))::Unit e; P#(.BASE(T))::Unit e;
`DUMP initial `DUMP
// TODO: support local overrides if (1) begin : blk
// if (1) begin : blk localparam X = 3;
// localparam X = 3; localparam type T = logic [7:0];
// localparam type T = logic [7:0]; P#()::Unit a;
// P#()::Unit a; P#(X)::Unit b;
// P#(X)::Unit b; P#(X, T)::Unit c;
// P#(X, T)::Unit c; P#(.WIDTH(X))::Unit d;
// P#(.WIDTH(X))::Unit d; P#(.BASE(T))::Unit e;
// P#(.BASE(T))::Unit e; initial `DUMP
// `DUMP end
// 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 endmodule
`define DUMP \ `define DUMP \
initial begin \ begin \
a = 1'sb1; \ a = 1'sb1; \
b = 1'sb1; \ b = 1'sb1; \
c = 1'sb1; \ c = 1'sb1; \
...@@ -14,16 +14,17 @@ module top; ...@@ -14,16 +14,17 @@ module top;
reg [63:0] c; reg [63:0] c;
reg [1:0] d; reg [1:0] d;
reg [31:0] e; reg [31:0] e;
`DUMP initial `DUMP
generate generate
// TODO: support local overrides if (1) begin : blk
// if (1) begin : blk reg [0:0] a;
// reg [0:0] a; reg [2:0] b;
// reg [2:0] b; reg [23:0] c;
// reg [23:0] c; reg [2:0] d;
// reg [2:0] d; reg [7:0] e;
// reg [7:0] e; initial
// `DUMP repeat (4)
// end `DUMP
end
endgenerate endgenerate
endmodule 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