clash-lib-1.0.1: CAES Language for Synchronous Hardware - As a Library
Copyright(C) 2012-2016 University of Twente
2017 Myrtle Software Ltd
2017-2018 Google Inc.
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

data Declaration Source #

Internals of a Component

Constructors

Assignment

Signal assignment

Fields

CondAssignment

Conditional signal assignment:

Fields

  • !Identifier

    Signal to assign

  • !HWType

    Type of the result/alternatives

  • !Expr

    Scrutinized expression

  • !HWType

    Type of the scrutinee

  • [(Maybe Literal, Expr)]

    List of: (Maybe expression scrutinized expression is compared with,RHS of alternative)

InstDecl

Instantiation of another component:

Fields

BlackBoxD

Instantiation of blackbox declaration

Fields

NetDecl'

Signal declaration

Fields

TickDecl Comment

HDL tick corresponding to a Core tick

Bundled Patterns

pattern NetDecl 

Fields

Instances

Instances details
Show Declaration Source # 
Instance details

Defined in Clash.Netlist.Types

NFData Declaration Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: Declaration -> () #

newtype NetlistMonad a Source #

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

Instances

Instances details
Monad NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

Functor NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

fmap :: (a -> b) -> NetlistMonad a -> NetlistMonad b #

(<$) :: a -> NetlistMonad b -> NetlistMonad a #

MonadFail NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

fail :: String -> NetlistMonad a #

Applicative NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

MonadIO NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

liftIO :: IO a -> NetlistMonad a #

MonadReader NetlistEnv NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

MonadState NetlistState NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

data BlackBox Source #

Instances

Instances details
Show BlackBox Source # 
Instance details

Defined in Clash.Netlist.Types

Generic BlackBox Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep BlackBox :: Type -> Type #

Methods

from :: BlackBox -> Rep BlackBox x #

to :: Rep BlackBox x -> BlackBox #

Binary BlackBox Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

put :: BlackBox -> Put #

get :: Get BlackBox #

putList :: [BlackBox] -> Put #

NFData BlackBox Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: BlackBox -> () #

type Rep BlackBox Source # 
Instance details

Defined in Clash.Netlist.Types

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#, Right e: dataToTag#

BlackBoxE

Instantiation of a BlackBox expression

Fields

ConvBV (Maybe Identifier) HWType Bool Expr 
IfThenElse Expr Expr Expr 

Instances

Instances details
Show Expr Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

data Component Source #

Component: base unit of a Netlist

Constructors

Component 

Fields

Instances

Instances details
Show Component Source # 
Instance details

Defined in Clash.Netlist.Types

NFData Component Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: Component -> () #

data Declaration Source #

Internals of a Component

Constructors

Assignment

Signal assignment

Fields

CondAssignment

Conditional signal assignment:

Fields

  • !Identifier

    Signal to assign

  • !HWType

    Type of the result/alternatives

  • !Expr

    Scrutinized expression

  • !HWType

    Type of the scrutinee

  • [(Maybe Literal, Expr)]

    List of: (Maybe expression scrutinized expression is compared with,RHS of alternative)

InstDecl

Instantiation of another component:

Fields

BlackBoxD

Instantiation of blackbox declaration

Fields

NetDecl'

Signal declaration

Fields

TickDecl Comment

HDL tick corresponding to a Core tick

Instances

Instances details
Show Declaration Source # 
Instance details

Defined in Clash.Netlist.Types

NFData Declaration Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: Declaration -> () #

data HWType Source #

Representable hardware types

Constructors

Void (Maybe HWType)

Empty type. Just Size for "empty" Vectors so we can still have primitives that can traverse e.g. Vectors of unit and know the length of that vector.

String

String type

Integer

Integer type (for parameters only)

Bool

Boolean type

Bit

Bit 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 (Maybe [Text]) [HWType]

Product type: Name, field names, and field types. Field names will be populated when using records.

SP !Identifier [(Identifier, [HWType])]

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

Clock !Identifier

Clock type corresponding to domain Identifier

Reset !Identifier

Reset type corresponding to domain Identifier

BiDirectional !PortDirection !HWType

Tagging type indicating a bidirectional (inout) port

CustomSP !Identifier !DataRepr' !Size [(ConstrRepr', Identifier, [HWType])]

Same as Sum-Of-Product, but with a user specified bit representation. For more info, see: Clash.Annotations.BitRepresentations.

CustomSum !Identifier !DataRepr' !Size [(ConstrRepr', Identifier)]

Same as Sum, but with a user specified bit representation. For more info, see: Clash.Annotations.BitRepresentations.

