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 | None |
Language | Haskell2010 |
Utilties to verify blackbox contexts against templates and rendering filled in templates
Synopsis
- inputHole :: Element -> Maybe Int
- verifyBlackBoxContext :: BlackBoxContext -> BlackBox -> Maybe String
- extractLiterals :: BlackBoxContext -> [Expr]
- setSym :: forall m. IdentifierSetMonad m => BlackBoxContext -> BlackBoxTemplate -> m (BlackBoxTemplate, [Declaration])
- selectNewName :: Foldable t => t String -> FilePath -> String
- renderFilePath :: [(String, FilePath)] -> String -> ([(String, FilePath)], String)
- renderTemplate :: Backend backend => BlackBoxContext -> BlackBoxTemplate -> State backend (Int -> Text)
- renderBlackBox :: Backend backend => [BlackBoxTemplate] -> [BlackBoxTemplate] -> [((Text, Text), BlackBox)] -> BlackBox -> BlackBoxContext -> State backend (Int -> Doc)
- renderElem :: HasCallStack => Backend backend => BlackBoxContext -> Element -> State backend (Int -> Text)
- getDomainConf :: (Backend backend, HasCallStack) => HWType -> State backend VDomainConfiguration
- generalGetDomainConf :: forall m. (Monad m, HasCallStack) => m DomainMap -> HWType -> m VDomainConfiguration
- parseFail :: Text -> BlackBoxTemplate
- idToExpr :: (Text, HWType) -> (Expr, HWType, Bool)
- bbResult :: HasCallStack => String -> BlackBoxContext -> (Expr, HWType)
- lineToIdentifier :: Backend backend => BlackBoxContext -> BlackBoxTemplate -> State backend Text
- lineToType :: BlackBoxContext -> BlackBoxTemplate -> HWType
- renderTag :: Backend backend => BlackBoxContext -> Element -> State backend Text
- elementsToText :: BlackBoxContext -> [Element] -> Either String Text
- elementToText :: BlackBoxContext -> Element -> Either String Text
- exprToString :: Expr -> Maybe String
- prettyBlackBox :: Monad m => BlackBoxTemplate -> Ap m Text
- prettyElem :: (HasCallStack, Monad m) => Element -> Ap m Text
- walkElement :: (Element -> Maybe a) -> Element -> [a]
- usedVariables :: Expr -> [IdentifierText]
- getUsedArguments :: BlackBox -> [Int]
- onBlackBox :: (BlackBoxTemplate -> r) -> (BBName -> BBHash -> TemplateFunction -> r) -> BlackBox -> r
- checkUndefined :: Expr -> Bool
Documentation
verifyBlackBoxContext Source #
:: BlackBoxContext | Blackbox to verify |
-> BlackBox | Template to check against |
-> Maybe String |
Determine if the number of normalliteralfunction inputs of a blackbox context at least matches the number of argument that is expected by the template.
extractLiterals :: BlackBoxContext -> [Expr] 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.
:: 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.
renderBlackBox :: Backend backend => [BlackBoxTemplate] -> [BlackBoxTemplate] -> [((Text, Text), BlackBox)] -> BlackBox -> BlackBoxContext -> State backend (Int -> Doc) Source #
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 #
:: forall m. (Monad m, HasCallStack) | |
=> m DomainMap | a way to get the |
-> HWType | |
-> m VDomainConfiguration |
parseFail :: Text -> BlackBoxTemplate Source #
bbResult :: HasCallStack => String -> BlackBoxContext -> (Expr, HWType) Source #
lineToIdentifier :: Backend backend => BlackBoxContext -> BlackBoxTemplate -> State backend Text Source #
Fill out the template corresponding to an output/input assignment of a component instantiation, and turn it into a single identifier so it can be used for a new blackbox context.
lineToType :: BlackBoxContext -> BlackBoxTemplate -> HWType Source #
renderTag :: Backend backend => BlackBoxContext -> Element -> State backend Text Source #
Give a context and a tagged hole (of a template), returns part of the context that matches the tag of the hole.
elementsToText :: BlackBoxContext -> [Element] -> Either String Text Source #
Compute string from a list of elements. Can interpret ~NAME string literals on template level (constants).
elementToText :: BlackBoxContext -> Element -> Either String Text Source #
prettyBlackBox :: Monad m => BlackBoxTemplate -> Ap m Text Source #
prettyElem :: (HasCallStack, Monad m) => Element -> Ap m Text Source #
walkElement :: (Element -> Maybe a) -> Element -> [a] Source #
Recursively walk Element
, applying f
to each element in the tree.
usedVariables :: Expr -> [IdentifierText] Source #
Determine variables used in an expression. Used for VHDL sensitivity list. Also see: https://github.com/clash-lang/clash-compiler/issues/365
getUsedArguments :: BlackBox -> [Int] Source #
Collect arguments (e.g., ~ARG, ~LIT) used in this blackbox
onBlackBox :: (BlackBoxTemplate -> r) -> (BBName -> BBHash -> TemplateFunction -> r) -> BlackBox -> r Source #