Copyright | (C) 2012-2016 University of Twente 2016-2017 Myrtle Software Ltd 2021-2023 QBayLogic B.V. 2022 LUMI GUIDE FIETSDETECTIE B.V. 2022 Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Clash.Netlist.BlackBox.Util
Description
Utilties to verify blackbox contexts against templates and rendering filled in templates
Synopsis
- renderTemplate :: Backend backend => BlackBoxContext -> BlackBoxTemplate -> State backend (Int -> Text)
- walkElement :: (Element -> Maybe a) -> Element -> [a]
- verifyBlackBoxContext :: BlackBoxContext -> BlackBox -> Maybe String
- onBlackBox :: (BlackBoxTemplate -> r) -> (BBName -> BBHash -> TemplateFunction -> r) -> BlackBox -> r
- setSym :: forall m. IdentifierSetMonad m => BlackBoxContext -> BlackBoxTemplate -> m (BlackBoxTemplate, [Declaration])
- extractLiterals :: BlackBoxContext -> [Expr]
- renderBlackBox :: Backend backend => [BlackBoxTemplate] -> [BlackBoxTemplate] -> [((Text, Text), BlackBox)] -> BlackBox -> BlackBoxContext -> State backend (Int -> Doc)
- getUsedArguments :: BlackBox -> [Int]
- renderFilePath :: [(String, FilePath)] -> String -> ([(String, FilePath)], String)
- exprToString :: Expr -> Maybe String
- renderElem :: HasCallStack => Backend backend => BlackBoxContext -> Element -> State backend (Int -> Text)
- getDomainConf :: (Backend backend, HasCallStack) => HWType -> State backend VDomainConfiguration
- prettyBlackBox :: Monad m => BlackBoxTemplate -> Ap m Text
Documentation
Arguments
:: Backend backend | |
=> BlackBoxContext | Context used to fill in the hole |
-> BlackBoxTemplate | Blackbox template |
-> State backend (Int -> Text) |
Render a blackbox given a certain context. Returns a filled out template
and a list of hidden
inputs that must be added to the encompassing component.
walkElement :: (Element -> Maybe a) -> Element -> [a] Source #
Recursively walk Element
, applying f
to each element in the tree.
verifyBlackBoxContext Source #
Arguments
:: BlackBoxContext | Blackbox to verify |
-> BlackBox | Template to check against |
-> Maybe String |
Determine if the number of normal/literal/function inputs of a blackbox context at least matches the number of argument that is expected by the template.
onBlackBox :: (BlackBoxTemplate -> r) -> (BBName -> BBHash -> TemplateFunction -> r) -> BlackBox -> r Source #
setSym :: forall m. IdentifierSetMonad m => BlackBoxContext -> BlackBoxTemplate -> m (BlackBoxTemplate, [Declaration]) Source #
Update all the symbol references in a template, and increment the symbol counter for every newly encountered symbol.
extractLiterals :: BlackBoxContext -> [Expr] Source #
renderBlackBox :: Backend backend => [BlackBoxTemplate] -> [BlackBoxTemplate] -> [((Text, Text), BlackBox)] -> BlackBox -> BlackBoxContext -> State backend (Int -> Doc) Source #
getUsedArguments :: BlackBox -> [Int] Source #
Collect arguments (e.g., ~ARG, ~LIT) used in this blackbox
renderElem :: HasCallStack => Backend backend => BlackBoxContext -> Element -> State backend (Int -> Text) Source #
Render a single template element
getDomainConf :: (Backend backend, HasCallStack) => HWType -> State backend VDomainConfiguration Source #
prettyBlackBox :: Monad m => BlackBoxTemplate -> Ap m Text Source #