Annotated [Attr'] !HWType

Annotated with HDL attributes

KnownDomain !Identifier !Integer !ActiveEdge !ResetKind !InitBehavior !ResetPolarity

Domain name, period, active edge, reset kind, initial value behavior

Instances

Instances details
Eq HWType Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

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

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

Ord HWType Source # 
Instance details

Defined in Clash.Netlist.Types

Show HWType Source # 
Instance details

Defined in Clash.Netlist.Types

Generic HWType Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep HWType :: Type -> Type #

Methods

from :: HWType -> Rep HWType x #

to :: Rep HWType x -> HWType #

Hashable HWType Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

hashWithSalt :: Int -> HWType -> Int #

hash :: HWType -> Int #

NFData HWType Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: HWType -> () #

type Rep HWType Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep HWType = D1 ('MetaData "HWType" "Clash.Netlist.Types" "clash-lib-1.0.1-inplace" 'False) ((((C1 ('MetaCons "Void" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe HWType))) :+: C1 ('MetaCons "String" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Integer" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Bool" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bit" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BitVector" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Size)) :+: C1 ('MetaCons "Index" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer))) :+: (C1 ('MetaCons "Signed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Size)) :+: (C1 ('MetaCons "Unsigned" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Size)) :+: C1 ('MetaCons "Vector" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Size) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HWType)))))) :+: (((C1 ('MetaCons "RTree" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Size) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HWType)) :+: C1 ('MetaCons "Sum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Identifier]))) :+: (C1 ('MetaCons "Product" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [HWType]))) :+: (C1 ('MetaCons "SP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Identifier, [HWType])])) :+: C1 ('MetaCons "Clock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier))))) :+: ((C1 ('MetaCons "Reset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier)) :+: (C1 ('MetaCons "BiDirectional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PortDirection) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HWType)) :+: C1 ('MetaCons "CustomSP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DataRepr')) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Size) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ConstrRepr', Identifier, [HWType])]))))) :+: (C1 ('MetaCons "CustomSum" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DataRepr')) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Size) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ConstrRepr', Identifier)]))) :+: (C1 ('MetaCons "Annotated" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Attr']) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HWType)) :+: C1 ('MetaCons "KnownDomain" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Identifier) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ActiveEdge))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ResetKind) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InitBehavior) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ResetPolarity)))))))))

type Identifier = Text Source #

Signal reference

data TemplateFunction where Source #

Constructors

TemplateFunction :: [Int] -> (BlackBoxContext -> Bool) -> (forall s. Backend s => BlackBoxContext -> State s Doc) -> TemplateFunction 

Instances

Instances details
Binary TemplateFunction Source #

NB: serialisation doesn't preserve the embedded function

Instance details

Defined in Clash.Netlist.Types

NFData TemplateFunction Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: TemplateFunction -> () #

data BlackBoxContext Source #

Context used to fill in the holes of a BlackBox template

Constructors

Context 

Fields

Instances

Instances details
Show BlackBoxContext Source # 
Instance details

Defined in Clash.Netlist.Types

data Bit Source #

Bit literal

Constructors

H

High

L

Low

U

Undefined

Z

High-impedance

Instances

Instances details
Eq Bit Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

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

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

Show Bit Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

Lift Bit Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

lift :: Bit -> Q Exp #

data Literal Source #

Literals used in an expression

Constructors

NumLit !Integer

Number literal

BitLit !Bit

Bit literal

BitVecLit !Integer !Integer

BitVector literal

BoolLit !Bool

Boolean literal

VecLit [Literal]

Vector literal

StringLit !String

String literal

Instances

Instances details
Eq Literal Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

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

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

Show Literal Source # 
Instance details

Defined in Clash.Netlist.Types

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

Sliced (HWType, Int, Int)

Slice the identifier of the given type from start to end

Nested Modifier Modifier 

Instances

Instances details
Show Modifier Source # 
Instance details

Defined in Clash.Netlist.Types

data PortDirection Source #

Constructors

In 
Out 

Instances

Instances details
Eq PortDirection Source # 
Instance details

Defined in Clash.Netlist.Types

Ord PortDirection Source # 
Instance details

Defined in Clash.Netlist.Types

Show PortDirection Source # 
Instance details

Defined in Clash.Netlist.Types

Generic PortDirection Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep PortDirection :: Type -> Type #

Hashable PortDirection Source # 
Instance details

Defined in Clash.Netlist.Types

NFData PortDirection Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: PortDirection -> () #

type Rep PortDirection Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep PortDirection = D1 ('MetaData "PortDirection" "Clash.Netlist.Types" "clash-lib-1.0.1-inplace" 'False) (C1 ('MetaCons "In" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Out" 'PrefixI 'False) (U1 :: Type -> Type))

data WireOrReg Source #

Constructors

Wire 
Reg 

Instances

Instances details
Show WireOrReg Source # 
Instance details

Defined in Clash.Netlist.Types

Generic WireOrReg Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep WireOrReg :: Type -> Type #

NFData WireOrReg Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: WireOrReg -> () #

type Rep WireOrReg Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep WireOrReg = D1 ('MetaData "WireOrReg" "Clash.Netlist.Types" "clash-lib-1.0.1-inplace" 'False) (C1 ('MetaCons "Wire" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Reg" 'PrefixI 'False) (U1 :: Type -> Type))

data EntityOrComponent Source #

Constructors

Entity 
Comp 
Empty 

Instances

Instances details
Show EntityOrComponent Source # 
Instance details

Defined in Clash.Netlist.Types

data FilteredHWType Source #

Tree structure indicating which constructor fields were filtered from a type due to them being void. We need this information to generate stable and/or user-defined port mappings.

Instances

Instances details
Eq FilteredHWType Source # 
Instance details

Defined in Clash.Netlist.Types

Show FilteredHWType Source # 
Instance details

Defined in Clash.Netlist.Types

type Size = Int Source #

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

data NetlistState Source #

State of the NetlistMonad

Constructors

NetlistState 

Fields

Instances

Instances details
MonadState NetlistState NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

data NetlistEnv Source #

Environment of the NetlistMonad

Constructors

NetlistEnv 

Fields

Instances

Instances details
MonadReader NetlistEnv NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

pattern NetDecl Source #

Arguments

:: Maybe Comment

Note; will be inserted as a comment in target hdl

-> Identifier

Name of signal

-> HWType

Type of signal

-> Declaration 

hwTypeAttrs :: HWType -> [Attr'] Source #

Extract hardware attributes from Annotated. Returns an empty list if non-Annotated given or if Annotated has an empty list of attributes.

toBit Source #

Arguments

:: Integer

mask

-> Integer

value

-> Bit