netlist-0.3.1: Netlist AST
Copyright(c) Signali Corp. 2010
LicenseAll rights reserved
Maintainerpweaver@signalicorp.com
Stabilityexperimental
Portabilitynon-portable (DeriveDataTypeable)
Safe HaskellNone
LanguageHaskell98

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.

Constructors

Module 

Instances

Instances details
Eq Module Source # 
Instance details

Defined in Language.Netlist.AST

Methods

(==) :: Module -> Module -> Bool

(/=) :: Module -> Module -> Bool

Data Module Source # 
Instance details

Defined in Language.Netlist.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module

toConstr :: Module -> Constr

dataTypeOf :: Module -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Module)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module)

gmapT :: (forall b. Data b => b -> b) -> Module -> Module

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r

gmapQ :: (forall d. Data d => d -> u) -> Module -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module

Ord Module Source # 
Instance details

Defined in Language.Netlist.AST

Methods

compare :: Module -> Module -> Ordering

(<) :: Module -> Module -> Bool

(<=) :: Module -> Module -> Bool

(>) :: Module -> Module -> Bool

(>=) :: Module -> Module -> Bool

max :: Module -> Module -> Module

min :: Module -> Module -> Module

Show Module Source # 
Instance details

Defined in Language.Netlist.AST

Methods

showsPrec :: Int -> Module -> ShowS

show :: Module -> String

showList :: [Module] -> ShowS

Binary Module Source # 
Instance details

Defined in Language.Netlist.AST

Methods

put :: Module -> Put

get :: Get Module

putList :: [Module] -> Put

type Ident = String Source #

An identifier name.

type Size = Int Source #

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) (Maybe [Expr])

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]

MemAssign Ident Expr Expr

These are permanent assignments to memory locations, of the form mem[addr] = val

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 (Maybe (Event, Stmt)) Stmt

A sequential process with clock and (optional) asynchronous reset.

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.

Instances

Instances details
Eq Decl Source # 
Instance details

Defined in Language.Netlist.AST

Methods

(==) :: Decl -> Decl -> Bool

(/=) :: Decl -> Decl -> Bool

Data Decl Source # 
Instance details

Defined in Language.Netlist.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Decl -> c Decl

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Decl

toConstr :: Decl -> Constr

dataTypeOf :: Decl -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Decl)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Decl)

gmapT :: (forall b. Data b => b -> b) -> Decl -> Decl

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Decl -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Decl -> r

gmapQ :: (forall d. Data d => d -> u) -> Decl -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Decl -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Decl -> m Decl

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Decl -> m Decl

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Decl -> m Decl

Ord Decl Source # 
Instance details

Defined in Language.Netlist.AST

Methods

compare :: Decl -> Decl -> Ordering

(<) :: Decl -> Decl -> Bool

(<=) :: Decl -> Decl -> Bool

(>) :: Decl -> Decl -> Bool

(>=) :: Decl -> Decl -> Bool

max :: Decl -> Decl -> Decl

min :: Decl -> Decl -> Decl

Show Decl Source # 
Instance details

Defined in Language.Netlist.AST

Methods

showsPrec :: Int -> Decl -> ShowS

show :: Decl -> String

showList :: [Decl] -> ShowS

Binary Decl Source # 
Instance details

Defined in Language.Netlist.AST

Methods

put :: Decl -> Put

get :: Get Decl

putList :: [Decl] -> Put

data Range Source #

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

Constructors

Range ConstExpr ConstExpr 

Instances

Instances details
Eq Range Source # 
Instance details

Defined in Language.Netlist.AST

Methods

(==) :: Range -> Range -> Bool

(/=) :: Range -> Range -> Bool

Data Range Source # 
Instance details

Defined in Language.Netlist.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Range -> c Range

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Range

toConstr :: Range -> Constr

dataTypeOf :: Range -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Range)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Range)

gmapT :: (forall b. Data b => b -> b) -> Range -> Range

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Range -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Range -> r

gmapQ :: (forall d. Data d => d -> u) -> Range -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Range -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Range -> m Range

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Range -> m Range

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Range -> m Range

Ord Range Source # 
Instance details

Defined in Language.Netlist.AST

Methods

compare :: Range -> Range -> Ordering

(<) :: Range -> Range -> Bool

(<=) :: Range -> Range -> Bool

(>) :: Range -> Range -> Bool

(>=) :: Range -> Range -> Bool

max :: Range -> Range -> Range

