Commit d847fdfa by Zachary Snow

split phases into sections

parent 5c263298
...@@ -51,15 +51,19 @@ import qualified Convert.Unsigned ...@@ -51,15 +51,19 @@ import qualified Convert.Unsigned
import qualified Convert.Wildcard import qualified Convert.Wildcard
type Phase = [AST] -> [AST] type Phase = [AST] -> [AST]
type Selector = Job.Exclude -> Phase -> Phase
phases :: [Job.Exclude] -> [Phase] finalPhases :: Selector -> [Phase]
phases excludes = finalPhases _ =
[ Convert.NamedBlock.convert
, Convert.DuplicateGenvar.convert
]
mainPhases :: Selector -> [Phase]
mainPhases selectExclude =
[ Convert.AsgnOp.convert [ Convert.AsgnOp.convert
, Convert.NamedBlock.convert
, selectExclude (Job.Assert , Convert.Assertion.convert)
, Convert.BlockDecl.convert , Convert.BlockDecl.convert
, Convert.DuplicateGenvar.convert , selectExclude Job.Logic Convert.Logic.convert
, selectExclude (Job.Logic , Convert.Logic.convert)
, Convert.FuncRet.convert , Convert.FuncRet.convert
, Convert.FuncRoutine.convert , Convert.FuncRoutine.convert
, Convert.EmptyArgs.convert , Convert.EmptyArgs.convert
...@@ -67,7 +71,6 @@ phases excludes = ...@@ -67,7 +71,6 @@ phases excludes =
, Convert.Inside.convert , Convert.Inside.convert
, Convert.IntTypes.convert , Convert.IntTypes.convert
, Convert.KWArgs.convert , Convert.KWArgs.convert
, Convert.LogOp.convert
, Convert.MultiplePacked.convert , Convert.MultiplePacked.convert
, Convert.UnbasedUnsized.convert , Convert.UnbasedUnsized.convert
, Convert.Cast.convert , Convert.Cast.convert
...@@ -79,39 +82,45 @@ phases excludes = ...@@ -79,39 +82,45 @@ phases excludes =
, Convert.Struct.convert , Convert.Struct.convert
, Convert.TFBlock.convert , Convert.TFBlock.convert
, Convert.Typedef.convert , Convert.Typedef.convert
, Convert.Unique.convert
, Convert.UnpackedArray.convert , Convert.UnpackedArray.convert
, Convert.Unsigned.convert , Convert.Unsigned.convert
, Convert.Wildcard.convert , Convert.Wildcard.convert
, Convert.Enum.convert , Convert.Enum.convert
, Convert.ForDecl.convert , Convert.ForDecl.convert
, Convert.Jump.convert
, Convert.Foreach.convert
, Convert.StringParam.convert , Convert.StringParam.convert
, selectExclude (Job.Interface, Convert.Interface.convert) , selectExclude Job.Interface Convert.Interface.convert
, Convert.StarPort.convert , selectExclude Job.Succinct Convert.RemoveComments.convert
, selectExclude (Job.Always , Convert.AlwaysKW.convert)
, selectExclude (Job.Succinct , Convert.RemoveComments.convert)
] ]
where
selectExclude :: (Job.Exclude, Phase) -> Phase
selectExclude (exclude, phase) =
if elem exclude excludes
then id
else phase
run :: [Job.Exclude] -> Phase initialPhases :: Selector -> [Phase]
run excludes = foldr (.) id $ phases excludes initialPhases selectExclude =
[ Convert.Jump.convert
, Convert.Unique.convert
, Convert.LogOp.convert
, Convert.Foreach.convert
, Convert.StarPort.convert
, selectExclude Job.Assert Convert.Assertion.convert
, selectExclude Job.Always Convert.AlwaysKW.convert
, Convert.Package.convert
, Convert.ParamNoDefault.convert
]
convert :: [Job.Exclude] -> Phase convert :: [Job.Exclude] -> Phase
convert excludes = convert excludes =
convert' final . loopMain . initial
. Convert.Package.convert
. Convert.ParamNoDefault.convert
where where
convert' :: Phase final = combine $ finalPhases selectExclude
convert' descriptions = main = combine $ mainPhases selectExclude
initial = combine $ initialPhases selectExclude
combine = foldr1 (.)
loopMain :: Phase
loopMain descriptions =
if descriptions == descriptions' if descriptions == descriptions'
then descriptions then descriptions
else convert' descriptions' else loopMain descriptions'
where descriptions' = run excludes descriptions where descriptions' = main descriptions
selectExclude :: Selector
selectExclude exclude phase =
if elem exclude excludes
then id
else phase
...@@ -139,9 +139,8 @@ convertStmt (Block Par x decls stmts) = do ...@@ -139,9 +139,8 @@ convertStmt (Block Par x decls stmts) = do
modify $ \s -> s { sJumpAllowed = jumpAllowed, sReturnAllowed = returnAllowed } modify $ \s -> s { sJumpAllowed = jumpAllowed, sReturnAllowed = returnAllowed }
return $ Block Par x decls stmts' return $ Block Par x decls stmts'
convertStmt (Block Seq x decls stmts) = do convertStmt (Block Seq x decls stmts) =
stmts' <- step stmts step stmts >>= return . Block Seq x decls
return $ Block Seq x decls $ filter (/= Null) stmts'
where where
step :: [Stmt] -> State Info [Stmt] step :: [Stmt] -> State Info [Stmt]
step [] = return [] step [] = return []
......
...@@ -103,6 +103,8 @@ traverseModuleItem ports scopes = ...@@ -103,6 +103,8 @@ traverseModuleItem ports scopes =
Just (_, _, t) -> tell [isRegType t] Just (_, _, t) -> tell [isRegType t]
_ -> tell [False] _ -> tell [False]
always_comb = AlwaysC Always . Timing (Event SenseStar)
fixModuleItem :: ModuleItem -> ModuleItem fixModuleItem :: ModuleItem -> ModuleItem
-- rewrite bad continuous assignments to use procedural assignments -- rewrite bad continuous assignments to use procedural assignments
fixModuleItem (Assign AssignOptionNone lhs expr) = fixModuleItem (Assign AssignOptionNone lhs expr) =
...@@ -112,7 +114,7 @@ traverseModuleItem ports scopes = ...@@ -112,7 +114,7 @@ traverseModuleItem ports scopes =
Generate $ map GenModuleItem Generate $ map GenModuleItem
[ MIPackageItem (Decl (Variable Local t x [] Nil)) [ MIPackageItem (Decl (Variable Local t x [] Nil))
, Assign AssignOptionNone (LHSIdent x) expr , Assign AssignOptionNone (LHSIdent x) expr
, AlwaysC AlwaysComb $ Asgn AsgnOpEq Nothing lhs (Ident x) , always_comb $ Asgn AsgnOpEq Nothing lhs (Ident x)
] ]
where where
t = Net (NetType TWire) Unspecified t = Net (NetType TWire) Unspecified
...@@ -146,7 +148,7 @@ traverseModuleItem ports scopes = ...@@ -146,7 +148,7 @@ traverseModuleItem ports scopes =
[(DimsFn FnBits $ Right expr, RawNum 1)] [(DimsFn FnBits $ Right expr, RawNum 1)]
items = items =
[ MIPackageItem $ Decl $ Variable Local t tmp [] Nil [ MIPackageItem $ Decl $ Variable Local t tmp [] Nil
, AlwaysC AlwaysComb $ Asgn AsgnOpEq Nothing lhs tmpExpr] , always_comb $ Asgn AsgnOpEq Nothing lhs tmpExpr]
lhs = case exprToLHS expr of lhs = case exprToLHS expr of
Just l -> l Just l -> l
Nothing -> Nothing ->
......
...@@ -45,8 +45,10 @@ convertPackageItem other = other ...@@ -45,8 +45,10 @@ convertPackageItem other = other
convertStmt :: Stmt -> Stmt convertStmt :: Stmt -> Stmt
convertStmt (CommentStmt _) = Null convertStmt (CommentStmt _) = Null
convertStmt (Block kw name decls stmts) = convertStmt (Block kw name decls stmts) =
Block kw name decls' stmts Block kw name decls' stmts'
where decls' = convertDecls decls where
decls' = convertDecls decls
stmts' = filter (/= Null) stmts
convertStmt (For (Left decls) cond incr stmt) = convertStmt (For (Left decls) cond incr stmt) =
For (Left decls') cond incr stmt For (Left decls') cond incr stmt
where decls' = convertDecls decls where decls' = convertDecls decls
......
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