Copyright | (C) 2015-2016 University of Twente 2017 Myrtle Software Ltd Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Clash.Backend
Description
Synopsis
- type ModName = String
- data Usage
- class Backend state where
- nestM :: Modifier -> Modifier -> Maybe Modifier
- escapeTemplate :: Identifier -> Identifier
Documentation
Is a type used for internal or external use
class Backend state where Source #
Minimal complete definition
initBackend, hdlKind, primDirs, name, extension, extractTypes, genHDL, mkTyPackage, hdlType, hdlTypeErrValue, hdlTypeMark, hdlRecSel, hdlSig, genStmt, inst, expr, iwWidth, toBV, fromBV, hdlSyn, mkIdentifier, extendIdentifier, setModName, setSrcSpan, getSrcSpan, blockDecl, unextend, addInclude, addLibraries, addImports
Methods
initBackend :: Int -> HdlSyn -> 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 :: String -> SrcSpan -> Component -> Mon (State state) ((String, Doc), [(String, Doc)]) Source #
Generate HDL for a Netlist component
mkTyPackage :: String -> [HWType] -> Mon (State state) [(String, Doc)] Source #
Generate a HDL package containing type definitions for the given HWTypes
hdlType :: Usage -> HWType -> Mon (State state) Doc Source #
Convert a Netlist HWType to a target HDL type
hdlTypeErrValue :: HWType -> Mon (State state) Doc Source #
Convert a Netlist HWType to an HDL error value for that type
hdlTypeMark :: HWType -> Mon (State state) Doc Source #
Convert a Netlist HWType to the root of a target HDL type
hdlRecSel :: HWType -> Int -> Mon (State state) Doc Source #
Create a record selector
hdlSig :: Text -> HWType -> Mon (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 -> Mon (State state) (Maybe Doc) Source #
Turn a Netlist Declaration to a HDL concurrent block
expr :: Bool -> Expr -> Mon (State state) Doc Source #
Turn a Netlist expression into a HDL expression
iwWidth :: State state Int Source #
Bit-width of IntWordInteger
toBV :: HWType -> Text -> Mon (State state) Doc Source #
Convert to a bit-vector
fromBV :: HWType -> Text -> Mon (State state) Doc Source #
Convert from a bit-vector
hdlSyn :: State state HdlSyn Source #
Synthesis tool we're generating HDL for
mkIdentifier :: State state (IdType -> Identifier -> Identifier) Source #
mkIdentifier
extendIdentifier :: State state (IdType -> Identifier -> Identifier -> Identifier) Source #
mkIdentifier
setModName :: ModName -> state -> state Source #
setModName
setSrcSpan :: SrcSpan -> State state () Source #
setSrcSpan
getSrcSpan :: State state SrcSpan Source #
getSrcSpan
blockDecl :: Text -> [Declaration] -> Mon (State state) Doc Source #
Block of declarations
unextend :: State state (Identifier -> Identifier) Source #
unextend/unescape identifier
addInclude :: (String, Doc) -> State state () Source #
addLibraries :: [Text] -> State state () Source #
addImports :: [Text] -> State state () Source #
Instances
nestM :: Modifier -> Modifier -> Maybe Modifier Source #
Try to merge nested modifiers into a single modifier, needed by the VHDL and SystemVerilog backend.
escapeTemplate :: Identifier -> Identifier Source #
Replace a normal HDL template placeholder with an unescaped/unextended template placeholder.
Needed when the the place-holder is filled with an escaped/extended identifier inside an escaped/extended identifier and we want to strip the escape /extension markers. Otherwise we end up with illegal identifiers.