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

Copyright(C) 2012-2016 University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
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

type Identifier = Text Source #

Signal reference

data Component Source #

Component: base unit of a Netlist

Constructors

Component 

Fields

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

BitVector !Size

BitVector of a specified size

Index !Integer

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

RTree !Size !HWType

RTree 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 !Integer

Clock type with specified name and period

Reset !Identifier !Integer

Reset type corresponding to clock with a specified name and period

Instances

Eq HWType Source # 

Methods

(==) :: HWType -> HWType -> Bool #

(/=) :: HWType -> HWType -> Bool #

Ord HWType Source # 
Show HWType Source # 
Generic HWType Source # 

Associated Types

type Rep HWType :: * -> * #

Methods

from :: HWType -> Rep HWType x #

to :: Rep HWType x -> HWType #

Hashable HWType Source # 

Methods

hashWithSalt :: Int -> HWType -> Int #

hash :: HWType -> Int #

NFData HWType Source # 

Methods

rnf :: HWType -> () #

MonadWriter (Set (Identifier, HWType)) NetlistMonad Source # 
type Rep HWType Source # 
type Rep HWType = D1 (MetaData "HWType" "CLaSH.Netlist.Types" "clash-lib-0.7-83ZNOjNIImPHkX9dasXVwo" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Void" PrefixI False) U1) ((:+:) (C1 (MetaCons "String" PrefixI False) U1) (C1 (MetaCons "Bool" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "BitVector" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Size))) (C1 (MetaCons "Index" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Integer)))) ((:+:) (C1 (MetaCons "Signed" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Size))) (C1 (MetaCons "Unsigned" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Size)))))) ((:+:) ((:+:) (C1 (MetaCons "Vector" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Size)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HWType)))) ((:+:) (C1 (MetaCons "RTree" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Size)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HWType)))) (C1 (MetaCons "Sum" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Identifier)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Identifier])))))) ((:+:) ((:+:) (C1 (MetaCons "Product" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Identifier)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [HWType])))) (C1 (MetaCons "SP" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Identifier)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Identifier, [HWType])]))))) ((:+:) (C1 (MetaCons "Clock" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Identifier)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Integer)))) (C1 (MetaCons "Reset" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Identifier)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Integer))))))))

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, PortDirection, HWType, Expr)]

Instantiation of another component

BlackBoxD !Text [Text] [Text] (Maybe (Text, BlackBoxTemplate)) !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

RTreeAppend

See the expression in the context of a Tree append operation

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 [Text] [Text] (Maybe (Text, BlackBoxTemplate)) !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

Eq Bit Source # 

Methods

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

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

Show Bit Source # 

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

data BlackBoxContext Source #

Context used to fill in the holes of a BlackBox template

Constructors

Context 

Fields

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

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