netlist-0.2: Netlist AST

Portabilitynon-portable (DeriveDataTypeable)
Stabilityexperimental
Maintainerpweaver@signalicorp.com

Language.Netlist.AST

Description

An abstract syntax tree (AST) for a generic netlist, kind of like a high-level subset of Verilog and VHDL that is compatible with both languages.

There are no definitive semantics assigned to this AST.

For example, the user may choose to treat the bindings as recursive, so that expressions can reference variables before their declaration, like in Haskell, which is not supported in Verilog and VHDL. in this case, the user must fix the bindings when converting to an HDL.

Also, the user may treat module instantiations and processes as having an implict clock/reset, so that they are not explicitly named in those constructs in this AST. Then, the clock and reset can be inserted when generating HDL.

When you instantiate a module but information about that module is missing (e.g. the clock/reset are implicit and you need to know what they are called in that module), you can use ExternDecl (TODO) to declare a module's interface so that you know how to instantiate it, or retrieve the interface from a user-maintained database or by parsing and extracting from an HDL file.

Synopsis

Documentation

data Module Source

A Module corresponds to a "module" in Verilog or an "entity" in VHDL.

type Ident = StringSource

An identifier name.

type Size = IntSource

The size of a wire.

data Decl Source

A declaration, analogous to an "item" in the Verilog formal syntax.

Constructors

NetDecl Ident (Maybe Range) (Maybe Expr)

A net (wire in Verilog) has a continuously assigned value. The net can be declared and assigned at the same time (Just Expr), or separately (Nothing) in a NetAssign.

NetAssign Ident Expr 
MemDecl Ident (Maybe Range) (Maybe Range)

A mem (reg in Verilog) is stateful. It can be assigned by a non-blocking assignment (or blocking, but we don't support those yet) within a process. TODO: support optional initial value

The first range is the most significant dimension. So, MemDecl x (0, 31) (7, 0) corresponds to the following in Verilog: reg [7:0] x [0:31]

InstDecl Ident Ident [(Ident, Expr)] [(Ident, Expr)] [(Ident, Expr)]

A module/entity instantiation. The arguments are the name of the module, the name of the instance, the parameter assignments, the input port connections, and the output port connections.

ProcessDecl [(Event, Stmt)]

A general process construct, compatible with both VHDL and Verilog processes. It supports positive and negative edge triggers and a body (a statement) for each trigger. Here are loose semantics of a process [(trigger0, stmt0), (trigger1, stmt1)...]:

 if trigger0
    statement0
 else if
    trigger1
 ...
InitProcessDecl Stmt

A statement that executes once at the beginning of simulation. Equivalent to Verilog "initial" statement.

CommentDecl String

A basic comment (typically is placed above a decl of interest). Newlines are allowed, and generate new single line comments.

data Range Source

A Range tells us the type of a bit vector. It can count up or down.

Constructors

Range ConstExpr ConstExpr 

type ConstExpr = ExprSource

A constant expression is simply an expression that must be a constant (i.e. the only free variables are static parameters). This restriction is not made in the AST.

data Edge Source

An event can be triggered by the rising edge (PosEdge) or falling edge (NegEdge) of a signal.

data Expr Source

Expr is a combination of VHDL and Verilog expressions.

In VHDL, concatenation is a binary operator, but in Verilog it takes any number of arguments. In this AST, we define it like the Verilog operator. If we translate to VHDL, we have to convert it to the VHDL binary operator.

There are some HDL operators that we don't represent here. For example, in Verilog there is a multiple concatenation (a.k.a. replication) operator, which we don't bother to support.

Constructors

ExprLit (Maybe Size) ExprLit

a sized or unsized literal

ExprVar Ident

a variable ference

ExprString String

a quoted string (useful for parameters)

ExprIndex Ident Expr
x[e]
ExprSlice Ident Expr Expr
x[e1 : e2]
ExprSliceOff Ident Expr Int

x[e : e+i], where i can be negative

ExprCase Expr [([ConstExpr], Expr)] (Maybe Expr)

case expression. supports multiple matches per result value, and an optional default value

ExprConcat [Expr]

concatenation

ExprCond Expr Expr Expr

conditional expression

ExprUnary UnaryOp Expr

application of a unary operator

ExprBinary BinaryOp Expr Expr

application of a binary operator

ExprFunCall Ident [Expr]

a function application

data ExprLit Source

Constructors

ExprNum Integer

a number

ExprBit Bit

a single bit. in vhdl, bits are different than 1-bit bitvectors

ExprBitVector [Bit] 

data Bit Source

Constructors

T 
F 
U 
Z 

data Stmt Source

Behavioral sequential statement

Constructors

Assign LValue Expr

non-blocking assignment

If Expr Stmt (Maybe Stmt)

if statement

Case Expr [([Expr], Stmt)] (Maybe Stmt)

case statement, with optional default case

Seq [Stmt]

multiple statements in sequence

FunCallStmt Ident [Expr]

a function call that can appear as a statement, useful for calling Verilog tasks (e.g. $readmem).

type LValue = ExprSource

An LValue is something that can appear on the left-hand side of an assignment. We're lazy and do not enforce any restriction, and define this simply to be Expr.

data UnaryOp Source

Unary operators

LNeg is logical negation, Neg is bitwise negation. UAnd, UNand, UOr, UNor, UXor, and UXnor are sometimes called "reduction operators".

Constructors

UPlus 
UMinus 
LNeg 
Neg 
UAnd 
UNand 
UOr 
UNor 
UXor 
UXnor 

data BinaryOp Source

Binary operators.

These operators include almost all VHDL and Verilog operators.

  • precedence and pretty-printing are language specific, and defined elsewhere.
  • exponentation operators were introduced in Verilog-2001.
  • some operators are not prefix/infix, such as verilog concatenation and the conditional (x ? y : z) operator. those operators are defined in Expr.
  • VHDL has both "logical" and "barithmetic" shift operators, which we don't yet distinguish between here.
  • VHDL has both a mod and a rem operator, but so far we only define Modulo.
  • VHDL has a concat operator (&) that isn't yet supported here. Use ExprConcat instead.
  • VHDL has an abs operator that isn't yet supported here.