2019-03-04 08:58:00 +01:00
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
2019-02-08 06:19:39 +01:00
|
|
|
module Language.SystemVerilog.AST
|
2019-02-08 05:49:12 +01:00
|
|
|
( Identifier
|
2019-02-18 09:59:17 +01:00
|
|
|
, Description(..)
|
2019-03-07 19:19:31 +01:00
|
|
|
, PackageItem(..)
|
2019-02-08 05:49:12 +01:00
|
|
|
, ModuleItem (..)
|
2019-02-09 23:35:31 +01:00
|
|
|
, Direction (..)
|
|
|
|
|
, Type (..)
|
2019-02-08 05:49:12 +01:00
|
|
|
, Stmt (..)
|
|
|
|
|
, LHS (..)
|
|
|
|
|
, Expr (..)
|
|
|
|
|
, UniOp (..)
|
|
|
|
|
, BinOp (..)
|
2019-03-05 00:25:14 +01:00
|
|
|
, AsgnOp (..)
|
2019-02-08 05:49:12 +01:00
|
|
|
, Sense (..)
|
2019-03-05 02:58:09 +01:00
|
|
|
, Timing (..)
|
2019-02-18 00:33:20 +01:00
|
|
|
, GenItem (..)
|
2019-02-23 21:10:25 +01:00
|
|
|
, AlwaysKW (..)
|
|
|
|
|
, CaseKW (..)
|
2019-03-04 08:58:00 +01:00
|
|
|
, PartKW (..)
|
2019-02-24 09:06:40 +01:00
|
|
|
, Decl (..)
|
2019-03-04 20:25:38 +01:00
|
|
|
, Lifetime (..)
|
2019-02-18 09:59:17 +01:00
|
|
|
, AST
|
2019-02-08 05:49:12 +01:00
|
|
|
, PortBinding
|
2019-03-04 08:58:00 +01:00
|
|
|
, ModportDecl
|
2019-02-08 05:49:12 +01:00
|
|
|
, Case
|
|
|
|
|
, Range
|
2019-02-18 00:33:20 +01:00
|
|
|
, GenCase
|
2019-03-01 01:48:58 +01:00
|
|
|
, typeRanges
|
2019-03-06 06:51:09 +01:00
|
|
|
, simplify
|
|
|
|
|
, rangeSize
|
2019-02-08 05:49:12 +01:00
|
|
|
) where
|
|
|
|
|
|
|
|
|
|
import Data.List
|
|
|
|
|
import Data.Maybe
|
|
|
|
|
import Text.Printf
|
2019-03-06 06:51:09 +01:00
|
|
|
import Text.Read (readMaybe)
|
2019-02-08 05:49:12 +01:00
|
|
|
|
|
|
|
|
type Identifier = String
|
|
|
|
|
|
2019-02-09 23:35:31 +01:00
|
|
|
-- Note: Verilog allows modules to be declared with either a simple list of
|
|
|
|
|
-- ports _identifiers_, or a list of port _declarations_. If only the
|
|
|
|
|
-- identifiers are used, they must be declared with a type and direction
|
|
|
|
|
-- (potentially separately!) within the module itself.
|
|
|
|
|
|
|
|
|
|
-- Note: This AST will allow for the representation of syntactically invalid
|
|
|
|
|
-- things, like input regs. We might want to have a function for doing some
|
|
|
|
|
-- basing invariant checks. I want to avoid making a full type-checker though,
|
|
|
|
|
-- as we should only be given valid SystemVerilog input files.
|
|
|
|
|
|
2019-02-18 09:59:17 +01:00
|
|
|
type AST = [Description]
|
|
|
|
|
|
2019-03-07 19:19:31 +01:00
|
|
|
data PackageItem
|
|
|
|
|
= Typedef Type Identifier
|
|
|
|
|
| Function (Maybe Lifetime) Type Identifier [Decl] [Stmt]
|
2019-03-07 19:58:20 +01:00
|
|
|
| Task (Maybe Lifetime) Identifier [Decl] [Stmt]
|
2019-03-07 19:19:31 +01:00
|
|
|
| Comment String
|
|
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
instance Show PackageItem where
|
|
|
|
|
show (Typedef t x) = printf "typedef %s %s;" (show t) x
|
|
|
|
|
show (Function ml t x i b) =
|
|
|
|
|
printf "function %s%s%s;\n%s\n%s\nendfunction"
|
|
|
|
|
(showLifetime ml) (showPad t) x (indent $ show i)
|
|
|
|
|
(indent $ unlines' $ map show b)
|
2019-03-07 19:58:20 +01:00
|
|
|
show (Task ml x i b) =
|
|
|
|
|
printf "task %s%s;\n%s\n%s\nendtask"
|
|
|
|
|
(showLifetime ml) x (indent $ show i)
|
|
|
|
|
(indent $ unlines' $ map show b)
|
2019-03-07 19:19:31 +01:00
|
|
|
show (Comment c) = "// " ++ c
|
|
|
|
|
|
2019-02-18 09:59:17 +01:00
|
|
|
data Description
|
2019-03-04 08:58:00 +01:00
|
|
|
= Part PartKW Identifier [Identifier] [ModuleItem]
|
2019-03-07 19:19:31 +01:00
|
|
|
| PackageItem PackageItem
|
2019-02-09 23:35:31 +01:00
|
|
|
deriving Eq
|
2019-02-08 05:49:12 +01:00
|
|
|
|
2019-02-18 09:59:17 +01:00
|
|
|
instance Show Description where
|
|
|
|
|
showList descriptions _ = intercalate "\n" $ map show descriptions
|
2019-03-04 08:58:00 +01:00
|
|
|
show (Part kw name ports items) = unlines
|
|
|
|
|
[ (show kw) ++ " " ++ name ++ portsStr ++ ";"
|
2019-02-10 23:59:41 +01:00
|
|
|
, indent $ unlines' $ map show items
|
2019-03-04 08:58:00 +01:00
|
|
|
, "end" ++ (show kw) ]
|
2019-02-10 23:59:41 +01:00
|
|
|
where
|
|
|
|
|
portsStr =
|
|
|
|
|
if null ports
|
|
|
|
|
then ""
|
|
|
|
|
else indentedParenList ports
|
2019-03-07 19:19:31 +01:00
|
|
|
show (PackageItem i) = show i
|
2019-02-08 05:49:12 +01:00
|
|
|
|
2019-03-04 08:58:00 +01:00
|
|
|
data PartKW
|
|
|
|
|
= Module
|
|
|
|
|
| Interface
|
|
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
instance Show PartKW where
|
|
|
|
|
show Module = "module"
|
|
|
|
|
show Interface = "interface"
|
|
|
|
|
|
2019-02-09 23:35:31 +01:00
|
|
|
data Direction
|
|
|
|
|
= Input
|
|
|
|
|
| Output
|
|
|
|
|
| Inout
|
2019-02-24 09:06:40 +01:00
|
|
|
| Local
|
2019-02-09 23:35:31 +01:00
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
instance Show Direction where
|
|
|
|
|
show Input = "input"
|
|
|
|
|
show Output = "output"
|
|
|
|
|
show Inout = "inout"
|
2019-02-24 09:06:40 +01:00
|
|
|
show Local = ""
|
2019-02-09 23:35:31 +01:00
|
|
|
|
|
|
|
|
data Type
|
2019-02-24 09:06:40 +01:00
|
|
|
= Reg [Range]
|
|
|
|
|
| Wire [Range]
|
|
|
|
|
| Logic [Range]
|
|
|
|
|
| Alias Identifier [Range]
|
|
|
|
|
| Implicit [Range]
|
|
|
|
|
| IntegerT
|
2019-02-24 03:24:13 +01:00
|
|
|
| Enum (Maybe Type) [(Identifier, Maybe Expr)] [Range]
|
2019-03-02 02:26:44 +01:00
|
|
|
| Struct Bool [(Type, Identifier)] [Range]
|
2019-03-04 08:58:00 +01:00
|
|
|
| InterfaceT Identifier (Maybe Identifier) [Range]
|
2019-03-01 04:44:31 +01:00
|
|
|
deriving (Eq, Ord)
|
2019-02-09 23:35:31 +01:00
|
|
|
|
|
|
|
|
instance Show Type where
|
2019-02-24 09:06:40 +01:00
|
|
|
show (Reg r) = "reg" ++ (showRanges r)
|
|
|
|
|
show (Wire r) = "wire" ++ (showRanges r)
|
|
|
|
|
show (Logic r) = "logic" ++ (showRanges r)
|
|
|
|
|
show (Alias t r) = t ++ (showRanges r)
|
|
|
|
|
show (Implicit r) = (showRanges r)
|
|
|
|
|
show (IntegerT ) = "integer"
|
2019-03-04 08:58:00 +01:00
|
|
|
show (InterfaceT x my r) = x ++ yStr ++ (showRanges r)
|
|
|
|
|
where yStr = maybe "" ("."++) my
|
2019-02-24 03:24:13 +01:00
|
|
|
show (Enum mt vals r) = printf "enum %s{%s}%s" tStr (commas $ map showVal vals) (showRanges r)
|
|
|
|
|
where
|
2019-02-24 09:06:40 +01:00
|
|
|
tStr = maybe "" showPad mt
|
2019-02-24 03:24:13 +01:00
|
|
|
showVal :: (Identifier, Maybe Expr) -> String
|
|
|
|
|
showVal (x, e) = x ++ (showAssignment e)
|
2019-03-02 02:26:44 +01:00
|
|
|
show (Struct p items r) = printf "struct %s{\n%s\n}%s" packedStr itemsStr (showRanges r)
|
|
|
|
|
where
|
|
|
|
|
packedStr = if p then "packed " else ""
|
|
|
|
|
itemsStr = indent $ unlines' $ map showItem items
|
|
|
|
|
showItem (t, x) = printf "%s %s;" (show t) x
|
2019-02-09 23:35:31 +01:00
|
|
|
|
2019-03-04 08:58:00 +01:00
|
|
|
instance Show ([Range] -> Type) where
|
2019-03-06 06:51:09 +01:00
|
|
|
show tf = show (tf [])
|
2019-03-04 08:58:00 +01:00
|
|
|
|
|
|
|
|
instance Eq ([Range] -> Type) where
|
2019-03-06 06:51:09 +01:00
|
|
|
(==) tf1 tf2 = (tf1 []) == (tf2 [])
|
|
|
|
|
|
|
|
|
|
instance Ord ([Range] -> Type) where
|
|
|
|
|
compare tf1 tf2 = compare (show tf1) (show tf2)
|
2019-03-04 08:58:00 +01:00
|
|
|
|
2019-03-01 01:48:58 +01:00
|
|
|
typeRanges :: Type -> ([Range] -> Type, [Range])
|
|
|
|
|
typeRanges (Reg r) = (Reg , r)
|
|
|
|
|
typeRanges (Wire r) = (Wire , r)
|
|
|
|
|
typeRanges (Logic r) = (Logic , r)
|
|
|
|
|
typeRanges (Alias t r) = (Alias t, r)
|
|
|
|
|
typeRanges (Implicit r) = (Implicit, r)
|
2019-03-06 06:51:09 +01:00
|
|
|
typeRanges (IntegerT ) = (\[] -> IntegerT, [])
|
2019-03-01 01:48:58 +01:00
|
|
|
typeRanges (Enum t v r) = (Enum t v, r)
|
2019-03-02 02:26:44 +01:00
|
|
|
typeRanges (Struct p l r) = (Struct p l, r)
|
2019-03-04 08:58:00 +01:00
|
|
|
typeRanges (InterfaceT x my r) = (InterfaceT x my, r)
|
2019-02-26 06:40:50 +01:00
|
|
|
|
2019-02-24 09:06:40 +01:00
|
|
|
data Decl
|
|
|
|
|
= Parameter Type Identifier Expr
|
|
|
|
|
| Localparam Type Identifier Expr
|
|
|
|
|
| Variable Direction Type Identifier [Range] (Maybe Expr)
|
|
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
instance Show Decl where
|
|
|
|
|
showList l _ = unlines' $ map show l
|
|
|
|
|
show (Parameter t x e) = printf "parameter %s%s = %s;" (showPad t) x (show e)
|
|
|
|
|
show (Localparam t x e) = printf "localparam %s%s = %s;" (showPad t) x (show e)
|
|
|
|
|
show (Variable d t x a me) = printf "%s%s %s%s%s;" (showPad d) (show t) x (showRanges a) (showAssignment me)
|
|
|
|
|
|
2019-02-08 05:49:12 +01:00
|
|
|
data ModuleItem
|
2019-03-07 19:19:31 +01:00
|
|
|
= MIDecl Decl
|
2019-02-18 06:26:43 +01:00
|
|
|
| AlwaysC AlwaysKW Stmt
|
2019-02-08 05:49:12 +01:00
|
|
|
| Assign LHS Expr
|
2019-02-20 21:22:26 +01:00
|
|
|
| Instance Identifier [PortBinding] Identifier (Maybe [PortBinding]) -- `Nothing` represents `.*`
|
2019-02-18 00:33:20 +01:00
|
|
|
| Genvar Identifier
|
|
|
|
|
| Generate [GenItem]
|
2019-03-04 08:58:00 +01:00
|
|
|
| Modport Identifier [ModportDecl]
|
2019-03-05 02:58:09 +01:00
|
|
|
| Initial Stmt
|
2019-03-07 19:19:31 +01:00
|
|
|
| MIPackageItem PackageItem
|
2019-02-08 05:49:12 +01:00
|
|
|
deriving Eq
|
|
|
|
|
|
2019-02-18 06:26:43 +01:00
|
|
|
data AlwaysKW
|
|
|
|
|
= Always
|
|
|
|
|
| AlwaysComb
|
|
|
|
|
| AlwaysFF
|
|
|
|
|
| AlwaysLatch
|
|
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
instance Show AlwaysKW where
|
|
|
|
|
show Always = "always"
|
|
|
|
|
show AlwaysComb = "always_comb"
|
|
|
|
|
show AlwaysFF = "always_ff"
|
|
|
|
|
show AlwaysLatch = "always_latch"
|
|
|
|
|
|
2019-02-08 05:49:12 +01:00
|
|
|
type PortBinding = (Identifier, Maybe Expr)
|
2019-03-04 08:58:00 +01:00
|
|
|
type ModportDecl = (Direction, Identifier, Maybe Expr)
|
2019-02-08 05:49:12 +01:00
|
|
|
|
|
|
|
|
instance Show ModuleItem where
|
2019-02-09 23:35:31 +01:00
|
|
|
show thing = case thing of
|
2019-02-24 09:06:40 +01:00
|
|
|
MIDecl nest -> show nest
|
2019-02-18 06:26:43 +01:00
|
|
|
AlwaysC k b -> printf "%s %s" (show k) (show b)
|
2019-02-08 05:49:12 +01:00
|
|
|
Assign a b -> printf "assign %s = %s;" (show a) (show b)
|
|
|
|
|
Instance m params i ports
|
2019-02-20 21:22:26 +01:00
|
|
|
| null params -> printf "%s %s%s;" m i (showMaybePorts ports)
|
|
|
|
|
| otherwise -> printf "%s #%s %s%s;" m (showPorts params) i (showMaybePorts ports)
|
2019-02-18 00:33:20 +01:00
|
|
|
Genvar x -> printf "genvar %s;" x
|
|
|
|
|
Generate b -> printf "generate\n%s\nendgenerate" (indent $ unlines' $ map show b)
|
2019-03-05 02:58:09 +01:00
|
|
|
Modport x l -> printf "modport %s(\n%s\n);" x (indent $ intercalate ",\n" $ map showModportDecl l)
|
|
|
|
|
Initial s -> printf "initial %s" (show s)
|
2019-03-07 19:19:31 +01:00
|
|
|
MIPackageItem i -> show i
|
2019-02-08 05:49:12 +01:00
|
|
|
where
|
2019-02-24 09:06:40 +01:00
|
|
|
showMaybePorts = maybe "(.*)" showPorts
|
|
|
|
|
showPorts :: [PortBinding] -> String
|
|
|
|
|
showPorts ports = indentedParenList $ map showPort ports
|
|
|
|
|
showPort :: PortBinding -> String
|
|
|
|
|
showPort (i, arg) =
|
|
|
|
|
if i == ""
|
|
|
|
|
then show (fromJust arg)
|
|
|
|
|
else printf ".%s(%s)" i (if isJust arg then show $ fromJust arg else "")
|
2019-03-04 08:58:00 +01:00
|
|
|
showModportDecl :: ModportDecl -> String
|
|
|
|
|
showModportDecl (dir, ident, me) =
|
|
|
|
|
if me == Just (Ident ident)
|
|
|
|
|
then printf "%s %s" (show dir) ident
|
|
|
|
|
else printf "%s .%s(%s)" (show dir) ident (maybe "" show me)
|
2019-02-11 20:46:09 +01:00
|
|
|
|
|
|
|
|
showAssignment :: Maybe Expr -> String
|
|
|
|
|
showAssignment Nothing = ""
|
|
|
|
|
showAssignment (Just val) = " = " ++ show val
|
|
|
|
|
|
|
|
|
|
showRanges :: [Range] -> String
|
2019-02-22 19:55:48 +01:00
|
|
|
showRanges [] = ""
|
|
|
|
|
showRanges l = " " ++ (concat $ map rangeToString l)
|
|
|
|
|
where rangeToString d = init $ showRange $ Just d
|
2019-02-11 20:46:09 +01:00
|
|
|
|
2019-02-08 05:49:12 +01:00
|
|
|
showRange :: Maybe Range -> String
|
|
|
|
|
showRange Nothing = ""
|
2019-02-17 20:54:12 +01:00
|
|
|
showRange (Just (h, l)) = printf "[%s:%s] " (show h) (show l)
|
2019-02-08 05:49:12 +01:00
|
|
|
|
2019-02-24 09:06:40 +01:00
|
|
|
showPad :: Show t => t -> String
|
|
|
|
|
showPad x =
|
|
|
|
|
if str == ""
|
|
|
|
|
then ""
|
|
|
|
|
else str ++ " "
|
|
|
|
|
where str = show x
|
|
|
|
|
|
2019-02-08 05:49:12 +01:00
|
|
|
indent :: String -> String
|
|
|
|
|
indent a = '\t' : f a
|
|
|
|
|
where
|
|
|
|
|
f [] = []
|
2019-02-09 23:35:31 +01:00
|
|
|
f (x : xs)
|
|
|
|
|
| x == '\n' = "\n\t" ++ f xs
|
|
|
|
|
| otherwise = x : f xs
|
2019-02-08 05:49:12 +01:00
|
|
|
|
|
|
|
|
unlines' :: [String] -> String
|
|
|
|
|
unlines' = intercalate "\n"
|
|
|
|
|
|
|
|
|
|
data Expr
|
|
|
|
|
= String String
|
2019-02-17 20:54:12 +01:00
|
|
|
| Number String
|
2019-02-08 05:49:12 +01:00
|
|
|
| ConstBool Bool
|
|
|
|
|
| Ident Identifier
|
2019-03-04 21:46:12 +01:00
|
|
|
| Range Expr Range
|
|
|
|
|
| Bit Expr Expr
|
2019-02-08 05:49:12 +01:00
|
|
|
| Repeat Expr [Expr]
|
|
|
|
|
| Concat [Expr]
|
2019-02-18 03:17:00 +01:00
|
|
|
| Call Identifier [Expr]
|
2019-02-08 05:49:12 +01:00
|
|
|
| UniOp UniOp Expr
|
|
|
|
|
| BinOp BinOp Expr Expr
|
|
|
|
|
| Mux Expr Expr Expr
|
2019-02-24 03:24:13 +01:00
|
|
|
| Cast Type Expr
|
2019-03-04 21:46:12 +01:00
|
|
|
| Access Expr Identifier
|
|
|
|
|
| Pattern [(Maybe Identifier, Expr)]
|
2019-03-01 04:44:31 +01:00
|
|
|
deriving (Eq, Ord)
|
2019-02-08 05:49:12 +01:00
|
|
|
|
2019-02-10 23:46:18 +01:00
|
|
|
data UniOp
|
|
|
|
|
= Not
|
|
|
|
|
| BWNot
|
|
|
|
|
| UAdd
|
|
|
|
|
| USub
|
|
|
|
|
| RedAnd
|
|
|
|
|
| RedNand
|
|
|
|
|
| RedOr
|
|
|
|
|
| RedNor
|
|
|
|
|
| RedXor
|
|
|
|
|
| RedXnor
|
2019-03-01 04:44:31 +01:00
|
|
|
deriving (Eq, Ord)
|
2019-02-08 05:49:12 +01:00
|
|
|
|
|
|
|
|
instance Show UniOp where
|
2019-02-10 23:46:18 +01:00
|
|
|
show Not = "!"
|
|
|
|
|
show BWNot = "~"
|
|
|
|
|
show UAdd = "+"
|
|
|
|
|
show USub = "-"
|
|
|
|
|
show RedAnd = "&"
|
|
|
|
|
show RedNand = "~&"
|
|
|
|
|
show RedOr = "|"
|
|
|
|
|
show RedNor = "~|"
|
|
|
|
|
show RedXor = "^"
|
|
|
|
|
show RedXnor = "~^"
|
2019-02-08 05:49:12 +01:00
|
|
|
|
|
|
|
|
data BinOp
|
2019-02-08 05:58:34 +01:00
|
|
|
= And
|
|
|
|
|
| Or
|
|
|
|
|
| BWAnd
|
|
|
|
|
| BWXor
|
|
|
|
|
| BWOr
|
|
|
|
|
| Mul
|
|
|
|
|
| Div
|
|
|
|
|
| Mod
|
|
|
|
|
| Add
|
|
|
|
|
| Sub
|
2019-02-08 05:49:12 +01:00
|
|
|
| ShiftL
|
|
|
|
|
| ShiftR
|
2019-02-08 05:58:34 +01:00
|
|
|
| Eq
|
|
|
|
|
| Ne
|
|
|
|
|
| Lt
|
|
|
|
|
| Le
|
|
|
|
|
| Gt
|
|
|
|
|
| Ge
|
2019-03-05 00:25:14 +01:00
|
|
|
| Pow
|
2019-02-18 02:52:01 +01:00
|
|
|
| ShiftAL
|
|
|
|
|
| ShiftAR
|
2019-03-05 00:25:14 +01:00
|
|
|
| TEq
|
|
|
|
|
| TNe
|
|
|
|
|
| WEq
|
|
|
|
|
| WNe
|
2019-03-01 04:44:31 +01:00
|
|
|
deriving (Eq, Ord)
|
2019-02-08 05:49:12 +01:00
|
|
|
|
|
|
|
|
instance Show BinOp where
|
|
|
|
|
show a = case a of
|
|
|
|
|
And -> "&&"
|
|
|
|
|
Or -> "||"
|
|
|
|
|
BWAnd -> "&"
|
|
|
|
|
BWXor -> "^"
|
|
|
|
|
BWOr -> "|"
|
|
|
|
|
Mul -> "*"
|
|
|
|
|
Div -> "/"
|
|
|
|
|
Mod -> "%"
|
|
|
|
|
Add -> "+"
|
|
|
|
|
Sub -> "-"
|
|
|
|
|
ShiftL -> "<<"
|
|
|
|
|
ShiftR -> ">>"
|
|
|
|
|
Eq -> "=="
|
|
|
|
|
Ne -> "!="
|
|
|
|
|
Lt -> "<"
|
|
|
|
|
Le -> "<="
|
|
|
|
|
Gt -> ">"
|
|
|
|
|
Ge -> ">="
|
2019-03-05 00:25:14 +01:00
|
|
|
Pow -> "**"
|
2019-02-18 02:52:01 +01:00
|
|
|
ShiftAL -> "<<<"
|
|
|
|
|
ShiftAR -> ">>>"
|
2019-03-05 00:25:14 +01:00
|
|
|
TEq -> "==="
|
|
|
|
|
TNe -> "!=="
|
|
|
|
|
WEq -> "==?"
|
|
|
|
|
WNe -> "!=?"
|
2019-02-08 05:49:12 +01:00
|
|
|
|
2019-02-17 20:54:12 +01:00
|
|
|
instance Show Expr where
|
|
|
|
|
show x = case x of
|
|
|
|
|
String a -> printf "\"%s\"" a
|
|
|
|
|
Number a -> a
|
|
|
|
|
ConstBool a -> printf "1'b%s" (if a then "1" else "0")
|
|
|
|
|
Ident a -> a
|
2019-03-04 21:46:12 +01:00
|
|
|
Bit a b -> printf "%s[%s]" (show a) (show b)
|
|
|
|
|
Range a (b, c) -> printf "%s[%s:%s]" (show a) (show b) (show c)
|
2019-02-17 20:54:12 +01:00
|
|
|
Repeat a b -> printf "{%s {%s}}" (show a) (commas $ map show b)
|
|
|
|
|
Concat a -> printf "{%s}" (commas $ map show a)
|
2019-02-18 03:17:00 +01:00
|
|
|
Call a b -> printf "%s(%s)" a (commas $ map show b)
|
2019-02-17 20:54:12 +01:00
|
|
|
UniOp a b -> printf "(%s %s)" (show a) (show b)
|
|
|
|
|
BinOp a b c -> printf "(%s %s %s)" (show b) (show a) (show c)
|
|
|
|
|
Mux a b c -> printf "(%s ? %s : %s)" (show a) (show b) (show c)
|
2019-02-24 03:24:13 +01:00
|
|
|
Cast a b -> printf "%s'(%s)" (show a) (show b)
|
2019-03-04 21:46:12 +01:00
|
|
|
Access e n -> printf "%s.%s" (show e) n
|
|
|
|
|
Pattern l -> printf "'{\n%s\n}" (showPatternItems l)
|
2019-03-02 02:26:44 +01:00
|
|
|
where
|
|
|
|
|
showPatternItems :: [(Maybe Identifier, Expr)] -> String
|
|
|
|
|
showPatternItems l = indent $ intercalate ",\n" (map showPatternItem l)
|
|
|
|
|
showPatternItem :: (Maybe Identifier, Expr) -> String
|
|
|
|
|
showPatternItem (Nothing, e) = show e
|
|
|
|
|
showPatternItem (Just n , e) = printf "%s: %s" n (show e)
|
2019-02-08 05:49:12 +01:00
|
|
|
|
2019-03-05 00:25:14 +01:00
|
|
|
data AsgnOp
|
|
|
|
|
= AsgnOpEq
|
|
|
|
|
| AsgnOp BinOp
|
|
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
instance Show AsgnOp where
|
|
|
|
|
show AsgnOpEq = "="
|
|
|
|
|
show (AsgnOp op) = (show op) ++ "="
|
|
|
|
|
|
2019-02-08 05:49:12 +01:00
|
|
|
data LHS
|
2019-03-04 21:16:53 +01:00
|
|
|
= LHSIdent Identifier
|
|
|
|
|
| LHSBit LHS Expr
|
|
|
|
|
| LHSRange LHS Range
|
2019-03-04 08:58:00 +01:00
|
|
|
| LHSDot LHS Identifier
|
2019-02-08 05:49:12 +01:00
|
|
|
| LHSConcat [LHS]
|
|
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
instance Show LHS where
|
2019-03-04 21:16:53 +01:00
|
|
|
show (LHSIdent x ) = x
|
|
|
|
|
show (LHSBit l e ) = printf "%s[%s]" (show l) (show e)
|
|
|
|
|
show (LHSRange l (a, b)) = printf "%s[%s:%s]" (show l) (show a) (show b)
|
|
|
|
|
show (LHSDot l x ) = printf "%s.%s" (show l) x
|
|
|
|
|
show (LHSConcat lhss ) = printf "{%s}" (commas $ map show lhss)
|
2019-02-08 05:49:12 +01:00
|
|
|
|
2019-02-23 21:10:25 +01:00
|
|
|
data CaseKW
|
|
|
|
|
= CaseN
|
|
|
|
|
| CaseZ
|
|
|
|
|
| CaseX
|
|
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
instance Show CaseKW where
|
|
|
|
|
show CaseN = "case"
|
|
|
|
|
show CaseZ = "casez"
|
|
|
|
|
show CaseX = "casex"
|
|
|
|
|
|
2019-02-08 05:49:12 +01:00
|
|
|
data Stmt
|
2019-03-07 21:39:19 +01:00
|
|
|
= Block (Maybe Identifier) [Decl] [Stmt]
|
2019-03-05 00:25:14 +01:00
|
|
|
| Case Bool CaseKW Expr [Case] (Maybe Stmt)
|
2019-02-24 09:06:40 +01:00
|
|
|
| For (Identifier, Expr) Expr (Identifier, Expr) Stmt
|
|
|
|
|
| AsgnBlk LHS Expr
|
|
|
|
|
| Asgn LHS Expr
|
2019-03-05 03:32:30 +01:00
|
|
|
| While Expr Stmt
|
|
|
|
|
| RepeatL Expr Stmt
|
|
|
|
|
| DoWhile Expr Stmt
|
|
|
|
|
| Forever Stmt
|
2019-02-24 09:06:40 +01:00
|
|
|
| If Expr Stmt Stmt
|
2019-03-05 02:58:09 +01:00
|
|
|
| Timing Timing Stmt
|
2019-03-04 20:25:38 +01:00
|
|
|
| Return Expr
|
2019-03-05 02:58:09 +01:00
|
|
|
| Subroutine Identifier [Expr]
|
2019-02-08 05:49:12 +01:00
|
|
|
| Null
|
|
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
commas :: [String] -> String
|
|
|
|
|
commas = intercalate ", "
|
|
|
|
|
|
|
|
|
|
instance Show Stmt where
|
2019-03-07 21:39:19 +01:00
|
|
|
show (Block name decls stmts) =
|
|
|
|
|
printf "begin%s\n%s\n%s\nend" header (block decls) (block stmts)
|
2019-02-24 09:06:40 +01:00
|
|
|
where
|
2019-03-07 21:39:19 +01:00
|
|
|
header = maybe "" (" : " ++) name
|
2019-02-24 09:06:40 +01:00
|
|
|
block :: Show t => [t] -> String
|
|
|
|
|
block = indent . unlines' . map show
|
2019-03-05 00:25:14 +01:00
|
|
|
show (Case u kw e cs def) =
|
|
|
|
|
printf "%s%s (%s)\n%s%s\nendcase" uniqStr (show kw) (show e) (indent $ unlines' $ map showCase cs) defStr
|
2019-02-24 09:06:40 +01:00
|
|
|
where
|
2019-03-05 00:25:14 +01:00
|
|
|
uniqStr = if u then "unique " else ""
|
|
|
|
|
defStr = case def of
|
|
|
|
|
Nothing -> ""
|
|
|
|
|
Just c -> printf "\n\tdefault: %s" (show c)
|
2019-02-24 09:06:40 +01:00
|
|
|
show (For (a,b) c (d,e) f) = printf "for (%s = %s; %s; %s = %s)\n%s" a (show b) (show c) d (show e) $ indent $ show f
|
|
|
|
|
show (AsgnBlk v e) = printf "%s = %s;" (show v) (show e)
|
|
|
|
|
show (Asgn v e) = printf "%s <= %s;" (show v) (show e)
|
2019-03-05 03:32:30 +01:00
|
|
|
show (While e s) = printf "while (%s) %s" (show e) (show s)
|
|
|
|
|
show (RepeatL e s) = printf "repeat (%s) %s" (show e) (show s)
|
|
|
|
|
show (DoWhile e s) = printf "do %s while (%s);" (show s) (show e)
|
|
|
|
|
show (Forever s ) = printf "forever %s" (show s)
|
2019-03-04 08:58:00 +01:00
|
|
|
show (If a b Null) = printf "if (%s) %s" (show a) (show b)
|
2019-02-24 09:19:02 +01:00
|
|
|
show (If a b c ) = printf "if (%s) %s\nelse %s" (show a) (show b) (show c)
|
2019-03-04 20:25:38 +01:00
|
|
|
show (Return e ) = printf "return %s;" (show e)
|
2019-03-05 02:58:09 +01:00
|
|
|
show (Subroutine x a) = printf "%s(%s);" x (commas $ map show a)
|
|
|
|
|
show (Timing t s ) = printf "%s%s" (show t) rest
|
2019-02-24 09:19:02 +01:00
|
|
|
where
|
|
|
|
|
rest = case s of
|
2019-03-05 02:58:09 +01:00
|
|
|
Null -> ";"
|
2019-03-07 21:39:19 +01:00
|
|
|
Block _ _ _ -> " " ++ (show s)
|
2019-02-24 09:19:02 +01:00
|
|
|
_ -> "\n" ++ (indent $ show s)
|
2019-02-24 09:06:40 +01:00
|
|
|
show (Null ) = ";"
|
2019-02-15 05:29:42 +01:00
|
|
|
|
2019-02-08 05:49:12 +01:00
|
|
|
type Case = ([Expr], Stmt)
|
|
|
|
|
|
2019-02-18 00:33:20 +01:00
|
|
|
showCase :: (Show x, Show y) => ([x], y) -> String
|
2019-02-24 09:19:02 +01:00
|
|
|
showCase (a, b) = printf "%s: %s" (commas $ map show a) (show b)
|
2019-02-08 05:49:12 +01:00
|
|
|
|
2019-03-05 02:58:09 +01:00
|
|
|
data Timing
|
|
|
|
|
= Event Sense
|
|
|
|
|
| Delay Expr
|
|
|
|
|
| Cycle Expr
|
|
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
instance Show Timing where
|
|
|
|
|
show (Event s) = printf "@(%s)" (show s)
|
|
|
|
|
show (Delay e) = printf "#(%s)" (show e)
|
|
|
|
|
show (Cycle e) = printf "##(%s)" (show e)
|
|
|
|
|
|
2019-02-08 05:49:12 +01:00
|
|
|
data Sense
|
|
|
|
|
= Sense LHS
|
|
|
|
|
| SenseOr Sense Sense
|
|
|
|
|
| SensePosedge LHS
|
|
|
|
|
| SenseNegedge LHS
|
2019-02-10 23:46:18 +01:00
|
|
|
| SenseStar
|
2019-02-08 05:49:12 +01:00
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
instance Show Sense where
|
2019-02-09 23:35:31 +01:00
|
|
|
show (Sense a ) = show a
|
|
|
|
|
show (SenseOr a b) = printf "%s or %s" (show a) (show b)
|
|
|
|
|
show (SensePosedge a ) = printf "posedge %s" (show a)
|
|
|
|
|
show (SenseNegedge a ) = printf "negedge %s" (show a)
|
2019-02-10 23:46:18 +01:00
|
|
|
show (SenseStar ) = "*"
|
2019-02-08 05:49:12 +01:00
|
|
|
|
|
|
|
|
type Range = (Expr, Expr)
|
|
|
|
|
|
2019-02-10 23:59:41 +01:00
|
|
|
indentedParenList :: [String] -> String
|
|
|
|
|
indentedParenList [] = "()"
|
|
|
|
|
indentedParenList [x] = "(" ++ x ++ ")"
|
|
|
|
|
indentedParenList l =
|
|
|
|
|
"(\n" ++ (indent $ intercalate ",\n" l) ++ "\n)"
|
2019-02-18 00:33:20 +01:00
|
|
|
|
|
|
|
|
type GenCase = ([Expr], GenItem)
|
|
|
|
|
|
|
|
|
|
data GenItem
|
|
|
|
|
= GenBlock (Maybe Identifier) [GenItem]
|
|
|
|
|
| GenCase Expr [GenCase] (Maybe GenItem)
|
2019-03-05 00:25:14 +01:00
|
|
|
| GenFor (Identifier, Expr) Expr (Identifier, AsgnOp, Expr) Identifier [GenItem]
|
2019-02-18 00:33:20 +01:00
|
|
|
| GenIf Expr GenItem GenItem
|
|
|
|
|
| GenNull
|
|
|
|
|
| GenModuleItem ModuleItem
|
|
|
|
|
deriving Eq
|
|
|
|
|
|
|
|
|
|
instance Show GenItem where
|
|
|
|
|
showList i _ = unlines' $ map show i
|
2019-02-24 09:06:40 +01:00
|
|
|
show (GenBlock Nothing i) = printf "begin\n%s\nend" (indent $ unlines' $ map show i)
|
2019-02-18 00:33:20 +01:00
|
|
|
show (GenBlock (Just x) i) = printf "begin : %s\n%s\nend" x (indent $ unlines' $ map show i)
|
|
|
|
|
show (GenCase e c Nothing ) = printf "case (%s)\n%s\nendcase" (show e) (indent $ unlines' $ map showCase c)
|
|
|
|
|
show (GenCase e c (Just d)) = printf "case (%s)\n%s\n\tdefault:\n%s\nendcase" (show e) (indent $ unlines' $ map showCase c) (indent $ indent $ show d)
|
2019-02-24 09:19:02 +01:00
|
|
|
show (GenIf e a GenNull) = printf "if (%s) %s" (show e) (show a)
|
|
|
|
|
show (GenIf e a b ) = printf "if (%s) %s\nelse %s" (show e) (show a) (show b)
|
2019-03-05 00:25:14 +01:00
|
|
|
show (GenFor (x1, e1) c (x2, o2, e2) x is) = printf "for (%s = %s; %s; %s %s %s) %s" x1 (show e1) (show c) x2 (show o2) (show e2) (show $ GenBlock (Just x) is)
|
2019-02-18 00:33:20 +01:00
|
|
|
show GenNull = ";"
|
|
|
|
|
show (GenModuleItem item) = show item
|
2019-03-04 20:25:38 +01:00
|
|
|
|
|
|
|
|
data Lifetime
|
|
|
|
|
= Static
|
|
|
|
|
| Automatic
|
|
|
|
|
deriving (Eq, Ord)
|
|
|
|
|
|
|
|
|
|
instance Show Lifetime where
|
|
|
|
|
show Static = "static"
|
|
|
|
|
show Automatic = "automatic"
|
|
|
|
|
|
|
|
|
|
showLifetime :: Maybe Lifetime -> String
|
|
|
|
|
showLifetime Nothing = ""
|
|
|
|
|
showLifetime (Just l) = show l ++ " "
|
2019-03-06 06:51:09 +01:00
|
|
|
|
|
|
|
|
-- basic expression simplfication utility to help us generate nicer code in the
|
|
|
|
|
-- common case of ranges like `[FOO-1:0]`
|
|
|
|
|
simplify :: Expr -> Expr
|
|
|
|
|
simplify (BinOp op e1 e2) =
|
|
|
|
|
case (op, e1', e2') of
|
|
|
|
|
(Add, Number "0", e) -> e
|
|
|
|
|
(Add, e, Number "0") -> e
|
|
|
|
|
(Sub, e, Number "0") -> e
|
|
|
|
|
(Add, BinOp Sub e (Number "1"), Number "1") -> e
|
|
|
|
|
(Add, e, BinOp Sub (Number "0") (Number "1")) -> BinOp Sub e (Number "1")
|
|
|
|
|
(_ , Number a, Number b) ->
|
|
|
|
|
case (op, readMaybe a :: Maybe Int, readMaybe b :: Maybe Int) of
|
|
|
|
|
(Add, Just x, Just y) -> Number $ show (x + y)
|
|
|
|
|
(Sub, Just x, Just y) -> Number $ show (x - y)
|
|
|
|
|
(Mul, Just x, Just y) -> Number $ show (x * y)
|
|
|
|
|
_ -> BinOp op e1' e2'
|
|
|
|
|
_ -> BinOp op e1' e2'
|
|
|
|
|
where
|
|
|
|
|
e1' = simplify e1
|
|
|
|
|
e2' = simplify e2
|
|
|
|
|
simplify other = other
|
|
|
|
|
|
|
|
|
|
rangeSize :: Range -> Expr
|
|
|
|
|
rangeSize (s, e) =
|
|
|
|
|
simplify $ BinOp Add (BinOp Sub s e) (Number "1")
|