Commit 14ba5dae by Zachary Snow

support for reduction ops, non-named/non-identifier module instantiation arguments, always @*

parent 5b336439
...@@ -40,6 +40,7 @@ data Module ...@@ -40,6 +40,7 @@ data Module
deriving Eq deriving Eq
instance Show Module where instance Show Module where
showList modules _ = intercalate "\n\n" $ map show modules
show (Module name ports items) = unlines show (Module name ports items) = unlines
[ "module " ++ name ++ (if null ports then "" else "(" ++ commas ports ++ ")") ++ ";" [ "module " ++ name ++ (if null ports then "" else "(" ++ commas ports ++ ")") ++ ";"
, unlines' $ map show items , unlines' $ map show items
...@@ -114,7 +115,7 @@ instance Show ModuleItem where ...@@ -114,7 +115,7 @@ instance Show ModuleItem where
| otherwise -> printf "%s #%s %s %s;" m (showPorts showExprConst params) i (showPorts show ports) | otherwise -> printf "%s #%s %s %s;" m (showPorts showExprConst params) i (showPorts show ports)
where where
showPorts :: (Expr -> String) -> [(Identifier, Maybe Expr)] -> String showPorts :: (Expr -> String) -> [(Identifier, Maybe Expr)] -> String
showPorts s ports = printf "(%s)" $ commas [ printf ".%s(%s)" i (if isJust arg then s $ fromJust arg else "") | (i, arg) <- ports ] showPorts s ports = printf "(%s)" $ commas [ if i == "" then show (fromJust arg) else printf ".%s(%s)" i (if isJust arg then s $ fromJust arg else "") | (i, arg) <- ports ]
showRange :: Maybe Range -> String showRange :: Maybe Range -> String
showRange Nothing = "" showRange Nothing = ""
...@@ -147,14 +148,30 @@ data Expr ...@@ -147,14 +148,30 @@ data Expr
| Bit Expr Int | Bit Expr Int
deriving Eq deriving Eq
data UniOp = Not | BWNot | UAdd | USub deriving Eq data UniOp
= Not
| BWNot
| UAdd
| USub
| RedAnd
| RedNand
| RedOr
| RedNor
| RedXor
| RedXnor
deriving Eq
instance Show UniOp where instance Show UniOp where
show a = case a of show Not = "!"
Not -> "!" show BWNot = "~"
BWNot -> "~" show UAdd = "+"
UAdd -> "+" show USub = "-"
USub -> "-" show RedAnd = "&"
show RedNand = "~&"
show RedOr = "|"
show RedNor = "~|"
show RedXor = "^"
show RedXnor = "~^"
data BinOp data BinOp
= And = And
...@@ -319,6 +336,7 @@ data Sense ...@@ -319,6 +336,7 @@ data Sense
| SenseOr Sense Sense | SenseOr Sense Sense
| SensePosedge LHS | SensePosedge LHS
| SenseNegedge LHS | SenseNegedge LHS
| SenseStar
deriving Eq deriving Eq
instance Show Sense where instance Show Sense where
...@@ -326,6 +344,7 @@ instance Show Sense where ...@@ -326,6 +344,7 @@ instance Show Sense where
show (SenseOr a b) = printf "%s or %s" (show a) (show b) show (SenseOr a b) = printf "%s or %s" (show a) (show b)
show (SensePosedge a ) = printf "posedge %s" (show a) show (SensePosedge a ) = printf "posedge %s" (show a)
show (SenseNegedge a ) = printf "negedge %s" (show a) show (SenseNegedge a ) = printf "negedge %s" (show a)
show (SenseStar ) = "*"
type Range = (Expr, Expr) type Range = (Expr, Expr)
...@@ -14,7 +14,7 @@ import Language.SystemVerilog.Parser.Tokens ...@@ -14,7 +14,7 @@ import Language.SystemVerilog.Parser.Tokens
%tokentype { Token } %tokentype { Token }
%error { parseError } %error { parseError }
-- %expect 0 %expect 0
%token %token
...@@ -147,7 +147,7 @@ string { Token Lit_string _ _ } ...@@ -147,7 +147,7 @@ string { Token Lit_string _ _ }
%left "<<" ">>" %left "<<" ">>"
%left "+" "-" %left "+" "-"
%left "*" "/" "%" %left "*" "/" "%"
%left UPlus UMinus "!" "~" %left UPlus UMinus "!" "~" RedOps
%% %%
...@@ -161,9 +161,9 @@ Modules :: { [Module] } ...@@ -161,9 +161,9 @@ Modules :: { [Module] }
| Modules Module { $1 ++ [$2] } | Modules Module { $1 ++ [$2] }
Module :: { Module } Module :: { Module }
: "module" Identifier ";" ModuleItems "endmodule" { Module $2 [] $4 } : "module" Identifier ";" ModuleItems "endmodule" opt(";") { Module $2 [] $4 }
| "module" Identifier PortNames ";" ModuleItems "endmodule" { Module $2 $3 $5 } | "module" Identifier PortNames ";" ModuleItems "endmodule" opt(";") { Module $2 $3 $5 }
| "module" Identifier PortDecls ";" ModuleItems "endmodule" { Module $2 (getPortNames $3) ($3 ++ $5) } | "module" Identifier PortDecls ";" ModuleItems "endmodule" opt(";") { Module $2 (getPortNames $3) ($3 ++ $5) }
Identifier :: { Identifier } Identifier :: { Identifier }
: simpleIdentifier { tokenString $1 } : simpleIdentifier { tokenString $1 }
...@@ -221,6 +221,9 @@ ModuleItem :: { [ModuleItem] } ...@@ -221,6 +221,9 @@ ModuleItem :: { [ModuleItem] }
| "initial" Stmt { [Initial $2] } | "initial" Stmt { [Initial $2] }
| "always" Stmt { [Always Nothing $2] } | "always" Stmt { [Always Nothing $2] }
| "always" "@" "(" Sense ")" Stmt { [Always (Just $4) $6] } | "always" "@" "(" Sense ")" Stmt { [Always (Just $4) $6] }
| "always" "@" "(" "*" ")" Stmt { [Always (Just SenseStar) $6] }
| "always" "@" "*" Stmt { [Always (Just SenseStar) $4] }
| "always" "@*" Stmt { [Always (Just SenseStar) $3] }
| Identifier ParameterBindings Identifier Bindings ";" { [Instance $1 $2 $3 $4] } | Identifier ParameterBindings Identifier Bindings ";" { [Instance $1 $2 $3 $4] }
RegDeclarations :: { [(Identifier, Maybe Range)] } RegDeclarations :: { [(Identifier, Maybe Range)] }
...@@ -271,6 +274,7 @@ Bindings1 :: { [(Identifier, Maybe Expr)] } ...@@ -271,6 +274,7 @@ Bindings1 :: { [(Identifier, Maybe Expr)] }
Binding :: { (Identifier, Maybe Expr) } Binding :: { (Identifier, Maybe Expr) }
: "." Identifier "(" MaybeExpr ")" { ($2, $4) } : "." Identifier "(" MaybeExpr ")" { ($2, $4) }
| "." Identifier { ($2, Just $ Ident $2) } | "." Identifier { ($2, Just $ Ident $2) }
| Expr { ("", Just $1) }
ParameterBindings :: { [(Identifier, Maybe Expr)] } ParameterBindings :: { [(Identifier, Maybe Expr)] }
: { [] } : { [] }
...@@ -355,12 +359,19 @@ Expr :: { Expr } ...@@ -355,12 +359,19 @@ Expr :: { Expr }
| Expr "+" Expr { BinOp Add $1 $3 } | Expr "+" Expr { BinOp Add $1 $3 }
| Expr "-" Expr { BinOp Sub $1 $3 } | Expr "-" Expr { BinOp Sub $1 $3 }
| Expr "*" Expr { BinOp Mul $1 $3 } | Expr "*" Expr { BinOp Mul $1 $3 }
| Expr"/" Expr { BinOp Div $1 $3 } | Expr "/" Expr { BinOp Div $1 $3 }
| Expr "%" Expr { BinOp Mod $1 $3 } | Expr "%" Expr { BinOp Mod $1 $3 }
| "!" Expr { UniOp Not $2 } | "!" Expr { UniOp Not $2 }
| "~" Expr { UniOp BWNot $2 } | "~" Expr { UniOp BWNot $2 }
| "+" Expr %prec UPlus { UniOp UAdd $2 } | "+" Expr %prec UPlus { UniOp UAdd $2 }
| "-" Expr %prec UMinus { UniOp USub $2 } | "-" Expr %prec UMinus { UniOp USub $2 }
| "&" Expr %prec RedOps { UniOp RedAnd $2 }
| "~&" Expr %prec RedOps { UniOp RedNand $2 }
| "|" Expr %prec RedOps { UniOp RedOr $2 }
| "~|" Expr %prec RedOps { UniOp RedNor $2 }
| "^" Expr %prec RedOps { UniOp RedXor $2 }
| "~^" Expr %prec RedOps { UniOp RedXnor $2 }
| "^~" Expr %prec RedOps { UniOp RedXnor $2 }
{ {
......
...@@ -58,6 +58,7 @@ preprocess env file content = unlines $ pp True [] env $ lines $ uncomment file ...@@ -58,6 +58,7 @@ preprocess env file content = unlines $ pp True [] env $ lines $ uncomment file
"`endif" : _ "`endif" : _
| not $ null stack -> "" : pp (head stack) (tail stack) env rest | not $ null stack -> "" : pp (head stack) (tail stack) env rest
| otherwise -> error $ "`endif without associated `ifdef/`ifndef: " ++ file | otherwise -> error $ "`endif without associated `ifdef/`ifndef: " ++ file
"`default_nettype" : _ -> "" : pp on stack env rest
_ -> (if on then ppLine env a else "") : pp on stack env rest _ -> (if on then ppLine env a else "") : pp on stack env rest
ppLine :: [(String, String)] -> String -> String ppLine :: [(String, String)] -> String -> String
......
...@@ -15,11 +15,11 @@ main = do ...@@ -15,11 +15,11 @@ main = do
[filePath] <- getArgs [filePath] <- getArgs
content <- readFile filePath content <- readFile filePath
let ast = parseFile [] filePath content let ast = parseFile [] filePath content
let res = Left ast let res = Right ast
case res of case res of
Left err -> do Left _ -> do
hPrint stderr err --hPrint stderr err
exitSuccess exitFailure
--exitFailure Right str -> do
Right _ -> do hPrint stdout str
exitSuccess exitSuccess
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