min :: Range -> Range -> Range

Show Range Source # 
Instance details

Defined in Language.Netlist.AST

Methods

showsPrec :: Int -> Range -> ShowS

show :: Range -> String

showList :: [Range] -> ShowS

Binary Range Source # 
Instance details

Defined in Language.Netlist.AST

Methods

put :: Range -> Put

get :: Get Range

putList :: [Range] -> Put

type ConstExpr = Expr Source #

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 Event Source #

Constructors

Event Expr Edge 

Instances

Instances details
Eq Event Source # 
Instance details

Defined in Language.Netlist.AST

Methods

(==) :: Event -> Event -> Bool

(/=) :: Event -> Event -> Bool

Data Event Source # 
Instance details

Defined in Language.Netlist.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Event -> c Event

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Event

toConstr :: Event -> Constr

dataTypeOf :: Event -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Event)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Event)

gmapT :: (forall b. Data b => b -> b) -> Event -> Event

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r

gmapQ :: (forall d. Data d => d -> u) -> Event -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Event -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Event -> m Event

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event

Ord Event Source # 
Instance details

Defined in Language.Netlist.AST

Methods

compare :: Event -> Event -> Ordering

(<) :: Event -> Event -> Bool

(<=) :: Event -> Event -> Bool

(>) :: Event -> Event -> Bool

(>=) :: Event -> Event -> Bool

max :: Event -> Event -> Event

min :: Event -> Event -> Event

Show Event Source # 
Instance details

Defined in Language.Netlist.AST

Methods

showsPrec :: Int -> Event -> ShowS

show :: Event -> String

showList :: [Event] -> ShowS

Binary Event Source # 
Instance details

Defined in Language.Netlist.AST

Methods

put :: Event -> Put

get :: Get Event

putList :: [Event] -> Put

data Edge Source #

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

Constructors

PosEdge 
NegEdge 

Instances

Instances details
Eq Edge Source # 
Instance details

Defined in Language.Netlist.AST

Methods

(==) :: Edge -> Edge -> Bool

(/=) :: Edge -> Edge -> Bool

Data Edge Source # 
Instance details

Defined in Language.Netlist.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Edge -> c Edge

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Edge

toConstr :: Edge -> Constr

dataTypeOf :: Edge -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Edge)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Edge)

gmapT :: (forall b. Data b => b -> b) -> Edge -> Edge

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Edge -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Edge -> r

gmapQ :: (forall d. Data d => d -> u) -> Edge -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Edge -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Edge -> m Edge

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Edge -> m Edge

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Edge -> m Edge

Ord Edge Source # 
Instance details

Defined in Language.Netlist.AST

Methods

compare :: Edge -> Edge -> Ordering

(<) :: Edge -> Edge -> Bool

(<=) :: Edge -> Edge -> Bool

(>) :: Edge -> Edge -> Bool

(>=) :: Edge -> Edge -> Bool

max :: Edge -> Edge -> Edge

min :: Edge -> Edge -> Edge

Show Edge Source # 
Instance details

Defined in Language.Netlist.AST

Methods

showsPrec :: Int -> Edge -> ShowS

show :: Edge -> String

showList :: [Edge] -> ShowS

Binary Edge Source # 
Instance details

Defined in Language.Netlist.AST

Methods

put :: Edge -> Put

get :: Get Edge

putList :: [Edge] -> Put

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

Instances

Instances details
Eq Expr Source # 
Instance details

Defined in Language.Netlist.AST

Methods

(==) :: Expr -> Expr -> Bool

(/=) :: Expr -> Expr -> Bool

Data Expr Source # 
Instance details

Defined in Language.Netlist.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expr -> c Expr

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Expr

toConstr :: Expr -> Constr

dataTypeOf :: Expr -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Expr)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Expr)

gmapT :: (forall b. Data b => b -> b) -> Expr -> Expr

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expr -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expr -> r

gmapQ :: (forall d. Data d => d -> u) -> Expr -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Expr -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expr -> m Expr

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr -> m Expr

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr -> m Expr

Ord Expr Source # 
Instance details

Defined in Language.Netlist.AST

Methods

compare :: Expr -> Expr -> Ordering

(<) :: Expr -> Expr -> Bool

(<=) :: Expr -> Expr -> Bool

(>) :: Expr -> Expr -> Bool

(>=) :: Expr -> Expr -> Bool

max :: Expr -> Expr -> Expr

min :: Expr -> Expr -> Expr

