clash-lib-1.6.3: Clash: a functional hardware description language - As a library
Copyright(C) 2012-2016 University of Twente
2017 Myrtle Software Ltd
2017-2018 Google Inc.
2020-2022 QBayLogic B.V.
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.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 CommentOrDirective

HDL tick corresponding to a Core tick

Seq [Seq]

Sequential statement

ConditionalDecl

Compilation conditional on some preprocessor symbol, note that declarations here are ignored for VHDL. See here for a discussion https://github.com/clash-lang/clash-compiler/pull/1798#discussion_r648571862

Fields

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 -> () #

data PreserveCase Source #

Whether to preserve casing in ids or converted everything to lowercase. Influenced by '-fclash-lower-case-basic-identifiers'

Constructors

PreserveCase 
ToLower 

Instances

Instances details
Eq PreserveCase Source # 
Instance details

Defined in Clash.Netlist.Types

Show PreserveCase Source # 
Instance details

Defined in Clash.Netlist.Types

Generic PreserveCase Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep PreserveCase :: Type -> Type #

Hashable PreserveCase Source # 
Instance details

Defined in Clash.Netlist.Types

Binary PreserveCase Source # 
Instance details

Defined in Clash.Netlist.Types

NFData PreserveCase Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: PreserveCase -> () #

type Rep PreserveCase Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep PreserveCase = D1 ('MetaData "PreserveCase" "Clash.Netlist.Types" "clash-lib-1.6.3-inplace" 'False) (C1 ('MetaCons "PreserveCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ToLower" 'PrefixI 'False) (U1 :: Type -> Type))

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 #

IdentifierSetMonad NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

MonadReader NetlistEnv NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

MonadState NetlistState NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

data TopEntityT Source #

Structure describing a top entity: it's id and its port annotations.

Constructors

TopEntityT 

Fields

Instances

Instances details
Eq TopEntityT Source # 
Instance details

Defined in Clash.Netlist.Types

Show TopEntityT Source # 
Instance details

Defined in Clash.Netlist.Types

Generic TopEntityT Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep TopEntityT :: Type -> Type #

Hashable TopEntityT Source # 
Instance details

Defined in Clash.Annotations.TopEntity.Extra

Binary TopEntityT Source # 
Instance details

Defined in Clash.Annotations.TopEntity.Extra

NFData TopEntityT Source # 
Instance details

Defined in Clash.Annotations.TopEntity.Extra

Methods

rnf :: TopEntityT -> () #

type Rep TopEntityT Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep TopEntityT = D1 ('MetaData "TopEntityT" "Clash.Netlist.Types" "clash-lib-1.6.3-inplace" 'False) (C1 ('MetaCons "TopEntityT" 'PrefixI 'True) (S1 ('MetaSel ('Just "topId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: (S1 ('MetaSel ('Just "topAnnotation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TopEntity)) :*: S1 ('MetaSel ('Just "topIsTestBench") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

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

ToBv

Convert some type to a BitVector.

Fields

FromBv

Convert BitVector to some type.

Fields

IfThenElse Expr Expr Expr 
Noop

Do nothing

Instances

Instances details
Show Expr Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

NFData Expr Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: Expr -> () #

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

Generic Component Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep Component :: Type -> Type #

NFData Component Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: Component -> () #

type Rep Component Source # 
Instance details

Defined in Clash.Netlist.Types

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 CommentOrDirective

HDL tick corresponding to a Core tick

Seq [Seq]

Sequential statement

ConditionalDecl

Compilation conditional on some preprocessor symbol, note that declarations here are ignored for VHDL. See here for a discussion https://github.com/clash-lang/clash-compiler/pull/1798#discussion_r648571862

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 -> () #

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

MemBlob !Size !Size

MemBlob type

RTree !Size !HWType

RTree type

Sum !Text [Text]

Sum type: Name and Constructor names

Product !Text (Maybe [Text]) [HWType]

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

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

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

Clock !DomainName

Clock type corresponding to domain DomainName

Reset !DomainName

Reset type corresponding to domain DomainName

Enable !DomainName

Enable type corresponding to domain DomainName

BiDirectional !PortDirection !HWType

Tagging type indicating a bidirectional (inout) port

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

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

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

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

CustomProduct !Text !DataRepr' !Size (Maybe [Text]) [(FieldAnn, HWType)]

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

Annotated [Attr'] !HWType

Annotated with HDL attributes

KnownDomain !DomainName !Integer !ActiveEdge !ResetKind !InitBehavior !ResetPolarity

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

FileType

File type for simulation-level I/O

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.6.3-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 "MemBlob" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Size) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Size)) :+: 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 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])) :+: (C1 ('MetaCons "Product" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (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 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, [HWType])])))) :+: (C1 ('MetaCons "Clock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DomainName)) :+: (C1 ('MetaCons "Reset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DomainName)) :+: C1 ('MetaCons "Enable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DomainName))))) :+: ((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 Text) :*: 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', Text, [HWType])]))) :+: C1 ('MetaCons "CustomSum" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: 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', Text)]))))) :+: ((C1 ('MetaCons "CustomProduct" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: 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 (Maybe [Text])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(FieldAnn, HWType)])))) :+: 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 DomainName) :*: (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)))) :+: C1 ('MetaCons "FileType" 'PrefixI 'False) (U1 :: Type -> Type))))))

