Commit 37355920 by Zachary Snow

cleaner AST output

parent d86f8535
......@@ -228,6 +228,7 @@ traverseSinglyNestedStmtsM fullMapper = cs
where
cs (StmtAttr a stmt) = fullMapper stmt >>= return . StmtAttr a
cs (Block _ "" [] []) = return Null
cs (Block _ "" [] [stmt]) = fullMapper stmt
cs (Block Seq name decls stmts) = do
stmts' <- mapM fullMapper stmts
return $ Block Seq name decls $ concatMap explode stmts'
......
......@@ -72,7 +72,7 @@ instance Show Expr where
show (Repeat e l ) = printf "{%s {%s}}" (show e) (commas $ map show l)
show (Concat l ) = printf "{%s}" (commas $ map show l)
show (Stream o e l) = printf "{%s %s%s}" (show o) (show e) (show $ Concat l)
show (UniOp a b ) = printf "(%s %s)" (show a) (show b)
show (UniOp o e ) = printf "%s%s" (show o) (show e)
show (BinOp o a b) = printf "(%s %s %s)" (show a) (show o) (show b)
show (Dot e n ) = printf "%s.%s" (show e) n
show (Mux c a b) = printf "(%s ? %s : %s)" (show c) (show a) (show b)
......
......@@ -54,3 +54,7 @@ instance Show GenItem where
show (GenModuleItem item) = show item
type GenCase = ([Expr], GenItem)
showCase :: (Show x, Show y) => ([x], y) -> String
showCase (a, b) = printf "%s: %s" (commas $ map show a) (show b)
......@@ -12,12 +12,10 @@ module Language.SystemVerilog.AST.ShowHelp
, unlines'
, commas
, indentedParenList
, showCase
, showEither
) where
import Data.List (intercalate)
import Text.Printf (printf)
showPad :: Show t => t -> String
showPad x =
......@@ -51,9 +49,6 @@ indentedParenList [] = "()"
indentedParenList [x] = "(" ++ x ++ ")"
indentedParenList l = "(\n" ++ (indent $ intercalate ",\n" l) ++ "\n)"
showCase :: (Show x, Show y) => ([x], y) -> String
showCase (a, b) = printf "%s: %s" (commas $ map show a) (show b)
showEither :: (Show a, Show b) => Either a b -> String
showEither (Left v) = show v
showEither (Right v) = show v
......@@ -25,7 +25,7 @@ module Language.SystemVerilog.AST.Stmt
import Text.Printf (printf)
import Language.SystemVerilog.AST.ShowHelp (commas, indent, unlines', showPad, showCase)
import Language.SystemVerilog.AST.ShowHelp (commas, indent, unlines', showPad)
import Language.SystemVerilog.AST.Attr (Attr)
import Language.SystemVerilog.AST.Decl (Decl)
import Language.SystemVerilog.AST.Expr (Expr, Args(..))
......@@ -93,16 +93,32 @@ instance Show Stmt where
show (DoWhile e s) = printf "do %s while (%s);" (show s) (show e)
show (Forever s ) = printf "forever %s" (show s)
show (Foreach x i s) = printf "foreach (%s [ %s ]) %s" x (commas $ map (maybe "" id) i) (show s)
show (If u a b Null) = printf "%sif (%s) %s" (maybe "" showPad u) (show a) (show b)
show (If u a b c ) = printf "%sif (%s) %s\nelse %s" (maybe "" showPad u) (show a) (show b) (show c)
show (If u a b Null) = printf "%sif (%s)%s" (maybe "" showPad u) (show a) (showBranch b)
show (If u a b c ) = printf "%sif (%s)%s\nelse%s" (maybe "" showPad u) (show a) (showBranch b) (showElseBranch c)
show (Return e ) = printf "return %s;" (show e)
show (Timing t s ) = printf "%s %s" (show t) (show s)
show (Timing t s ) = printf "%s%s" (show t) (showShortBranch s)
show (Trigger b x) = printf "->%s %s;" (if b then "" else ">") x
show (Assertion a) = show a
show (Continue ) = "continue;"
show (Break ) = "break;"
show (Null ) = ";"
showBranch :: Stmt -> String
showBranch (block @ Block{}) = ' ' : show block
showBranch stmt = '\n' : (indent $ show stmt)
showElseBranch :: Stmt -> String
showElseBranch (stmt @ If{}) = ' ' : show stmt
showElseBranch stmt = showBranch stmt
showShortBranch :: Stmt -> String
showShortBranch (stmt @ AsgnBlk{}) = ' ' : show stmt
showShortBranch (stmt @ Asgn{}) = ' ' : show stmt
showShortBranch stmt = showBranch stmt
showCase :: ([Expr], Stmt) -> String
showCase (a, b) = printf "%s:%s" (commas $ map show a) (showShortBranch b)
data CaseKW
= CaseN
| CaseZ
......
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