Copyright | (C) 2019 Myrtle Software Ltd. 2020 QBayLogic B.V. |
---|---|
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
- blackBoxHaskell :: [Int] -> HDL -> Name -> Name -> Primitive
- data BlockState backend = BlockState {
- _bsDeclarations :: [Declaration]
- _bsBackend :: backend
- data TExpr
- declaration :: Backend backend => Text -> State (BlockState backend) () -> State backend Doc
- instDecl :: Backend backend => EntityOrComponent -> Identifier -> Identifier -> [(Text, LitHDL)] -> [(Text, TExpr)] -> [(Text, TExpr)] -> State (BlockState backend) ()
- viaAnnotatedSignal :: (HasCallStack, Backend backend) => Text -> TExpr -> TExpr -> [Attr'] -> State (BlockState backend) ()
- bvLit :: Int -> Integer -> TExpr
- data LitHDL
- pattern High :: TExpr
- pattern Low :: TExpr
- tuple :: [TExpr] -> TExpr
- vec :: (HasCallStack, Backend backend) => [TExpr] -> State (BlockState backend) TExpr
- tInputs :: BlackBoxContext -> [(TExpr, HWType)]
- tResult :: BlackBoxContext -> TExpr
- getStr :: TExpr -> Maybe String
- getBool :: TExpr -> Maybe Bool
- exprToInteger :: Expr -> Maybe Integer
- tExprToInteger :: TExpr -> Maybe Integer
- untuple :: (HasCallStack, Backend backend) => TExpr -> [Identifier] -> State (BlockState backend) [TExpr]
- unvec :: Backend backend => Identifier -> TExpr -> State (BlockState backend) [TExpr]
- toBV :: Backend backend => Identifier -> TExpr -> State (BlockState backend) TExpr
- fromBV :: (HasCallStack, Backend backend) => Identifier -> TExpr -> State (BlockState backend) TExpr
- boolToBit :: (HasCallStack, Backend backend) => Identifier -> TExpr -> State (BlockState backend) TExpr
- boolFromBit :: Backend backend => Identifier -> TExpr -> State (BlockState backend) TExpr
- boolFromBitVector :: Backend backend => Size -> Identifier -> TExpr -> State (BlockState backend) TExpr
- unsignedFromBitVector :: Size -> Identifier -> TExpr -> State (BlockState VHDLState) TExpr
- boolFromBits :: [Identifier] -> TExpr -> State (BlockState VHDLState) [TExpr]
- andExpr :: Backend backend => Identifier -> TExpr -> TExpr -> State (BlockState backend) TExpr
- notExpr :: Backend backend => Identifier -> TExpr -> State (BlockState backend) TExpr
- pureToBV :: Identifier -> Int -> TExpr -> State (BlockState VHDLState) TExpr
- pureToBVResized :: Identifier -> Int -> TExpr -> State (BlockState VHDLState) TExpr
- open :: Backend backend => HWType -> State (BlockState backend) TExpr
- toIdentifier :: Backend backend => Identifier -> TExpr -> State (BlockState backend) TExpr
- tySize :: Num i => HWType -> i
- clog2 :: Num i => Integer -> i
Annotations
declarations
data BlockState backend Source #
The state of a block. Contains a list of declarations and a the backend state.
BlockState | |
|
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 | |
=> 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.
:: (HasCallStack, Backend backend) | |
=> Text | 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
:: (HasCallStack, Backend backend) | |
=> [TExpr] | Elements of vector |
-> State (BlockState backend) TExpr | Vector elements |
Create a vector of TExpr
s
Extraction
tResult :: BlackBoxContext -> TExpr Source #
The TExp result of a blackbox context.
:: (HasCallStack, Backend backend) | |
=> TExpr | Tuple expression |
-> [Identifier] | 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 the block scope.
:: Backend backend | |
=> Identifier | 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 | |
=> Identifier | BitVector name |
-> 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) | |
=> Identifier | BitVector name |
-> 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) | |
=> Identifier | Name hint for intermediate signal |
-> TExpr | |
-> State (BlockState backend) TExpr |
Convert a bool to a bit.
:: Backend backend | |
=> Identifier | Name hint for intermediate signal |
-> TExpr | |
-> State (BlockState backend) TExpr |
:: Backend backend | |
=> Size | |
-> Identifier | Name hint for intermediate signal |
-> TExpr | |
-> State (BlockState backend) TExpr |
Used to create an output Bool
from a BitVector
of given size.
Works in a similar way to boolFromBit
above.
unsignedFromBitVector Source #
:: Size | |
-> Identifier | 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 :: [Identifier] -> TExpr -> State (BlockState VHDLState) [TExpr] Source #
Operations
:: Backend backend | |
=> Identifier | name hint |
-> TExpr | a |
-> TExpr | a |
-> State (BlockState backend) TExpr | a && b |
And together (&&)
two expressions, assigning it to a new identifier.
:: Backend backend | |
=> Identifier | name hint |
-> TExpr | a |
-> State (BlockState backend) TExpr | not a |
Negate (not)
an expression, assigning it to a new identifier.
:: Identifier | 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
:: Identifier | 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
:: Backend backend | |
=> Identifier | 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.