clash-lib-0.2.0.1: CAES Language for Synchronous Hardware - As a Library

Safe HaskellNone

CLaSH.Netlist.Types

Description

Type and instance definitions for Netlist modules

Synopsis

Documentation

newtype NetlistMonad a Source

Monad that caches generated components (StateT) and remembers hidden inputs of components that are being generated (WriterT)

Constructors

NetlistMonad 

Fields

runNetlist :: WriterT [(Identifier, HWType)] (StateT NetlistState (FreshMT IO)) a
 

type VHDLState = (HashSet HWType, Int, HashMap HWType Doc)Source

State for the VHDLM monad:

  • Previously encountered HWTypes
  • Product type counter
  • Cache for previously generated product type names

data NetlistState Source

State of the NetlistMonad

Constructors

NetlistState 

Fields

_bindings :: HashMap TmName (Type, Term)

Global binders

_varEnv :: Gamma

Type environment/context

_varCount :: Int

Number of signal declarations

_cmpCount :: Int

Number of create components

_components :: HashMap TmName Component

Cached components

_primitives :: PrimMap

Primitive Definitions

_vhdlMState :: VHDLState

State for the VHDLM Monad

_typeTranslator :: Type -> Maybe (Either String HWType)

Hardcoded Type -> HWType translator

Instances

type Identifier = TextSource

Signal reference

data Component Source

Component: base unit of a Netlist

Constructors

Component 

Fields

componentName :: Identifier

Name of the component

hiddenPorts :: [(Identifier, HWType)]

Ports that have no correspondence the original function definition

inputs :: [(Identifier, HWType)]

Input ports

output :: (Identifier, HWType)

Output port

declarations :: [Declaration]

Internal declarations

Instances

type Size = IntSource

Size indication of a type (e.g. bit-size or number of elements)

data HWType Source

Representable hardware types

Constructors

Void

Empty type

Bit

Bit type

Bool

Boolean type

Integer

Integer type

Signed Size

Signed integer of a specified size

Unsigned Size

Unsigned integer of a specified size

Vector Size HWType

Vector type

Sum Identifier [Identifier]

Sum type: Name and Constructor names

Product Identifier [HWType]

Product type: Name and field types

SP Identifier [(Identifier, [HWType])]

Sum-of-Product type: Name and Constructor names + field types

Clock Int

Clock type with specified period

Reset Int

Reset type corresponding to clock with a specified period

data Declaration Source

Internals of a Component

Constructors

Assignment Identifier Expr

Signal assignment:

  • Signal to assign
  • Assigned expression
CondAssignment Identifier Expr [(Maybe Expr, Expr)]

Conditional signal assignment:

  • Signal to assign
  • Scrutinized expression
  • List of: (Maybe expression scrutinized expression is compared with,RHS of alternative)
InstDecl Identifier Identifier [(Identifier, Expr)]

Instantiation of another component

BlackBoxD Text

Instantiation of blackbox declaration

NetDecl Identifier HWType (Maybe Expr)

Signal declaration

Instances

data Modifier Source

Expression Modifier

Constructors

Indexed (HWType, Int, Int)

Index the expression: (Type of expression,DataCon tag,Field Tag)

DC (HWType, Int)

See expression in a DataCon context: (Type of the expression, DataCon tag)

VecAppend

See the expression in the context of a Vector append operation

Instances

data Expr Source

Expression used in RHS of a declaration

Constructors

Literal (Maybe Size) Literal

Literal expression

DataCon HWType (Maybe Modifier) [Expr]

DataCon application

Identifier Identifier (Maybe Modifier)

Signal reference

BlackBoxE Text (Maybe Modifier)

Instantiation of a BlackBox expression

Instances

data Literal Source

Literals used in an expression

Constructors

NumLit Int

Number literal

BitLit Bit

Bit literal

BoolLit Bool

Boolean literal

VecLit [Literal]

Vector literal

Instances

data Bit Source

Bit literal

Constructors

H

High

L

Low

U

Undefined

Z

High-impedance

Instances