data IdentifierSet Source #

A collection of unique identifiers. Allows for fast fresh identifier generation.

NB: use the functions in Clash.Netlist.Id. Don't use the constructor directly.

Constructors

IdentifierSet 

Fields

  • is_allowEscaped :: !Bool

    Allow escaped ids? If set to False, "make" will always behave like "makeBasic".

  • is_lowerCaseBasicIds :: !PreserveCase

    Force all generated basic identifiers to lowercase.

  • is_hdl :: !HDL

    HDL to generate fresh identifiers for

  • is_freshCache :: !FreshCache

    Maps an i_baseNameCaseFold to a map mapping the number of extensions (in i_extensionsRev) to the maximum word at that basename/level. For example, if a set would contain the identifiers:

    foo, foo_1, foo_2, bar_5, bar_7_8

    the map would look like:

    (foo, [(0, 0), (1, 2)
    ), (bar, [(1, 5), (2, 8)])]

    This mapping makes sure we can quickly generate fresh identifiers. For example, generating a new id for "foo_1" would be a matter of looking up the base name in this map, concluding that the maximum identifier with this basename and this number of extensions is "foo_2", subsequently generating "foo_3".

    Note that an identifier with no extensions is also stored in this map for practical purposes, but the maximum ext is invalid.

  • is_store :: !(HashSet Identifier)

    Identifier store

Instances

Instances details
Show IdentifierSet Source # 
Instance details

Defined in Clash.Netlist.Types

Generic IdentifierSet Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep IdentifierSet :: Type -> Type #

NFData IdentifierSet Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: IdentifierSet -> () #