Show Expr Source # 
Instance details

Defined in Language.Netlist.AST

Methods

showsPrec :: Int -> Expr -> ShowS

show :: Expr -> String

showList :: [Expr] -> ShowS

Binary Expr Source # 
Instance details

Defined in Language.Netlist.AST

Methods

put :: Expr -> Put

get :: Get Expr

putList :: [Expr] -> Put

data ExprLit Source #

Constructors

ExprNum Integer

a number

ExprBit Bit

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

ExprBitVector [Bit] 

Instances

Instances details
Eq ExprLit Source # 
Instance details

Defined in Language.Netlist.AST

Methods

(==) :: ExprLit -> ExprLit -> Bool

(/=) :: ExprLit -> ExprLit -> Bool

Data ExprLit Source # 
Instance details

Defined in Language.Netlist.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExprLit -> c ExprLit

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExprLit

toConstr :: ExprLit -> Constr

dataTypeOf :: ExprLit -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExprLit)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExprLit)

gmapT :: (forall b. Data b => b -> b) -> ExprLit -> ExprLit

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExprLit -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExprLit -> r

gmapQ :: (forall d. Data d => d -> u) -> ExprLit -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExprLit -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExprLit -> m ExprLit

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExprLit -> m ExprLit

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExprLit -> m ExprLit

Ord ExprLit Source # 
Instance details

Defined in Language.Netlist.AST

Methods

compare :: ExprLit -> ExprLit -> Ordering

(<) :: ExprLit -> ExprLit -> Bool

(<=) :: ExprLit -> ExprLit -> Bool

(>) :: ExprLit -> ExprLit -> Bool

(>=) :: ExprLit -> ExprLit -> Bool

max :: ExprLit -> ExprLit -> ExprLit

min :: ExprLit -> ExprLit -> ExprLit

Show ExprLit Source # 
Instance details

Defined in Language.Netlist.AST

Methods

showsPrec :: Int -> ExprLit -> ShowS

show :: ExprLit -> String

showList :: [ExprLit] -> ShowS

Binary ExprLit Source # 
Instance details

Defined in Language.Netlist.AST

Methods

put :: ExprLit -> Put

get :: Get ExprLit

putList :: [ExprLit] -> Put

data Bit Source #

Constructors

T 
F 
U 
Z 

Instances

Instances details
Eq Bit Source # 
Instance details

Defined in Language.Netlist.AST

Methods

(==) :: Bit -> Bit -> Bool

(/=) :: Bit -> Bit -> Bool

Data Bit Source # 
Instance details

Defined in Language.Netlist.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bit -> c Bit

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bit

toConstr :: Bit -> Constr

dataTypeOf :: Bit -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bit)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bit)

gmapT :: (forall b. Data b => b -> b) -> Bit -> Bit

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bit -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bit -> r

gmapQ :: (forall d. Data d => d -> u) -> Bit -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bit -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bit -> m Bit

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bit -> m Bit

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bit -> m Bit

Ord Bit Source # 
Instance details

Defined in Language.Netlist.AST

Methods

compare :: Bit -> Bit -> Ordering

(<) :: Bit -> Bit -> Bool

(<=) :: Bit -> Bit -> Bool

(>) :: Bit -> Bit -> Bool

(>=) :: Bit -> Bit -> Bool

max :: Bit -> Bit -> Bit

min :: Bit -> Bit -> Bit

Show Bit Source # 
Instance details

Defined in Language.Netlist.AST

Methods

showsPrec :: Int -> Bit -> ShowS

show :: Bit -> String

showList :: [Bit] -> ShowS

Binary Bit Source # 
Instance details

Defined in Language.Netlist.AST

Methods

put :: Bit -> Put

get :: Get Bit

putList :: [Bit] -> Put

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).

Instances

Instances details
Eq Stmt Source # 
Instance details

Defined in Language.Netlist.AST

Methods

(==) :: Stmt -> Stmt -> Bool

(/=) :: Stmt -> Stmt -> Bool

Data Stmt Source # 
Instance details

Defined in Language.Netlist.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stmt -> c Stmt

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stmt

toConstr :: Stmt -> Constr

dataTypeOf :: Stmt -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Stmt)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stmt)

gmapT :: (forall b. Data b => b -> b) -> Stmt -> Stmt

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stmt -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stmt -> r

gmapQ :: (forall d. Data d => d -> u) -> Stmt -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> Stmt -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt

Ord Stmt Source # 
Instance details

