clash-lib-1.4.0: Clash: a functional hardware description language - As a library
Copyright(C) 2019 Myrtle Software Ltd.
2020 QBayLogic B.V.
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Primitives.DSL

Description

This module contains a mini dsl for creating haskell blackbox instantiations.

Synopsis

Annotations

data BlackBoxHaskellOpts Source #

Options for blackBoxHaskell function. Use def from package 'data-default' for a set of default options.

Constructors

BlackBoxHaskellOpts 

Fields

Instances

Instances details
Default BlackBoxHaskellOpts Source # 
Instance details

Defined in Clash.Primitives.DSL

blackBoxHaskell Source #

Arguments

:: Name

blackbox name

-> Name

template function name

-> BlackBoxHaskellOpts

Options, see data structure for more information

-> Primitive 

Create a blackBoxHaskell primitive. To be used as part of an annotation:

{--}
2,3
would mean this blackbox ignores its second and third argument.

declarations

data BlockState backend Source #

The state of a block. Contains a list of declarations and a the backend state.

Constructors

BlockState 

Fields

Instances

Instances details
Backend backend => HasIdentifierSet (BlockState backend) Source # 
Instance details

Defined in Clash.Primitives.DSL

data TExpr Source #

A typed expression.

Instances

Instances details
Show TExpr Source # 
Instance details

Defined in Clash.Primitives.DSL

Methods

showsPrec :: Int -> TExpr -> ShowS #

show :: TExpr -> String #

showList :: [TExpr] -> ShowS #

declaration Source #

Arguments

:: Backend backend 
=> Text

block name

-> State (BlockState backend) ()

block builder

-> State backend Doc

pretty printed block

Run a block declaration.

declarationReturn Source #

Arguments

:: Backend backend 
=> BlackBoxContext 
-> Text

block name

-> State (BlockState backend) [TExpr]

block builder yielding an expression that should be assigned to the result variable in the blackbox context

-> State backend Doc

pretty printed block

Run a block declaration. Assign the result of the block builder to the result variable in the given blackbox context.

instDecl Source #

Arguments

:: forall backend. Backend backend 
=> EntityOrComponent

Type of instantiation

-> Identifier

component/entity name

-> Identifier

instantiation label

-> [(Text, LitHDL)]

attributes

-> [(Text, TExpr)]

in ports

-> [(Text, TExpr)]

out ports

-> State (BlockState backend) () 

Instantiate a component/entity in a block state.

instHO Source #

Arguments

:: Backend backend 
=> BlackBoxContext

BlackBoxContext, used for rendering higher-order function and error reporting

-> Int

Position of HO-argument. For example:

fold :: forall n a . (a -> a -> a) -> Vec (n + 1) a -> a

would have its HO-argument at position 0, while

iterateI :: forall n a. KnownNat n => (a -> a) -> a -> Vec n a

would have it at position 1.

-> (HWType, BlackBoxTemplate)

Result type of HO function

-> [(TExpr, BlackBoxTemplate)]

Arguments and their types

-> State (BlockState backend) TExpr

Result of the function

Instantiate/call a higher-order function.

viaAnnotatedSignal Source #

Arguments

:: (HasCallStack, Backend backend) 
=> Identifier

Name given to signal

-> TExpr

expression the signal is assigned to

-> TExpr

expression (must be identifier) to which the signal is assigned