HasIdentifierSet IdentifierSet Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep IdentifierSet Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep IdentifierSet = D1 ('MetaData "IdentifierSet" "Clash.Netlist.Types" "clash-lib-1.6.3-inplace" 'False) (C1 ('MetaCons "IdentifierSet" 'PrefixI 'True) ((S1 ('MetaSel ('Just "is_allowEscaped") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "is_lowerCaseBasicIds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PreserveCase)) :*: (S1 ('MetaSel ('Just "is_hdl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HDL) :*: (S1 ('MetaSel ('Just "is_freshCache") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FreshCache) :*: S1 ('MetaSel ('Just "is_store") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HashSet Identifier))))))

data Identifier Source #

HDL identifier. Consists of a base name and a number of extensions. An identifier with a base name of "foo" and a list of extensions [1, 2] will be rendered as "foo_1_2".

Note: The Eq instance of Identifier is case insensitive! E.g., two identifiers with base names fooBar and FoObAR are considered the same. However, identifiers are stored case preserving. This means Clash won't generate two identifiers with differing case, but it will try to keep capitalization.

The goal of this data structure is to greatly simplify how Clash deals with identifiers internally. Any Identifier should be trivially printable to any HDL.

NB: use the functions in Clash.Netlist.Id. Don't use these constructors directly.

Constructors

RawIdentifier

Unparsed identifier. Used for things such as port names, which should appear in the HDL exactly as the user specified.

Fields

  • !Text

    An identifier exactly as given by the user

  • (Maybe Identifier)

    Parsed version of raw identifier. Will not be populated if this identifier was created with an unsafe function.

  • !CallStack

    Stores where this identifier was generated. Tracking is only enabled is debugIsOn, otherwise this field will be populated by an empty callstack.

UniqueIdentifier

Parsed and sanitized identifier. See various fields for more information on its invariants.

Fields

  • i_baseName :: !Text

    Base name of identifier. make makes sure this field:

    • does not end in _num where num is a digit.
    • is solely made up of printable ASCII characters
    • has no leading or trailing whitespace
  • i_baseNameCaseFold :: !Text

    Same as i_baseName, but can be used for equality testing that doesn't depend on capitalization.

  • i_extensionsRev :: [Word]

    Extensions applied to base identifier. E.g., an identifier with a base name of foo and an extension of [6, 5] would render as foo_5_6. Note that extensions are stored in reverse order for easier manipulation.

  • i_idType :: !IdentifierType
  • i_hdl :: !HDL

    HDL this identifier is generated for.

  • i_provenance :: !CallStack

    Stores where this identifier was generated. Tracking is only enabled is debugIsOn, otherwise this field will be populated by an empty callstack.

Instances

Instances details
Eq Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

Ord Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

Show Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

Generic Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep Identifier :: Type -> Type #

Hashable Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

NFData Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: Identifier -> () #

Pretty Identifier Source # 
Instance details

Defined in Clash.Netlist.Id.Internal

Methods

pretty :: Identifier -> Doc ann #

prettyList :: [Identifier] -> Doc ann #

type Rep Identifier Source # 
Instance details

Defined in Clash.Netlist.Types

data IdentifierType Source #

Constructors

Basic

A basic identifier: does not have to be escaped in order to be a valid identifier in HDL.

Extended

An extended identifier: has to be escaped, wrapped, or otherwise postprocessed before writhing it to HDL.

Instances

Instances details
Eq IdentifierType Source # 
Instance details

Defined in Clash.Netlist.Types

Show IdentifierType Source # 
Instance details

Defined in Clash.Netlist.Types

Generic IdentifierType Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep IdentifierType :: Type -> Type #

NFData IdentifierType Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: IdentifierType -> () #

type Rep IdentifierType Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep IdentifierType = D1 ('MetaData "IdentifierType" "Clash.Netlist.Types" "clash-lib-1.6.3-inplace" 'False) (C1 ('MetaCons "Basic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Extended" 'PrefixI 'False) (U1 :: Type -> Type))

data DeclarationType Source #

Type of declaration, concurrent or sequential

Constructors

Concurrent 
Sequential 

data NetlistId Source #

Netlist-level identifier

Constructors

NetlistId Identifier Type

Identifier generated in the NetlistMonad, always derived from another NetlistId

CoreId Id

An original Core identifier

MultiId [Id]

A split identifier (into several sub-identifiers), needed to assign expressions of types that have to be split apart (e.g. tuples of Files)

Instances

Instances details
Show NetlistId Source # 
Instance details

Defined in Clash.Netlist.Types

data TemplateFunction where Source #

Constructors

TemplateFunction 

Fields

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 #

liftTyped :: Bit -> Q (TExp Bit) #

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.6.3-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.6.3-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 Seq Source #

Sequential statements

Constructors

AlwaysClocked

Clocked sequential statements

Fields

  • ActiveEdge

    Edge of the clock the statement should be executed

  • Expr

    Clock expression

  • [Seq]

    Statements to be executed on the active clock edge | Statements running at simulator start

Initial [Seq]

Statements to run at simulator start | Statements to run always

AlwaysComb [Seq]

Statements to run always | Declaration in sequential form

SeqDecl Declaration

The declaration | Branching statement

Branch 

Fields

  • !Expr

    Scrutinized expresson

  • !HWType

    Type of the scrutinized expression

  • [(Maybe Literal, [Seq])]

    List of: (Maybe match, RHS of Alternative)

Instances

Instances details
Show Seq Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

showsPrec :: Int -> Seq -> ShowS #

show :: Seq -> String #

showList :: [Seq] -> ShowS #

data PortMap Source #

Specifies how to wire up a component instance

Constructors

IndexedPortMap [(PortDirection, HWType, Expr)]

Port map based on port positions (port direction, type, assignment)

HDL Example:

bytemaster bytemaster_ds ( clk_1 , rst_1 , bitCtrl_0 );

NamedPortMap [(Expr, PortDirection, HWType, Expr)]

Port map based on port names (port name, port direction, type, assignment)

HDL Example:

bytemaster bytemaster_ds ( .clk (clk_1) , .rst (rst_1) , .bitCtrl (bitCtrl_0) );

Instances

Instances details
Show PortMap 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 SomeBackend where Source #

Existentially quantified backend

Constructors

SomeBackend :: Backend backend => backend -> SomeBackend 

data ComponentPrefix Source #

Constructors

ComponentPrefix 

Fields

Instances

Instances details
Show ComponentPrefix Source # 
Instance details

Defined in Clash.Netlist.Types

data NetlistState Source #

State of the NetlistMonad

Constructors

NetlistState 

Fields

  • _bindings :: BindingMap

    Global binders

  • _components :: ComponentMap

    Cached components. Is an insertion ordered map to preserve a topologically sorted component list for the manifest file.

  • _typeTranslator :: CustomReprs -> TyConMap -> Type -> State HWMap (Maybe (Either String FilteredHWType))

    Hardcoded Type -> HWType translator

  • _curCompNm :: !(Identifier, SrcSpan)
     
  • _seenIds :: IdentifierSet

    All names currently in scope.

  • _seenComps :: IdentifierSet

    Components (to be) generated during this netlist run. This is always a subset of seenIds. Reason d'etre: we currently generate components in a top down manner. E.g. given:

    • A
    • - B
    • - C

    we would generate component A first. Before trying to generate B and C. A might introduce a number of signal declarations. The names of these signals can't clash with the name of component B, hence we need to pick a name for B unique w.r.t. all these signal names. If we would postpone generating a unqiue name for B til _after_ generating all the signal names, the signal names would get all the "nice" names. E.g., a signal would be called "foo", thereby forcing the component B to be called "foo_1". Ideally, we'd use the "nice" names for components, and the "ugly" names for signals. To achieve this, we generate all the component names up front and subsequently store them in _seenComps.

  • _seenPrimitives :: Set Text

    Keeps track of invocations of ´mkPrimitive´. It is currently used to filter duplicate warning invocations for dubious blackbox instantiations, see GitHub pull request #286.

  • _componentNames :: VarEnv Identifier

    Names of components (to be) generated during this netlist run. Includes top entity names.

  • _topEntityAnns :: VarEnv TopEntityT
     
  • _hdlDir :: FilePath
     
  • _curBBlvl :: Int

    The current scoping level assigned to black box contexts

  • _isTestBench :: Bool

    Whether we're compiling a testbench (suppresses some warnings)

  • _backEndITE :: Bool

    Whether the backend supports ifThenElse expressions

  • _backend :: SomeBackend

    The current HDL backend

  • _htyCache :: HWMap
     

Instances

Instances details
MonadState NetlistState NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

data ComponentMeta Source #

Constructors

ComponentMeta 

Instances

Instances details
Show ComponentMeta Source # 
Instance details

Defined in Clash.Netlist.Types

Generic ComponentMeta Source # 
Instance details

Defined in Clash.Netlist.Types

Associated Types

type Rep ComponentMeta :: Type -> Type #

NFData ComponentMeta Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

rnf :: ComponentMeta -> () #

type Rep ComponentMeta Source # 
Instance details

Defined in Clash.Netlist.Types

type Rep ComponentMeta = D1 ('MetaData "ComponentMeta" "Clash.Netlist.Types" "clash-lib-1.6.3-inplace" 'False) (C1 ('MetaCons "ComponentMeta" 'PrefixI 'True) (S1 ('MetaSel ('Just "cmWereVoids") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Bool]) :*: (S1 ('MetaSel ('Just "cmLoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Just "cmScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IdentifierSet))))

data NetlistEnv Source #

Environment of the NetlistMonad

Constructors

NetlistEnv 

Fields

Instances

Instances details
MonadReader NetlistEnv NetlistMonad Source # 
Instance details

Defined in Clash.Netlist.Types

data ExpandedPortName a Source #

Constructors

ExpandedPortName HWType a

Same as PortName, but fully expanded

ExpandedPortProduct

Same as PortProduct, but fully expanded

Fields

Instances

Instances details
Functor ExpandedPortName Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

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

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

Foldable ExpandedPortName Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

fold :: Monoid m => ExpandedPortName m -> m #

foldMap :: Monoid m => (a -> m) -> ExpandedPortName a -> m #

foldMap' :: Monoid m => (a -> m) -> ExpandedPortName a -> m #

foldr :: (a -> b -> b) -> b -> ExpandedPortName a -> b #

foldr' :: (a -> b -> b) -> b -> ExpandedPortName a -> b #

foldl :: (b -> a -> b) -> b -> ExpandedPortName a -> b #

foldl' :: (b -> a -> b) -> b -> ExpandedPortName a -> b #

foldr1 :: (a -> a -> a) -> ExpandedPortName a -> a #

foldl1 :: (a -> a -> a) -> ExpandedPortName a -> a #

toList :: ExpandedPortName a -> [a] #

null :: ExpandedPortName a -> Bool #

length :: ExpandedPortName a -> Int #

elem :: Eq a => a -> ExpandedPortName a -> Bool #

maximum :: Ord a => ExpandedPortName a -> a #

minimum :: Ord a => ExpandedPortName a -> a #

sum :: Num a => ExpandedPortName a -> a #

product :: Num a => ExpandedPortName a -> a #

Traversable ExpandedPortName Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

traverse :: Applicative f => (a -> f b) -> ExpandedPortName a -> f (ExpandedPortName b) #

sequenceA :: Applicative f => ExpandedPortName (f a) -> f (ExpandedPortName a) #

mapM :: Monad m => (a -> m b) -> ExpandedPortName a -> m (ExpandedPortName b) #

sequence :: Monad m => ExpandedPortName (m a) -> m (ExpandedPortName a) #

Show a => Show (ExpandedPortName a) Source # 
Instance details

Defined in Clash.Netlist.Types

data ExpandedTopEntity a Source #

Same as TopEntity, but with all port names that end up in HDL specified

Constructors

ExpandedTopEntity 

Fields

Instances

Instances details
Functor ExpandedTopEntity Source # 
Instance details

Defined in Clash.Netlist.Types

Foldable ExpandedTopEntity Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

fold :: Monoid m => ExpandedTopEntity m -> m #

foldMap :: Monoid m => (a -> m) -> ExpandedTopEntity a -> m #

foldMap' :: Monoid m => (a -> m) -> ExpandedTopEntity a -> m #

foldr :: (a -> b -> b) -> b -> ExpandedTopEntity a -> b #

foldr' :: (a -> b -> b) -> b -> ExpandedTopEntity a -> b #

foldl :: (b -> a -> b) -> b -> ExpandedTopEntity a -> b #

foldl' :: (b -> a -> b) -> b -> ExpandedTopEntity a -> b #

foldr1 :: (a -> a -> a) -> ExpandedTopEntity a -> a #

foldl1 :: (a -> a -> a) -> ExpandedTopEntity a -> a #

toList :: ExpandedTopEntity a -> [a] #

null :: ExpandedTopEntity a -> Bool #

length :: ExpandedTopEntity a -> Int #

elem :: Eq a => a -> ExpandedTopEntity a -> Bool #

maximum :: Ord a => ExpandedTopEntity a -> a #

minimum :: Ord a => ExpandedTopEntity a -> a #

sum :: Num a => ExpandedTopEntity a -> a #

product :: Num a => ExpandedTopEntity a -> a #

Traversable ExpandedTopEntity Source # 
Instance details

Defined in Clash.Netlist.Types

Methods

traverse :: Applicative f => (a -> f b) -> ExpandedTopEntity a -> f (ExpandedTopEntity b) #

sequenceA :: Applicative f => ExpandedTopEntity (f a) -> f (ExpandedTopEntity a) #

mapM :: Monad m => (a -> m b) -> ExpandedTopEntity a -> m (ExpandedTopEntity b) #

sequence :: Monad m => ExpandedTopEntity (m a) -> m (ExpandedTopEntity a) #

Show a => Show (ExpandedTopEntity a) 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 

isBiDirectional :: (Identifier, HWType) -> Bool Source #

Check if an input port is really an inout port.

findClocks :: Component -> [(Text, Text)] Source #

Find the name and domain name of each clock argument of a component.

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 

netlistId1 Source #

Arguments

:: HasCallStack 
=> (Identifier -> r)

Eliminator for Identifiers generated in the NetlistMonad

-> (Id -> r)

Eliminator for original Core Identifiers

-> NetlistId 
-> r 

Eliminator for NetlistId, fails on MultiId

netlistTypes :: NetlistId -> [Type] Source #

Return the type(s) of a NetListId, returns multiple types when given a MultiId

netlistTypes1 :: HasCallStack => NetlistId -> Type Source #

Return the type of a NetlistId, fails on MultiId