Commit 8ae89a7b by Zachary Snow

support and convert jumps: break, continue, and return

parent 08c38e61
...@@ -21,6 +21,7 @@ import qualified Convert.Foreach ...@@ -21,6 +21,7 @@ import qualified Convert.Foreach
import qualified Convert.FuncRet import qualified Convert.FuncRet
import qualified Convert.Interface import qualified Convert.Interface
import qualified Convert.IntTypes import qualified Convert.IntTypes
import qualified Convert.Jump
import qualified Convert.KWArgs import qualified Convert.KWArgs
import qualified Convert.Logic import qualified Convert.Logic
import qualified Convert.LogOp import qualified Convert.LogOp
...@@ -30,7 +31,6 @@ import qualified Convert.NestPI ...@@ -30,7 +31,6 @@ import qualified Convert.NestPI
import qualified Convert.Package import qualified Convert.Package
import qualified Convert.ParamType import qualified Convert.ParamType
import qualified Convert.RemoveComments import qualified Convert.RemoveComments
import qualified Convert.Return
import qualified Convert.Simplify import qualified Convert.Simplify
import qualified Convert.SizeCast import qualified Convert.SizeCast
import qualified Convert.StarPort import qualified Convert.StarPort
...@@ -75,7 +75,7 @@ phases excludes = ...@@ -75,7 +75,7 @@ phases excludes =
, Convert.Package.convert , Convert.Package.convert
, Convert.Enum.convert , Convert.Enum.convert
, Convert.NestPI.convert , Convert.NestPI.convert
, Convert.Return.convert , Convert.Jump.convert
, Convert.Foreach.convert , Convert.Foreach.convert
, selectExclude (Job.Interface, Convert.Interface.convert) , selectExclude (Job.Interface, Convert.Interface.convert)
, selectExclude (Job.Always , Convert.AlwaysKW.convert) , selectExclude (Job.Always , Convert.AlwaysKW.convert)
......
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
- Conversion for `return`, `break`, and `continue`
-
- Because Verilog-2005 has no jumping statements, this conversion ends up
- producing significantly more verbose code to acheive the same control flow.
-}
module Convert.Jump (convert) where
import Control.Monad.State
import Convert.Traverse
import Language.SystemVerilog.AST
data JumpType
= JTNone
| JTContinue
| JTBreak
| JTReturn
deriving (Eq, Ord, Show)
data Info = Info
{ sJumpType :: JumpType
, sLoopID :: Identifier
}
convert :: [AST] -> [AST]
convert = map $ traverseDescriptions $ traverseModuleItems convertModuleItem
convertModuleItem :: ModuleItem -> ModuleItem
convertModuleItem (MIPackageItem (Function ml t f decls stmtsOrig)) =
if sJumpType finalState == JTNone || sJumpType finalState == JTReturn
then MIPackageItem $ Function ml t f decls stmts'
else error "illegal jump statement within task"
where
stmts = map (traverseNestedStmts convertReturn) stmtsOrig
convertReturn :: Stmt -> Stmt
convertReturn (Return Nil) = Return Nil
convertReturn (Return e) =
Block Seq "" []
[ asgn f e
, Return Nil
]
convertReturn other = other
initialState = Info { sJumpType = JTNone, sLoopID = "" }
(stmts', finalState) = runState (convertStmts stmts) initialState
convertModuleItem (MIPackageItem (Task ml f decls stmts)) =
if sJumpType finalState == JTNone || sJumpType finalState == JTReturn
then MIPackageItem $ Task ml f decls $ stmts'
else error "illegal jump statement within task"
where
initialState = Info { sJumpType = JTNone, sLoopID = "" }
(stmts', finalState) = runState (convertStmts stmts) initialState
convertModuleItem (Initial stmt) =
if sJumpType finalState == JTNone
then Initial stmt'
else error "illegal jump statement within initial construct"
where
initialState = Info { sJumpType = JTNone, sLoopID = "" }
(stmt', finalState) = runState (convertStmt stmt) initialState
convertModuleItem (AlwaysC kw stmt) =
if sJumpType finalState == JTNone
then AlwaysC kw stmt'
else error "illegal jump statement within always construct"
where
initialState = Info { sJumpType = JTNone, sLoopID = "" }
(stmt', finalState) = runState (convertStmt stmt) initialState
convertModuleItem other = other
convertStmts :: [Stmt] -> State Info [Stmt]
convertStmts stmts = do
res <- convertStmt $ Block Seq "" [] stmts
let Block Seq "" [] stmts' = res
return stmts'
-- rewrites the given statement, and returns the type of any unfinished jump
convertStmt :: Stmt -> State Info Stmt
convertStmt (Block Par x decls stmts) = do
-- break, continue, and return disallowed in fork-join
modify $ \s -> s { sLoopID = "" }
loopID <- gets sLoopID
stmts' <- mapM convertStmt stmts
modify $ \s -> s { sLoopID = loopID }
return $ Block Par x decls stmts'
convertStmt (Block Seq x decls stmts) = do
stmts' <- step stmts
return $ Block Seq x decls $ filter (/= Null) stmts'
where
step :: [Stmt] -> State Info [Stmt]
step [] = return []
step (s : ss) = do
jt <- gets sJumpType
loopID <- gets sLoopID
if jt == JTNone then do
s' <- convertStmt s
jt' <- gets sJumpType
if jt' == JTNone || not (isBranch s) || null loopID then do
ss' <- step ss
return $ s' : ss'
else do
modify $ \t -> t { sJumpType = JTNone }
ss' <- step ss
let comp = BinOp Eq (Ident loopID) runLoop
let stmt = Block Seq "" [] ss'
modify $ \t -> t { sJumpType = jt' }
return [s', If Nothing comp stmt Null]
else do
return [Null]
isBranch :: Stmt -> Bool
isBranch (If{}) = True
isBranch (Case{}) = True
isBranch _ = False
convertStmt (If unique expr thenStmt elseStmt) = do
(thenStmt', thenJT) <- convertSubStmt thenStmt
(elseStmt', elseJT) <- convertSubStmt elseStmt
let newJT = max thenJT elseJT
modify $ \s -> s { sJumpType = newJT }
return $ If unique expr thenStmt' elseStmt'
convertStmt (Case unique kw expr cases mdef) = do
(mdef', mdefJT) <-
case mdef of
Nothing -> return (Nothing, JTNone)
Just stmt -> do
(stmt', jt) <- convertSubStmt stmt
return (Just stmt', jt)
results <- mapM convertSubStmt $ map snd cases
let (stmts', jts) = unzip results
let cases' = zip (map fst cases) stmts'
let newJT = foldl max mdefJT jts
modify $ \s -> s { sJumpType = newJT }
return $ Case unique kw expr cases' mdef'
convertStmt (For inits comp incr stmt) =
convertLoop loop comp stmt
where loop c s = For inits c incr s
convertStmt (While comp stmt) =
convertLoop While comp stmt
convertStmt (DoWhile comp stmt) =
convertLoop DoWhile comp stmt
convertStmt (Continue) = do
loopID <- gets sLoopID
modify $ \s -> s { sJumpType = JTContinue }
assertMsg (not $ null loopID) "encountered continue outside of loop"
return $ asgn loopID continueLoop
convertStmt (Break) = do
loopID <- gets sLoopID
modify $ \s -> s { sJumpType = JTBreak }
assertMsg (not $ null loopID) "encountered break outside of loop"
return $ asgn loopID exitLoop
convertStmt (Return Nil) = do
loopID <- gets sLoopID
modify $ \s -> s { sJumpType = JTReturn }
if null loopID
then return Null
else return $ asgn loopID exitLoop
convertStmt (RepeatL expr stmt) = do
modify $ \s -> s { sLoopID = "repeat" }
stmt' <- convertStmt stmt
jt <- gets sJumpType
assertMsg (jt == JTNone) "jumps not supported within repeat loops"
return $ RepeatL expr stmt'
convertStmt (Forever stmt) = do
modify $ \s -> s { sLoopID = "forever" }
stmt' <- convertStmt stmt
jt <- gets sJumpType
assertMsg (jt == JTNone) "jumps not supported within forever loops"
return $ Forever stmt'
convertStmt (Timing timing stmt) =
convertStmt stmt >>= return . Timing timing
convertStmt (StmtAttr attr stmt) =
convertStmt stmt >>= return . StmtAttr attr
convertStmt (Return{}) = return $
error "non-void return should have been elaborated already"
convertStmt (Foreach{}) = return $
error "foreach should have been elaborated already"
convertStmt other = return other
-- convert a statement on its own without changing the state, but returning the
-- resulting jump type; used to reconcile across branching statements
convertSubStmt :: Stmt -> State Info (Stmt, JumpType)
convertSubStmt stmt = do
origState <- get
stmt' <- convertStmt stmt
jt <- gets sJumpType
put origState
if sJumpType origState == JTNone
then return (stmt', jt)
else error $ "convertStmt invariant failed on: " ++ show stmt
convertLoop :: (Expr -> Stmt -> Stmt) -> Expr -> Stmt -> State Info Stmt
convertLoop loop comp stmt = do
Info { sJumpType = origJT, sLoopID = origLoopID } <- get
let loopID = (++) "_sv2v_loop_" $ shortHash $ loop comp stmt
modify $ \s -> s { sLoopID = loopID }
stmt' <- convertStmt stmt
jt <- gets sJumpType
let afterJT = if jt == JTReturn then jt else origJT
put $ Info { sJumpType = afterJT, sLoopID = origLoopID }
let comp' = BinOp LogAnd (BinOp Ne (Ident loopID) exitLoop) comp
return $ if jt == JTNone
then loop comp stmt'
else Block Seq ""
[ Variable Local loopStateType loopID [] (Just runLoop)
]
[ loop comp' $ Block Seq "" []
[ asgn loopID runLoop
, stmt'
]
, if afterJT == JTReturn && origLoopID /= ""
then asgn origLoopID exitLoop
else Null
]
where loopStateType = IntegerVector TBit Unspecified [(Number "0", Number "1")]
-- stop running the loop immediately (break or return)
exitLoop :: Expr
exitLoop = Number "0"
-- keep running the loop normally
runLoop :: Expr
runLoop = Number "1"
-- skip to the next iteration of the loop (continue)
continueLoop :: Expr
continueLoop = Number "2"
assertMsg :: Bool -> String -> State Info ()
assertMsg True _ = return ()
assertMsg False msg = error msg
asgn :: Identifier -> Expr -> Stmt
asgn x e = AsgnBlk AsgnOpEq (LHSIdent x) e
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
- Conversion for `return`
-}
module Convert.Return (convert) where
import Convert.Traverse
import Language.SystemVerilog.AST
convert :: [AST] -> [AST]
convert = map $ traverseDescriptions $ traverseModuleItems convertFunction
convertFunction :: ModuleItem -> ModuleItem
convertFunction (MIPackageItem (Function ml t f decls stmts)) =
MIPackageItem $ Function ml t f decls $
map (traverseNestedStmts convertStmt) stmts
where
convertStmt :: Stmt -> Stmt
convertStmt (Return e) = AsgnBlk AsgnOpEq (LHSIdent f) e
convertStmt other = other
convertFunction other = other
...@@ -229,6 +229,13 @@ traverseSinglyNestedStmtsM fullMapper = cs ...@@ -229,6 +229,13 @@ traverseSinglyNestedStmtsM fullMapper = cs
where where
cs (StmtAttr a stmt) = fullMapper stmt >>= return . StmtAttr a cs (StmtAttr a stmt) = fullMapper stmt >>= return . StmtAttr a
cs (Block _ "" [] []) = return Null cs (Block _ "" [] []) = return Null
cs (Block Seq name decls stmts) = do
stmts' <- mapM fullMapper stmts
return $ Block Seq name decls $ concatMap explode stmts'
where
explode :: Stmt -> [Stmt]
explode (Block Seq "" [] ss) = ss
explode other = [other]
cs (Block kw name decls stmts) = cs (Block kw name decls stmts) =
mapM fullMapper stmts >>= return . Block kw name decls mapM fullMapper stmts >>= return . Block kw name decls
cs (Case u kw expr cases def) = do cs (Case u kw expr cases def) = do
...@@ -254,6 +261,8 @@ traverseSinglyNestedStmtsM fullMapper = cs ...@@ -254,6 +261,8 @@ traverseSinglyNestedStmtsM fullMapper = cs
cs (Trigger blocks x) = return $ Trigger blocks x cs (Trigger blocks x) = return $ Trigger blocks x
cs (Assertion a) = cs (Assertion a) =
traverseAssertionStmtsM fullMapper a >>= return . Assertion traverseAssertionStmtsM fullMapper a >>= return . Assertion
cs (Continue) = return Continue
cs (Break) = return Break
cs (Null) = return Null cs (Null) = return Null
traverseAssertionStmtsM :: Monad m => MapperM m Stmt -> MapperM m Assertion traverseAssertionStmtsM :: Monad m => MapperM m Stmt -> MapperM m Assertion
...@@ -714,6 +723,8 @@ traverseStmtExprsM exprMapper = flatStmtMapper ...@@ -714,6 +723,8 @@ traverseStmtExprsM exprMapper = flatStmtMapper
a' <- traverseAssertionStmtsM stmtMapper a a' <- traverseAssertionStmtsM stmtMapper a
a'' <- traverseAssertionExprsM exprMapper a' a'' <- traverseAssertionExprsM exprMapper a'
return $ Assertion a'' return $ Assertion a''
flatStmtMapper (Continue) = return Continue
flatStmtMapper (Break) = return Break
flatStmtMapper (Null) = return Null flatStmtMapper (Null) = return Null
initsMapper (Left decls) = mapM declMapper decls >>= return . Left initsMapper (Left decls) = mapM declMapper decls >>= return . Left
......
...@@ -51,6 +51,8 @@ data Stmt ...@@ -51,6 +51,8 @@ data Stmt
| Subroutine (Maybe Identifier) Identifier Args | Subroutine (Maybe Identifier) Identifier Args
| Trigger Bool Identifier | Trigger Bool Identifier
| Assertion Assertion | Assertion Assertion
| Continue
| Break
| Null | Null
deriving Eq deriving Eq
...@@ -96,6 +98,8 @@ instance Show Stmt where ...@@ -96,6 +98,8 @@ instance Show Stmt where
show (Timing t s ) = printf "%s %s" (show t) (show s) show (Timing t s ) = printf "%s %s" (show t) (show s)
show (Trigger b x) = printf "->%s %s;" (if b then "" else ">") x show (Trigger b x) = printf "->%s %s;" (if b then "" else ">") x
show (Assertion a) = show a show (Assertion a) = show a
show (Continue ) = "continue;"
show (Break ) = "break;"
show (Null ) = ";" show (Null ) = ";"
data CaseKW data CaseKW
......
...@@ -911,6 +911,9 @@ StmtNonBlock :: { Stmt } ...@@ -911,6 +911,9 @@ StmtNonBlock :: { Stmt }
| Identifier "::" Identifier CallArgs ";" { Subroutine (Just $1) $3 $4 } | Identifier "::" Identifier CallArgs ";" { Subroutine (Just $1) $3 $4 }
| TimingControl Stmt { Timing $1 $2 } | TimingControl Stmt { Timing $1 $2 }
| "return" Expr ";" { Return $2 } | "return" Expr ";" { Return $2 }
| "return" ";" { Return Nil }
| "break" ";" { Break }
| "continue" ";" { Continue }
| "while" "(" Expr ")" Stmt { While $3 $5 } | "while" "(" Expr ")" Stmt { While $3 $5 }
| "repeat" "(" Expr ")" Stmt { RepeatL $3 $5 } | "repeat" "(" Expr ")" Stmt { RepeatL $3 $5 }
| "do" Stmt "while" "(" Expr ")" ";" { DoWhile $5 $2 } | "do" Stmt "while" "(" Expr ")" ";" { DoWhile $5 $2 }
......
...@@ -66,6 +66,7 @@ executable sv2v ...@@ -66,6 +66,7 @@ executable sv2v
Convert.FuncRet Convert.FuncRet
Convert.Interface Convert.Interface
Convert.IntTypes Convert.IntTypes
Convert.Jump
Convert.KWArgs Convert.KWArgs
Convert.Logic Convert.Logic
Convert.LogOp Convert.LogOp
...@@ -75,7 +76,6 @@ executable sv2v ...@@ -75,7 +76,6 @@ executable sv2v
Convert.Package Convert.Package
Convert.ParamType Convert.ParamType
Convert.RemoveComments Convert.RemoveComments
Convert.Return
Convert.Simplify Convert.Simplify
Convert.SizeCast Convert.SizeCast
Convert.StarPort Convert.StarPort
......
module top;
task skip1;
$display("HELLO skip1");
return;
$display("UNREACHABLE");
endtask
function void skip2;
$display("HELLO skip2");
return;
$display("UNREACHABLE");
endfunction
function int skip3;
$display("HELLO skip3");
return 1;
$display("UNREACHABLE");
endfunction
task skip4;
for (int i = 0; i < 10; ++i) begin
$display("HELLO skip4");
return;
$display("UNREACHABLE");
end
$display("UNREACHABLE");
endtask
task skip5;
for (int i = 0; i < 10; ++i) begin
$display("HELLO skip5-1");
for (int j = 0; j < 10; ++j) begin
$display("HELLO skip5-2");
return;
$display("UNREACHABLE");
end
$display("UNREACHABLE");
end
$display("UNREACHABLE");
endtask
initial begin
skip1;
skip2;
$display(skip3());
skip4;
skip5;
end
initial
for (int i = 0; i < 10; ++i) begin
$display("Loop Y:", i);
continue;
$display("UNREACHABLE");
end
initial
for (int i = 0; i < 10; ++i) begin
$display("Loop Z:", i);
break;
$display("UNREACHABLE");
end
initial
for (int i = 0; i < 10; ++i)
if (i < 5)
$display("Loop A:", i);
else
break;
initial
for (int i = 0; i < 10; ++i) begin
if (i < 3)
$display("Loop B-1:", i);
else if (i < 7)
$display("Loop B-2:", i);
else begin
$display("Loop B-3:", i);
continue;
$display("UNREACHABLE");
end
$display("Loop B:", i);
end
endmodule
module top;
task skip1;
$display("HELLO skip1");
endtask
task skip2;
$display("HELLO skip2");
endtask
function integer skip3;
input x;
begin
$display("HELLO skip3");
skip3 = 1;
end
endfunction
task skip4;
$display("HELLO skip4");
endtask
task skip5;
begin
$display("HELLO skip5-1");
$display("HELLO skip5-2");
end
endtask
initial begin
skip1;
skip2;
$display(skip3(0));
skip4;
skip5;
end
initial begin : loop_y
integer i;
for (i = 0; i < 10; ++i)
$display("Loop Y:", i);
end
initial begin : loop_z
integer i;
i = 0;
$display("Loop Z:", i);
end
initial begin : loop_a
integer i;
for (i = 0; i < 5; ++i)
$display("Loop A:", i);
end
initial begin : loop_b
integer i;
for (i = 0; i < 10; ++i) begin
if (i < 3) begin
$display("Loop B-1:", i);
$display("Loop B:", i);
end
else if (i < 7) begin
$display("Loop B-2:", i);
$display("Loop B:", i);
end
else
$display("Loop B-3:", i);
end
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