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

Safe HaskellNone
LanguageHaskell2010

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)

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

_typeTranslator :: HashMap TyConName TyCon -> Type -> Maybe (Either String HWType)

Hardcoded Type -> HWType translator

_tcCache :: HashMap TyConName TyCon

TyCon cache

_modNm :: !String

Name of the module containing the topEntity

_curCompNm :: !Identifier
 
_dataFiles :: [(String, FilePath)]
 

type Identifier = Text Source

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

outputs :: [(Identifier, HWType)]

Output ports

declarations :: [Declaration]

Internal declarations

type Size = Int Source

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

data HWType Source

Representable hardware types

Constructors

Void

Empty type

String

String type

Bool

Boolean type

Integer

Integer type

BitVector !Size

BitVector of a specified size

Index !Size

Unsigned integer with specified (exclusive) upper bounder

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 !Identifier !Int

Clock type with specified name and period

Reset !Identifier !Int

Reset type corresponding to clock with a specified name and period

data Declaration Source

Internals of a Component

Constructors

Assignment !Identifier !Expr

Signal assignment:

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

Conditional signal assignment:

  • Signal to assign
  • Type of the result/alternatives
  • Scrutinized expression
  • Type of the scrutinee
  • List of: (Maybe expression scrutinized expression is compared with,RHS of alternative)
InstDecl !Identifier !Identifier [(Identifier, Expr)]

Instantiation of another component

BlackBoxD !Text !BlackBoxTemplate BlackBoxContext

Instantiation of blackbox declaration

NetDecl !Identifier !HWType

Signal declaration

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 (HWType, Size)) !Literal

Literal expression

DataCon !HWType !Modifier [Expr]

DataCon application

Identifier !Identifier !(Maybe Modifier)

Signal reference

DataTag !HWType !(Either Identifier Identifier)

Left e: tagToEnum

BlackBoxE !Text !BlackBoxTemplate !BlackBoxContext !Bool

Instantiation of a BlackBox expression

Instances

data Literal Source

Literals used in an expression

Constructors

NumLit !Integer

Number literal

BitLit !Bit

Bit literal

BoolLit !Bool

Boolean literal

VecLit [Literal]

Vector literal

StringLit !String

String literal

data Bit Source

Bit literal

Constructors

H

High

L

Low

U

Undefined

Z

High-impedance

Instances

data BlackBoxContext Source

Context used to fill in the holes of a BlackBox template

Constructors

Context 

Fields

bbResult :: (SyncExpr, HWType)

Result name and type

bbInputs :: [(SyncExpr, HWType, Bool)]

Argument names, types, and whether it is a literal

bbFunctions :: IntMap (Either BlackBoxTemplate Declaration, BlackBoxContext)

Function arguments (subset of inputs):

  • (Blackbox Template,Partial Blackbox Concext)

type SyncIdentifier = Either Identifier (Identifier, (Identifier, Int)) Source

Either the name of the identifier, or a tuple of the identifier and the corresponding clock