-> [Attr']

the attributes to annotate the signal with

-> State (BlockState backend) () 

Wires the two given TExprs together using a newly declared signal with (exactly) the given name sigNm. The new signal has an annotated type, using the given attributes.

Literals

bvLit Source #

Arguments

:: Int

BitVector size

-> Integer

Literal

-> TExpr 

Construct a fully defined BitVector literal

data LitHDL Source #

A literal that can be used for hdl attributes. It has a Num and IsString instances for convenience.

Constructors

B Bool 
S String 
I Integer 

Instances

Instances details
Num LitHDL Source # 
Instance details

Defined in Clash.Primitives.DSL

Show LitHDL Source # 
Instance details

Defined in Clash.Primitives.DSL

IsString LitHDL Source # 
Instance details

Defined in Clash.Primitives.DSL

Methods

fromString :: String -> LitHDL #

pattern High :: TExpr Source #

The high literal bit.

pattern Low :: TExpr Source #

The low literal bit.

constructProduct :: HWType -> [TExpr] -> TExpr Source #

Construct a product type given its type and fields

tuple :: [TExpr] -> TExpr Source #

Create an n-tuple of TExpr

vec Source #

Arguments

:: (HasCallStack, Backend backend) 
=> [TExpr]

Elements of vector

-> State (BlockState backend) TExpr

Vector elements

Create a vector of TExprs

Extraction

tInputs :: BlackBoxContext -> [(TExpr, HWType)] Source #

The TExp inputs from a blackbox context.

tResults :: BlackBoxContext -> [TExpr] Source #

The TExp result of a blackbox context.

getStr :: TExpr -> Maybe String Source #

Try to get the literal string value of an expression.

getBool :: TExpr -> Maybe Bool Source #

Try to get the literal bool value of an expression.

tExprToInteger :: TExpr -> Maybe Integer Source #

Try to get the literal nat value of an expression.

deconstructProduct Source #

Arguments

:: (HasCallStack, Backend backend) 
=> TExpr

Product expression

-> [Text]

Name hints for element assignments

-> State (BlockState backend) [TExpr] 

Extract the fields of a product type and return expressions to them. These new expressions are given unique names and get declared in the block scope.

untuple Source #

Arguments

:: (HasCallStack, Backend backend) 
=> TExpr

Tuple expression

-> [Text]

Name hints for element assignments

-> State (BlockState backend) [TExpr] 

Extract the elements of a tuple expression and return expressions to them. These new expressions are given unique names and get declared in the block scope.

unvec Source #

Arguments

:: Backend backend 
=> Text

Name hint for intermediate signal

-> TExpr

Vector expression

-> State (BlockState backend) [TExpr]

Vector elements

Extract the elements of a vector expression and return expressions to them. If given expression is not an identifier, an intermediate variable will be used to assign the given expression to which is subsequently indexed.

Conversion

toBV Source #

Arguments

:: Backend backend 
=> Text

BitVector name hint

-> TExpr

expression

-> State (BlockState backend) TExpr

BitVector expression

Assign an input bitvector to an expression. Declares a new bitvector if the expression is not already a bitvector.

fromBV Source #

Arguments

:: (HasCallStack, Backend backend) 
=> Text

BitVector name hint

-> TExpr

expression

-> State (BlockState backend) TExpr

bv expression

Assign an output bitvector to an expression. Declares a new bitvector if the expression is not already a bitvector.

boolToBit Source #

Arguments

:: (HasCallStack, Backend backend) 
=> Text

Name hint for intermediate signal

-> TExpr 
-> State (BlockState backend) TExpr 

Convert a bool to a bit.

boolFromBit Source #

Arguments

:: Text

Name hint for intermediate signal

-> TExpr 
-> State (BlockState VHDLState) TExpr 

Use to create an output Bool from a Bit. The expression given must be the identifier of the bool you wish to get assigned. Returns a reference to a declared Bit that should get assigned by something (usually the output port of an entity).

boolFromBitVector Source #

Arguments

:: Size 
-> Text

Name hint for intermediate signal

-> TExpr 
-> State (BlockState VHDLState) TExpr 

Used to create an output Bool from a BitVector of given size. Works in a similar way to boolFromBit above.

TODO: Implement for (System)Verilog

unsignedFromBitVector Source #

Arguments

:: Size 
-> Text

Name hint for intermediate signal

-> TExpr 
-> State (BlockState VHDLState) TExpr 

Used to create an output Unsigned from a BitVector of given size. Works in a similar way to boolFromBit above.

TODO: Implement for (System)Verilog

boolFromBits :: [Text] -> TExpr -> State (BlockState VHDLState) [TExpr] Source #

Used to create an output Bool from a number of Bits, using conjunction. Similarly to untuple, it returns a list of references to declared values (the inputs to the function) which should get assigned by something---usually output ports of an entity.

TODO: Implement for (System)Verilog

Operations

andExpr Source #

Arguments

:: Backend backend 
=> Text

name hint

-> TExpr

a

-> TExpr

a

-> State (BlockState backend) TExpr

a && b

And together (&&) two expressions, assigning it to a new identifier.

notExpr Source #

Arguments

:: Backend backend 
=> Text

name hint

-> TExpr

a

-> State (BlockState backend) TExpr

not a

Negate (not) an expression, assigning it to a new identifier.

pureToBV Source #

Arguments

:: Text

name hint

-> Int

Size (n)

-> TExpr

ARG

-> State (BlockState VHDLState) TExpr

(0 to n => ARG)

Creates a BV that produces the following vhdl:

   (0 to n => ARG)

TODO: Implement for (System)Verilog

pureToBVResized Source #

Arguments

:: Text

name hint

-> Int

Size (n)

-> TExpr

ARG

-> State (BlockState VHDLState) TExpr

std_logic_vector(resize(ARG, Size))

Creates a BV that produces the following vhdl:

   std_logic_vector(resize(ARG, Size))

TODO: Implement for (System)Verilog

open :: Backend backend => HWType -> State (BlockState backend) TExpr Source #

Allows assignment of a port to be "open"

Utilities

toIdentifier Source #

Arguments

:: Backend backend 
=> Text

desired new identifier name, will be made unique

-> TExpr

expression to get identifier of

-> State (BlockState backend) TExpr

identifier to expression

Get an identifier to an expression, creating a new assignment if necessary.

tySize :: Num i => HWType -> i Source #

clog2 :: Num i => Integer -> i Source #