Copyright | (C) 2019 Myrtle Software Ltd. 2020-2022 QBayLogic B.V. 2021 Myrtle.ai |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | None |
Language | Haskell2010 |
This module contains a mini dsl for creating haskell blackbox instantiations.
Synopsis
- data BlackBoxHaskellOpts = BlackBoxHaskellOpts {
- bo_ignoredArguments :: [Int]
- bo_supportedHdls :: [HDL]
- bo_multiResult :: Bool
- blackBoxHaskell :: Name -> Name -> BlackBoxHaskellOpts -> Primitive
- data BlockState backend = BlockState {
- _bsDeclarations :: [Declaration]
- _bsHigherOrderCalls :: IntMap Int
- _bsBackend :: backend
- data TExpr
- declaration :: Backend backend => Text -> State (BlockState backend) () -> State backend Doc
- declarationReturn :: Backend backend => BlackBoxContext -> Text -> State (BlockState backend) [TExpr] -> State backend Doc
- instDecl :: forall backend. Backend backend => EntityOrComponent -> Identifier -> Identifier -> [(Text, LitHDL)] -> [(Text, TExpr)] -> [(Text, TExpr)] -> State (BlockState backend) ()
- instHO :: Backend backend => BlackBoxContext -> Int -> (HWType, BlackBoxTemplate) -> [(TExpr, BlackBoxTemplate)] -> State (BlockState backend) TExpr
- viaAnnotatedSignal :: (HasCallStack, Backend backend) => Identifier -> TExpr -> TExpr -> [Attr'] -> State (BlockState backend) ()
- bvLit :: Int -> Integer -> TExpr
- data LitHDL
- pattern High :: TExpr
- pattern Low :: TExpr
- constructProduct :: HWType -> [TExpr] -> TExpr
- tuple :: HasCallStack => [TExpr] -> TExpr
- vec :: (HasCallStack, Backend backend) => [TExpr] -> State (BlockState backend) TExpr
- tInputs :: BlackBoxContext -> [(TExpr, HWType)]
- tResults :: BlackBoxContext -> [TExpr]
- getStr :: TExpr -> Maybe String
- getBool :: TExpr -> Maybe Bool
- exprToInteger :: Expr -> Maybe Integer
- tExprToInteger :: TExpr -> Maybe Integer
- deconstructProduct :: (HasCallStack, Backend backend) => TExpr -> [Text] -> State (BlockState backend) [TExpr]
- untuple :: (HasCallStack, Backend backend) => TExpr -> [Text] -> State (BlockState backend) [TExpr]
- unvec :: (HasCallStack, Backend backend) => Text -> TExpr -> State (BlockState backend) [TExpr]
- toBV :: Backend backend => Text -> TExpr -> State (BlockState backend) TExpr
- fromBV :: (HasCallStack, Backend backend) => Text -> TExpr -> State (BlockState backend) TExpr
- enableToBit :: (HasCallStack, Backend backend) => Text -> TExpr -> State (BlockState backend) TExpr
- boolToBit :: (HasCallStack, Backend backend) => Text -> TExpr -> State (BlockState backend) TExpr
- boolFromBit :: Text -> TExpr -> State (BlockState VHDLState) TExpr
- boolFromBitVector :: Size -> Text -> TExpr -> State (BlockState VHDLState) TExpr
- unsignedFromBitVector :: HasCallStack => Size -> Text -> TExpr -> State (BlockState VHDLState) TExpr
- boolFromBits :: [Text] -> TExpr -> State (BlockState VHDLState) [TExpr]
- andExpr :: Backend backend => Text -> TExpr -> TExpr -> State (BlockState backend) TExpr
- notExpr :: Backend backend => Text -> TExpr -> State (BlockState backend) TExpr
- pureToBV :: Text -> Int -> TExpr -> State (BlockState VHDLState) TExpr
- pureToBVResized :: Text -> Int -> TExpr -> State (BlockState VHDLState) TExpr
- open :: Backend backend => HWType -> State (BlockState backend) TExpr
- toIdentifier :: Backend backend => Text -> TExpr -> State (BlockState backend) TExpr
- tySize :: Num i => HWType -> i
- clog2 :: Num i => Integer -> i
Annotations
data BlackBoxHaskellOpts Source #
Options for blackBoxHaskell
function. Use def
from package
'data-default' for a set of default options.
BlackBoxHaskellOpts | |
|
Instances
Default BlackBoxHaskellOpts Source # | |
Defined in Clash.Primitives.DSL |
:: 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:
{-# ANN myFunction (blackBoxHaskell 'myFunction 'myBBF def{_ignoredArguments=[1,2]}) #-}
[1,2]
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.
BlockState | |
|
Instances
Backend backend => HasIdentifierSet (BlockState backend) Source # | |
Defined in Clash.Primitives.DSL identifierSet :: Lens' (BlockState backend) IdentifierSet Source # |
A typed expression.
:: Backend backend | |
=> Text | block name |
-> State (BlockState backend) () | block builder |
-> State backend Doc | pretty printed block |
Run a block declaration.
:: 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.
:: 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.
:: 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.
:: (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 TExpr
s together using a newly declared
signal with (exactly) the given name sigNm
. The new signal has an
annotated type, using the given attributes.
Literals
Construct a fully defined BitVector literal
constructProduct :: HWType -> [TExpr] -> TExpr Source #
Construct a product type given its type and fields
:: (HasCallStack, Backend backend) | |
=> [TExpr] | Elements of vector |
-> State (BlockState backend) TExpr | Vector elements |
Create a vector of TExpr
s
Extraction
tResults :: BlackBoxContext -> [TExpr] Source #
The TExp result of a blackbox context.
:: (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.
:: (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.
:: (HasCallStack, 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
:: 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.
:: (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.
:: (HasCallStack, Backend backend) | |
=> Text | Name hint for intermediate signal |
-> TExpr | |
-> State (BlockState backend) TExpr |
Convert an enable to a bit.
:: (HasCallStack, Backend backend) | |
=> Text | Name hint for intermediate signal |
-> TExpr | |
-> State (BlockState backend) TExpr |
Convert a bool to a bit.
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 #
:: HasCallStack | |
=> 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 #
Operations
And together (&&)
two expressions, assigning it to a new identifier.
Negate (not)
an expression, assigning it to a new identifier.
Creates a BV that produces the following vhdl:
(0 to n => ARG)
TODO: Implement for (System)Verilog
:: 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"