Commit 99428b2f by Zachary Snow

expanded support for interfaces with parameters

parent 8cfd05de
...@@ -17,8 +17,8 @@ import Language.SystemVerilog.AST ...@@ -17,8 +17,8 @@ import Language.SystemVerilog.AST
type Instances = Map.Map Identifier Identifier type Instances = Map.Map Identifier Identifier
type Interface = ([Identifier], [ModuleItem]) type Interface = ([Identifier], [ModuleItem])
type Interfaces = Map.Map Identifier Interface type Interfaces = Map.Map Identifier Interface
type Modports = Map.Map Identifier [ModportDecl] type Modports = Map.Map Identifier (Identifier, [ModportDecl])
type Modules = Map.Map Identifier [(Identifier, Type)] type Modules = Map.Map Identifier ([Identifier], [(Identifier, Type)])
convert :: [AST] -> [AST] convert :: [AST] -> [AST]
convert = convert =
...@@ -40,8 +40,9 @@ convert = ...@@ -40,8 +40,9 @@ convert =
collectDesc (orig @ (Part _ False kw _ name ports items)) = do collectDesc (orig @ (Part _ False kw _ name ports items)) = do
if kw == Interface if kw == Interface
then tell (Map.singleton name (ports, items), Map.empty) then tell (Map.singleton name (ports, items), Map.empty)
else tell (Map.empty, Map.singleton name decls) else tell (Map.empty, Map.singleton name (params, decls))
where where
params = map fst $ parameters items
decls = execWriter $ decls = execWriter $
collectModuleItemsM (collectDeclsM collectDecl) orig collectModuleItemsM (collectDeclsM collectDecl) orig
collectDecl :: Decl -> Writer [(Identifier, Type)] () collectDecl :: Decl -> Writer [(Identifier, Type)] ()
...@@ -71,12 +72,13 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po ...@@ -71,12 +72,13 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po
collectInterface (MIPackageItem (Decl (Variable _ t ident _ _))) = collectInterface (MIPackageItem (Decl (Variable _ t ident _ _))) =
case t of case t of
InterfaceT interfaceName (Just modportName) [] -> InterfaceT interfaceName (Just modportName) [] ->
tell (Map.empty, Map.singleton ident modportDecls) tell (Map.empty, Map.singleton ident (interfaceName, modportDecls))
where Just modportDecls = lookupModport interfaceName modportName where Just modportDecls = lookupModport interfaceName modportName
Alias Nothing interfaceName [] -> Alias Nothing interfaceName [] ->
case impliedModport interfaceName of case impliedModport interfaceName of
Just modportDecls -> Just modportDecls ->
tell (Map.empty, Map.singleton ident modportDecls) tell (Map.empty, Map.singleton ident modport)
where modport = (interfaceName, modportDecls)
Nothing -> return () Nothing -> return ()
_ -> return () _ -> return ()
collectInterface (Instance part _ ident Nothing _) = collectInterface (Instance part _ ident Nothing _) =
...@@ -89,9 +91,9 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po ...@@ -89,9 +91,9 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po
mapInterface (orig @ (MIPackageItem (Decl (Variable _ t ident _ _)))) = mapInterface (orig @ (MIPackageItem (Decl (Variable _ t ident _ _)))) =
-- expand instantiation of a modport -- expand instantiation of a modport
case Map.lookup ident modports of case Map.lookup ident modports of
Just modportDecls -> Generate $ Just (_, modportDecls) -> Generate $
map (GenModuleItem . MIPackageItem . Decl . mapper) map (GenModuleItem . MIPackageItem . Decl)
modportDecls (parameterDecls ++ map mapper modportDecls)
Nothing -> orig Nothing -> orig
where where
interfaceName = case t of interfaceName = case t of
...@@ -102,6 +104,8 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po ...@@ -102,6 +104,8 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po
case Map.lookup interfaceName interfaces of case Map.lookup interfaceName interfaces of
Just res -> snd res Just res -> snd res
Nothing -> error $ "could not find interface " ++ show interfaceName Nothing -> error $ "could not find interface " ++ show interfaceName
parameterDecls = map snd $ parameters interfaceItems
mapper :: ModportDecl -> Decl
mapper (dir, port, expr) = mapper (dir, port, expr) =
Variable dir mpt (ident ++ "_" ++ port) mprs Nil Variable dir mpt (ident ++ "_" ++ port) mprs Nil
where (mpt, mprs) = lookupType interfaceItems expr where (mpt, mprs) = lookupType interfaceItems expr
...@@ -111,9 +115,21 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po ...@@ -111,9 +115,21 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po
Just interface -> Just interface ->
-- inline instantiation of an interface -- inline instantiation of an interface
Generate $ map GenModuleItem $ Generate $ map GenModuleItem $
inlineInterface interface (ident, params, expandedPorts) inlineInterface interface (ident, params, instancePorts)
Nothing -> Instance part params ident Nothing expandedPorts Nothing ->
where expandedPorts = concatMap (uncurry $ expandPortBinding part) (zip instancePorts [0..]) if Map.member part modules
then Instance part params' ident Nothing expandedPorts
else Instance part params ident Nothing instancePorts
where
expandedBindings = map (uncurry $ expandPortBinding part) (zip instancePorts [0..])
expandedPorts = concatMap snd expandedBindings
Just (moduleParamNames, _) = Map.lookup part modules
addedParams = concatMap fst expandedBindings
paramsNamed = resolveParams moduleParamNames params
params' =
if null addedParams
then params
else paramsNamed ++ addedParams
mapInterface (orig @ (MIPackageItem (Function _ _ _ decls _))) = mapInterface (orig @ (MIPackageItem (Function _ _ _ decls _))) =
convertTF decls orig convertTF decls orig
mapInterface (orig @ (MIPackageItem (Task _ _ decls _))) = mapInterface (orig @ (MIPackageItem (Task _ _ decls _))) =
...@@ -132,28 +148,30 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po ...@@ -132,28 +148,30 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po
declVarIdent (Variable _ _ x _ _) = x declVarIdent (Variable _ _ x _ _) = x
declVarIdent _ = "" declVarIdent _ = ""
expandPortBinding :: Identifier -> PortBinding -> Int -> [PortBinding] expandPortBinding :: Identifier -> PortBinding -> Int -> ([ParamBinding], [PortBinding])
expandPortBinding _ (origBinding @ (portName, Dot (Ident instanceName) modportName)) _ = expandPortBinding _ (origBinding @ (portName, Dot (Ident instanceName) modportName)) _ =
-- expand instance modport bound to a modport -- expand instance modport bound to a modport
if Map.member instanceName instances && modportDecls /= Nothing if Map.member instanceName instances && modportDecls /= Nothing
then expandPortBinding' portName instanceName $ fromJust modportDecls then expandPortBinding' interfaceName portName instanceName
else [origBinding] (fromJust modportDecls)
else ([], [origBinding])
where where
interfaceName = instances Map.! instanceName interfaceName = instances Map.! instanceName
modportDecls = lookupModport interfaceName modportName modportDecls = lookupModport interfaceName modportName
expandPortBinding moduleName (origBinding @ (portName, Ident ident)) idx = expandPortBinding moduleName (origBinding @ (portName, Ident ident)) idx =
case (instances Map.!? ident, modports Map.!? ident) of case (instances Map.!? ident, modports Map.!? ident) of
(Nothing, Nothing) -> [origBinding] (Nothing, Nothing) -> ([], [origBinding])
(Just interfaceName, _) -> (Just interfaceName, _) ->
-- given entire interface, but just bound to a modport -- given entire interface, but just bound to a modport
if Map.notMember moduleName modules then if Map.notMember moduleName modules then
error $ "could not find module " ++ show moduleName error $ "could not find module " ++ show moduleName
else if modportDecls == Nothing then else if modportDecls == Nothing then
[origBinding] ([], [origBinding])
else else
expandPortBinding' portName ident $ fromJust modportDecls expandPortBinding' interfaceName portName ident
(fromJust modportDecls)
where where
Just decls = Map.lookup moduleName modules Just (_, decls) = Map.lookup moduleName modules
portType = portType =
if null portName if null portName
then if idx < length decls then if idx < length decls
...@@ -173,17 +191,24 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po ...@@ -173,17 +191,24 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po
Alias Nothing _ [] -> Alias Nothing _ [] ->
impliedModport interfaceName impliedModport interfaceName
_ -> Nothing _ -> Nothing
(_, Just modportDecls) -> (_, Just (interfaceName, modportDecls)) ->
-- modport directly bound to a modport -- modport directly bound to a modport
expandPortBinding' portName ident $ map redirect modportDecls expandPortBinding' interfaceName portName ident
(map redirect modportDecls)
where redirect (d, x, _) = (d, x, Ident x) where redirect (d, x, _) = (d, x, Ident x)
expandPortBinding _ other _ = [other] expandPortBinding _ other _ = ([], [other])
expandPortBinding' :: Identifier -> Identifier -> [ModportDecl] -> [PortBinding] expandPortBinding' :: Identifier -> Identifier -> Identifier ->
expandPortBinding' portName instanceName modportDecls = [ModportDecl] -> ([ParamBinding], [PortBinding])
map mapper modportDecls expandPortBinding' interfaceName portName instanceName modportDecls =
(paramBindings, portBindings)
where where
mapper (_, x, e) = (x', e') paramBindings = map toParamBinding interfaceParamNames
interfaceItems = snd $ interfaces Map.! interfaceName
interfaceParamNames = map fst $ parameters interfaceItems
toParamBinding x = (x, Right $ Ident $ instanceName ++ '_' : x)
portBindings = map toPortBinding modportDecls
toPortBinding (_, x, e) = (x', e')
where where
x' = if null portName then "" else portName ++ '_' : x x' = if null portName then "" else portName ++ '_' : x
e' = traverseNestedExprs prefixExpr e e' = traverseNestedExprs prefixExpr e
...@@ -201,7 +226,7 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po ...@@ -201,7 +226,7 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po
modportMap = execWriter $ modportMap = execWriter $
mapM (collectNestedModuleItemsM collectModport) $ mapM (collectNestedModuleItemsM collectModport) $
interfaceItems interfaceItems
collectModport :: ModuleItem -> Writer Modports () collectModport :: ModuleItem -> Writer (Map.Map Identifier [ModportDecl]) ()
collectModport (Modport ident l) = tell $ Map.singleton ident l collectModport (Modport ident l) = tell $ Map.singleton ident l
collectModport _ = return () collectModport _ = return ()
...@@ -237,7 +262,7 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po ...@@ -237,7 +262,7 @@ convertDescription interfaces modules (Part attrs extern Module lifetime name po
convertPort ident = convertPort ident =
case Map.lookup ident modports of case Map.lookup ident modports of
Nothing -> [ident] Nothing -> [ident]
Just decls -> map (\(_, x, _) -> ident ++ "_" ++ x) decls Just (_, decls) -> map (\(_, x, _) -> ident ++ "_" ++ x) decls
convertDescription _ _ other = other convertDescription _ _ other = other
...@@ -351,7 +376,9 @@ inlineInterface (ports, items) (instanceName, instanceParams, instancePorts) = ...@@ -351,7 +376,9 @@ inlineInterface (ports, items) (instanceName, instanceParams, instancePorts) =
MIPackageItem $ Decl $ CommentDecl $ "removed modport " ++ x MIPackageItem $ Decl $ CommentDecl $ "removed modport " ++ x
removeModport other = other removeModport other = other
instanceParamMap = Map.fromList instanceParams interfaceParamNames = map fst $ parameters items
instanceParamMap =
Map.fromList $ resolveParams interfaceParamNames instanceParams
overrideParam :: Decl -> Decl overrideParam :: Decl -> Decl
overrideParam (Param Parameter t x e) = overrideParam (Param Parameter t x e) =
case Map.lookup x instanceParamMap of case Map.lookup x instanceParamMap of
...@@ -391,3 +418,26 @@ inlineInterface (ports, items) (instanceName, instanceParams, instancePorts) = ...@@ -391,3 +418,26 @@ inlineInterface (ports, items) (instanceName, instanceParams, instancePorts) =
Just lhs -> lhs Just lhs -> lhs
Nothing -> error $ "trying to bind an interface output to " ++ Nothing -> error $ "trying to bind an interface output to " ++
show expr ++ " but that can't be an LHS" show expr ++ " but that can't be an LHS"
-- give a set of param bindings explicit names
resolveParams :: [Identifier] -> [ParamBinding] -> [ParamBinding]
resolveParams available bindings =
map (uncurry resolveParam) $ zip bindings [0..]
where
resolveParam :: ParamBinding -> Int -> ParamBinding
resolveParam ("", e) idx =
if idx < length available
then (available !! idx, e)
else error $ "interface param binding " ++ (show e)
++ " is out of range"
resolveParam other _ = other
-- given a list of module items, produces the parameters in order
parameters :: [ModuleItem] -> [(Identifier, Decl)]
parameters =
execWriter . mapM (collectNestedModuleItemsM $ collectDeclsM collectDeclM)
where
collectDeclM :: Decl -> Writer [(Identifier, Decl)] ()
collectDeclM (decl @ (Param Parameter _ x _)) = tell [(x, decl)]
collectDeclM (decl @ (ParamType Parameter x _)) = tell [(x, decl)]
collectDeclM _ = return ()
interface I;
parameter WIDTH = 32;
logic [WIDTH-1:0] data = 0;
modport P(input data);
endinterface
module M(i);
parameter A = 1;
I.P i;
parameter B = 2;
initial begin
$display("A %b", A);
$display("I.P %b", i.data);
$display("B %b", B);
end
endmodule
module top;
I x();
I #(10) y();
M a(x);
M b(y);
M #(3, 4) c(x);
M #(5, 6) d(y);
endmodule
module M(data);
parameter A = 1;
parameter WIDTH = 32;
parameter B = 2;
input wire [WIDTH-1:0] data;
initial begin
$display("A %b", A);
$display("I.P %b", data);
$display("B %b", B);
end
endmodule
module top;
wire [31:0] x_data = 0;
wire [9:0] y_data = 0;
M #(.WIDTH(32)) a(x_data);
M #(.WIDTH(10)) b(y_data);
M #(3, 32, 4) c(x_data);
M #(5, 10, 6) d(y_data);
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