Commit 6e8659a5 by Zachary Snow

support hierarchical calls to functions with no inputs

parent 5dcbce5f
......@@ -16,6 +16,7 @@
* Added support for procedural continuous assignments (`assign`/`deassign` and
`force`/`release`)
* Added conversion for `do` `while` loops
* Added support for hierarchical calls to functions with no inputs
* Added support for passing through DPI imports and exports
* Added support for passing through functions with output ports
* Extended applicability of simplified Yosys-compatible `for` loop elaboration
......
......@@ -67,6 +67,7 @@ finalPhases _ =
[ Convert.NamedBlock.convert
, Convert.DuplicateGenvar.convert
, Convert.AsgnOp.convert
, Convert.EmptyArgs.convert
, Convert.FuncRet.convert
, Convert.TFBlock.convert
]
......@@ -107,7 +108,6 @@ initialPhases selectExclude =
, Convert.Unique.convert
, Convert.EventEdge.convert
, Convert.LogOp.convert
, Convert.EmptyArgs.convert
, Convert.DoWhile.convert
, Convert.Foreach.convert
, Convert.FuncRoutine.convert
......
......@@ -8,50 +8,77 @@
module Convert.EmptyArgs (convert) where
import Control.Monad.Writer.Strict
import qualified Data.Set as Set
import Convert.Scoper
import Convert.Traverse
import Language.SystemVerilog.AST
type Idents = Set.Set Identifier
type SC = Scoper ()
convert :: [AST] -> [AST]
convert = map $ traverseDescriptions convertDescription
convertDescription :: Description -> Description
convertDescription description@Part{} =
traverseModuleItems
(traverseExprs $ traverseNestedExprs $ convertExpr functions)
description'
where
(description', functions) =
runWriter $ traverseModuleItemsM traverseFunctionsM description
convertDescription other = other
traverseFunctionsM :: ModuleItem -> Writer Idents ModuleItem
traverseFunctionsM item@(MIPackageItem (Function _ Void _ _ _)) =
return item
traverseFunctionsM (MIPackageItem (Function l t f decls stmts)) = do
decls' <-
if any isInput decls
then return decls
else do
tell $ Set.singleton f
return $ dummyDecl : decls
return $ MIPackageItem $ Function l t f decls' stmts
where
dummyType = IntegerVector TReg Unspecified []
dummyDecl = Variable Input dummyType "_sv2v_unused" [] Nil
isInput :: Decl -> Bool
isInput (Variable Input _ _ _ _) = True
isInput _ = False
traverseFunctionsM other = return other
convertExpr :: Idents -> Expr -> Expr
convertExpr functions (Call (Ident func) (Args [] [])) =
Call (Ident func) (Args args [])
where args = if Set.member func functions
then [RawNum 0]
else []
convertExpr _ other = other
convert = map $ traverseDescriptions traverseDescription
traverseDescription :: Description -> Description
traverseDescription =
evalScoper . scopePart scoper .
traverseModuleItems addDummyArg
where scoper = scopeModuleItem
traverseDecl traverseModuleItem traverseGenItem traverseStmt
-- add a dummy argument to functions with no input ports
addDummyArg :: ModuleItem -> ModuleItem
addDummyArg (MIPackageItem (Function l t f decls stmts))
| all (not . isInput) decls =
MIPackageItem $ Function l t f (dummyDecl : decls) stmts
addDummyArg other = other
isInput :: Decl -> Bool
isInput (Variable Input _ _ _ _) = True
isInput _ = False
-- write down all declarations so we can look up the dummy arg
traverseDecl :: Decl -> SC Decl
traverseDecl decl = do
decl' <- case decl of
Param _ _ x _ -> insertElem x () >> return decl
ParamType _ x _ -> insertElem x () >> return decl
Variable d t x a e -> do
insertElem x ()
-- new dummy args have a special name for idempotence
return $ if x == dummyIdent
then Variable d t dummyIdentFinal a e
else decl
Net _ _ _ _ x _ _ -> insertElem x () >> return decl
CommentDecl{} -> return decl
traverseDeclExprsM traverseExpr decl'
traverseModuleItem :: ModuleItem -> SC ModuleItem
traverseModuleItem = traverseExprsM traverseExpr
traverseGenItem :: GenItem -> SC GenItem
traverseGenItem = traverseGenItemExprsM traverseExpr
traverseStmt :: Stmt -> SC Stmt
traverseStmt = traverseStmtExprsM traverseExpr
-- pass a dummy value to functions which had no inputs
traverseExpr :: Expr -> SC Expr
traverseExpr (Call func (Args args [])) = do
details <- lookupElemM $ Dot func dummyIdent
let args' = if details /= Nothing
then RawNum 0 : args
else args
return $ Call func (Args args' [])
traverseExpr expr =
traverseSinglyNestedExprsM traverseExpr expr
dummyIdent :: Identifier
dummyIdent = '?' : dummyIdentFinal
dummyIdentFinal :: Identifier
dummyIdentFinal = "_sv2v_unused"
dummyType :: Type
dummyType = IntegerVector TReg Unspecified []
dummyDecl :: Decl
dummyDecl = Variable Input dummyType dummyIdent [] Nil
interface intf;
function automatic integer f;
return 1;
endfunction
if (1) begin : blk
function automatic integer f;
return 2;
endfunction
end
endinterface
module top;
intf i();
function automatic integer f;
return 3;
endfunction
if (1) begin : blk
function automatic integer f;
return 4;
endfunction
end
initial begin
$display(f());
$display(blk.f());
$display(i.f());
$display(i.blk.f());
$display(top.f());
$display(top.blk.f());
$display(top.i.f());
$display(top.i.blk.f());
end
endmodule
module top;
generate
if (1) begin : i
function automatic integer f;
input unused;
f = 1;
endfunction
if (1) begin : blk
function automatic integer f;
input unused;
f = 2;
endfunction
end
end
function automatic integer f;
input unused;
f = 3;
endfunction
if (1) begin : blk
function automatic integer f;
input unused;
f = 4;
endfunction
end
endgenerate
initial begin
$display(f(0));
$display(blk.f(0));
$display(i.f(0));
$display(i.blk.f(0));
$display(top.f(0));
$display(top.blk.f(0));
$display(top.i.f(0));
$display(top.i.blk.f(0));
end
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