Copyright | (C) 2012-2016 University of Twente 2016-2017 Myrtle Software Ltd 2017 Google Inc. 2021-2024 QBayLogic B.V. 2022 Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | None |
Language | Haskell2010 |
Functions to create BlackBox Contexts and fill in BlackBox templates
Synopsis
- warn :: ClashOpts -> String -> IO ()
- mkBlackBoxContext :: HasCallStack => Text -> [Id] -> [Either Term Type] -> NetlistMonad (BlackBoxContext, [Declaration])
- prepareBlackBox :: Text -> BlackBox -> BlackBoxContext -> NetlistMonad (BlackBox, [Declaration])
- isLiteral :: Term -> Bool
- mkArgument :: Text -> Identifier -> Int -> Term -> NetlistMonad ((Expr, HWType, Bool), [Declaration])
- extractPrimWarnOrFail :: HasCallStack => Text -> NetlistMonad CompiledPrimitive
- mkPrimitive :: Bool -> Bool -> DeclarationType -> NetlistId -> PrimInfo -> [Either Term Type] -> [Declaration] -> NetlistMonad (Expr, [Declaration])
- collectMealy :: HasCallStack => Identifier -> NetlistId -> TyConMap -> [Term] -> NetlistMonad [Declaration]
- collectBindIO :: NetlistId -> [Term] -> NetlistMonad (Expr, [Declaration])
- collectAppIO :: NetlistId -> [Term] -> [Term] -> NetlistMonad (Expr, [Declaration])
- unSimIO :: TyConMap -> Term -> Term
- mkFunInput :: HasCallStack => Text -> Id -> Term -> NetlistMonad ((Either BlackBox (Identifier, [Declaration]), Usage, [BlackBoxTemplate], [BlackBoxTemplate], [((Text, Text), BlackBox)], BlackBoxContext), [Declaration])
Documentation
:: HasCallStack | |
=> Text | Blackbox function name |
-> [Id] | Identifiers binding the primitive/blackbox application |
-> [Either Term Type] | Arguments of the primitive/blackbox application |
-> NetlistMonad (BlackBoxContext, [Declaration]) |
Generate the context for a BlackBox instantiation.
prepareBlackBox :: Text -> BlackBox -> BlackBoxContext -> NetlistMonad (BlackBox, [Declaration]) Source #
:: Text | Blackbox function name |
-> Identifier | LHS of the original let-binder. Is used as a name hint to generate new names in case the argument is a declaration. |
-> Int | Argument n (zero-indexed). Used for error message. |
-> Term | |
-> NetlistMonad ((Expr, HWType, Bool), [Declaration]) |
extractPrimWarnOrFail Source #
:: HasCallStack | |
=> Text | Name of primitive |
-> NetlistMonad CompiledPrimitive |
Extract a compiled primitive from a guarded primitive. Emit a warning if the guard wants to, or fail entirely.
:: Bool | Put BlackBox expression in parenthesis |
-> Bool | Treat BlackBox expression as declaration |
-> DeclarationType | Are we concurrent or sequential? |
-> NetlistId | Id to assign the result to |
-> PrimInfo | Primitive info |
-> [Either Term Type] | Arguments |
-> [Declaration] | Tick declarations |
-> NetlistMonad (Expr, [Declaration]) |
:: HasCallStack | |
=> Identifier | Identifier to assign the final result to |
-> NetlistId | Id to assign the final result to |
-> TyConMap | |
-> [Term] | The arguments to |
-> NetlistMonad [Declaration] |
Turn a mealyIO
expression into a two sequential processes, one "initial"
process for the starting state, and one clocked sequential process.
collectBindIO :: NetlistId -> [Term] -> NetlistMonad (Expr, [Declaration]) Source #
Collect the sequential declarations for bindIO
collectAppIO :: NetlistId -> [Term] -> [Term] -> NetlistMonad (Expr, [Declaration]) Source #
Collect the sequential declarations for appIO
unSimIO :: TyConMap -> Term -> Term Source #
Unwrap the new-type wrapper for things of type SimIO, this is needed to allow applications of the `State# World` token to the underlying IO type.
XXX: this is most likely needed because Ghc2Core that threw away the cast that this unwrapping; we should really start to support casts.
:: HasCallStack | |
=> Text | Name of the primitive of which the function in question is an argument. Used for error reporting. |
-> Id | Identifier binding the encompassing primitive/blackbox application. Used
as a name hint if |
-> Term | The function argument term |
-> NetlistMonad ((Either BlackBox (Identifier, [Declaration]), Usage, [BlackBoxTemplate], [BlackBoxTemplate], [((Text, Text), BlackBox)], BlackBoxContext), [Declaration]) |
Create an template instantiation text and a partial blackbox content for an argument term, given that the term is a function. Errors if the term is not a function