| Copyright | (C) 2015-2016 University of Twente 2017 Myrtle Software Ltd Google Inc. 2021-2022 QBayLogic B.V. | 
|---|---|
| License | BSD2 (see the file LICENSE) | 
| Maintainer | QBayLogic B.V. <devops@qbaylogic.com> | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Clash.Backend
Description
Synopsis
- primsRoot :: IO FilePath
- clashVer :: String
- type ModName = Text
- data Usage
- newtype AggressiveXOptBB = AggressiveXOptBB Bool
- newtype RenderEnums = RenderEnums Bool
- data HWKind
- type DomainMap = HashMap Text VDomainConfiguration
- emptyDomainMap :: DomainMap
- class HasIdentifierSet state => Backend state where- initBackend :: ClashOpts -> state
- hdlKind :: state -> HDL
- primDirs :: state -> IO [FilePath]
- name :: state -> String
- extension :: state -> String
- extractTypes :: state -> HashSet HWType
- genHDL :: ModName -> SrcSpan -> IdentifierSet -> Component -> Ap (State state) ((String, Doc), [(String, Doc)])
- mkTyPackage :: ModName -> [HWType] -> Ap (State state) [(String, Doc)]
- hdlType :: Usage -> HWType -> Ap (State state) Doc
- hdlHWTypeKind :: HWType -> State state HWKind
- hdlTypeErrValue :: HWType -> Ap (State state) Doc
- hdlTypeMark :: HWType -> Ap (State state) Doc
- hdlRecSel :: HWType -> Int -> Ap (State state) Doc
- hdlSig :: Text -> HWType -> Ap (State state) Doc
- genStmt :: Bool -> State state Doc
- inst :: Declaration -> Ap (State state) (Maybe Doc)
- expr :: Bool -> Expr -> Ap (State state) Doc
- iwWidth :: State state Int
- toBV :: HWType -> Text -> Ap (State state) Doc
- fromBV :: HWType -> Text -> Ap (State state) Doc
- hdlSyn :: State state HdlSyn
- setModName :: ModName -> state -> state
- setSrcSpan :: SrcSpan -> State state ()
- getSrcSpan :: State state SrcSpan
- blockDecl :: Identifier -> [Declaration] -> Ap (State state) Doc
- addIncludes :: [(String, Doc)] -> State state ()
- addLibraries :: [Text] -> State state ()
- addImports :: [Text] -> State state ()
- addAndSetData :: FilePath -> State state String
- getDataFiles :: State state [(String, FilePath)]
- addMemoryDataFile :: (String, String) -> State state ()
- getMemoryDataFiles :: State state [(String, String)]
- ifThenElseExpr :: state -> Bool
- aggressiveXOptBB :: State state AggressiveXOptBB
- renderEnums :: State state RenderEnums
- domainConfigurations :: State state DomainMap
- setDomainConfigurations :: DomainMap -> state -> state
 
Documentation
Is a type used for internal or external use
newtype AggressiveXOptBB Source #
Is '-fclash-aggresive-x-optimization-blackbox' set?
Constructors
| AggressiveXOptBB Bool | 
Kind of a HDL type. Used to determine whether types need conversions in order to cross top entity boundaries.
Constructors
| PrimitiveType | A type defined in an HDL spec. Usually types such as: bool, bit, .. | 
| SynonymType | A user defined type that's simply a synonym for another type, very much like a type synonym in Haskell. As long as two synonym types refer to the same type, they can be used interchangeably. E.g., a subtype in VHDL. | 
| UserType | User defined type that's not interchangeable with any others, even if the underlying structures are the same. Similar to an ADT in Haskell. | 
class HasIdentifierSet state => Backend state where Source #
Methods
initBackend :: ClashOpts -> state Source #
Initial state for state monad
hdlKind :: state -> HDL Source #
What HDL is the backend generating
primDirs :: state -> IO [FilePath] Source #
Location for the primitive definitions
name :: state -> String Source #
Name of backend, used for directory to put output files in. Should be constant function / ignore argument.
extension :: state -> String Source #
File extension for target langauge
extractTypes :: state -> HashSet HWType Source #
Get the set of types out of state
genHDL :: ModName -> SrcSpan -> IdentifierSet -> Component -> Ap (State state) ((String, Doc), [(String, Doc)]) Source #
Generate HDL for a Netlist component
mkTyPackage :: ModName -> [HWType] -> Ap (State state) [(String, Doc)] Source #
Generate a HDL package containing type definitions for the given HWTypes
hdlType :: Usage -> HWType -> Ap (State state) Doc Source #
Convert a Netlist HWType to a target HDL type
hdlHWTypeKind :: HWType -> State state HWKind Source #
Query what kind of type a given HDL type is
hdlTypeErrValue :: HWType -> Ap (State state) Doc Source #
Convert a Netlist HWType to an HDL error value for that type
hdlTypeMark :: HWType -> Ap (State state) Doc Source #
Convert a Netlist HWType to the root of a target HDL type
hdlRecSel :: HWType -> Int -> Ap (State state) Doc Source #
Create a record selector
hdlSig :: Text -> HWType -> Ap (State state) Doc Source #
Create a signal declaration from an identifier (Text) and Netlist HWType
genStmt :: Bool -> State state Doc Source #
Create a generative block statement marker
inst :: Declaration -> Ap (State state) (Maybe Doc) Source #
Turn a Netlist Declaration to a HDL concurrent block
Turn a Netlist expression into a HDL expression
iwWidth :: State state Int Source #
Bit-width of Int,Word,Integer
toBV :: HWType -> Text -> Ap (State state) Doc Source #
Convert to a bit-vector
fromBV :: HWType -> Text -> Ap (State state) Doc Source #
Convert from a bit-vector
hdlSyn :: State state HdlSyn Source #
Synthesis tool we're generating HDL for
setModName :: ModName -> state -> state Source #
setModName
setSrcSpan :: SrcSpan -> State state () Source #
setSrcSpan
getSrcSpan :: State state SrcSpan Source #
getSrcSpan
blockDecl :: Identifier -> [Declaration] -> Ap (State state) Doc Source #
Block of declarations
addIncludes :: [(String, Doc)] -> State state () Source #
addLibraries :: [Text] -> State state () Source #
addImports :: [Text] -> State state () Source #
addAndSetData :: FilePath -> State state String Source #
getDataFiles :: State state [(String, FilePath)] Source #
addMemoryDataFile :: (String, String) -> State state () Source #
getMemoryDataFiles :: State state [(String, String)] Source #
ifThenElseExpr :: state -> Bool Source #
aggressiveXOptBB :: State state AggressiveXOptBB Source #
Whether -fclash-aggressive-x-optimization-blackboxes was set
renderEnums :: State state RenderEnums Source #
Whether -fclash-no-render-enums was set
domainConfigurations :: State state DomainMap Source #
All the domain configurations of design
setDomainConfigurations :: DomainMap -> state -> state Source #
Set the domain configurations