Defined in Language.Netlist.AST

Methods

compare :: Stmt -> Stmt -> Ordering

(<) :: Stmt -> Stmt -> Bool

(<=) :: Stmt -> Stmt -> Bool

(>) :: Stmt -> Stmt -> Bool

(>=) :: Stmt -> Stmt -> Bool

max :: Stmt -> Stmt -> Stmt

min :: Stmt -> Stmt -> Stmt

Show Stmt Source # 
Instance details

Defined in Language.Netlist.AST

Methods

showsPrec :: Int -> Stmt -> ShowS

show :: Stmt -> String

showList :: [Stmt] -> ShowS

Binary Stmt Source # 
Instance details

Defined in Language.Netlist.AST

Methods

put :: Stmt -> Put

get :: Get Stmt

putList :: [Stmt] -> Put

type LValue = Expr Source #

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 

Instances

Instances details
Eq UnaryOp Source # 
Instance details

Defined in Language.Netlist.AST

Methods

(==) :: UnaryOp -> UnaryOp -> Bool

(/=) :: UnaryOp -> UnaryOp -> Bool

Data UnaryOp Source # 
Instance details

Defined in Language.Netlist.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnaryOp -> c UnaryOp

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnaryOp

toConstr :: UnaryOp -> Constr

dataTypeOf :: UnaryOp -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnaryOp)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnaryOp)

gmapT :: (forall b. Data b => b -> b) -> UnaryOp -> UnaryOp

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnaryOp -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnaryOp -> r

gmapQ :: (forall d. Data d => d -> u) -> UnaryOp -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> UnaryOp -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp

Ord UnaryOp Source # 
Instance details

Defined in Language.Netlist.AST

Methods

compare :: UnaryOp -> UnaryOp -> Ordering

(<) :: UnaryOp -> UnaryOp -> Bool

(<=) :: UnaryOp -> UnaryOp -> Bool

(>) :: UnaryOp -> UnaryOp -> Bool

(>=) :: UnaryOp -> UnaryOp -> Bool

max :: UnaryOp -> UnaryOp -> UnaryOp

min :: UnaryOp -> UnaryOp -> UnaryOp

Show UnaryOp Source # 
Instance details

Defined in Language.Netlist.AST

Methods

showsPrec :: Int -> UnaryOp -> ShowS

show :: UnaryOp -> String

showList :: [UnaryOp] -> ShowS

Binary UnaryOp Source # 
Instance details

Defined in Language.Netlist.AST

Methods

put :: UnaryOp -> Put

get :: Get UnaryOp

putList :: [UnaryOp] -> Put

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.

Instances

Instances details
Eq BinaryOp Source # 
Instance details

Defined in Language.Netlist.AST

Methods

(==) :: BinaryOp -> BinaryOp -> Bool

(/=) :: BinaryOp -> BinaryOp -> Bool

Data BinaryOp Source # 
Instance details

Defined in Language.Netlist.AST

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinaryOp -> c BinaryOp

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinaryOp

toConstr :: BinaryOp -> Constr

dataTypeOf :: BinaryOp -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinaryOp)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinaryOp)

gmapT :: (forall b. Data b => b -> b) -> BinaryOp -> BinaryOp

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinaryOp -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinaryOp -> r

gmapQ :: (forall d. Data d => d -> u) -> BinaryOp -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> BinaryOp -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinaryOp -> m BinaryOp

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinaryOp -> m BinaryOp

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinaryOp -> m BinaryOp

Ord BinaryOp Source # 
Instance details

Defined in Language.Netlist.AST

Methods

compare :: BinaryOp -> BinaryOp -> Ordering

(<) :: BinaryOp -> BinaryOp -> Bool

(<=) :: BinaryOp -> BinaryOp -> Bool

(>) :: BinaryOp -> BinaryOp -> Bool

(>=) :: BinaryOp -> BinaryOp -> Bool

max :: BinaryOp -> BinaryOp -> BinaryOp

min :: BinaryOp -> BinaryOp -> BinaryOp

Show BinaryOp Source # 
Instance details

Defined in Language.Netlist.AST

Methods

showsPrec :: Int -> BinaryOp -> ShowS

show :: BinaryOp -> String

showList :: [BinaryOp] -> ShowS

Binary BinaryOp Source # 
Instance details

Defined in Language.Netlist.AST

Methods

put :: BinaryOp -> Put

get :: Get BinaryOp

putList :: [BinaryOp] -> Put