clash-lib-1.5.0: Clash: a functional hardware description language - As a library
Copyright(C) 2015-2016 University of Twente
2017 Myrtle Software Ltd Google Inc.
2021-2022 QBayLogic B.V.
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Backend

Description

 
Synopsis

Documentation

data Usage Source #

Is a type used for internal or external use

Constructors

Internal

Internal use

External Text

External use, field indicates the library name

newtype AggressiveXOptBB Source #

Is '-fclash-aggresive-x-optimization-blackbox' set?

Constructors

AggressiveXOptBB Bool 

newtype RenderEnums Source #

Is '-fclash-render-enums' set?

Constructors

RenderEnums Bool 

data HWKind Source #

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.

type DomainMap = HashMap Text VDomainConfiguration Source #

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

expr Source #

Arguments

:: Bool

Enclose in parentheses?

-> Expr

Expr to convert

-> Ap (State state) Doc 

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

Instances

Instances details
Backend VerilogState Source # 
Instance details

Defined in Clash.Backend.Verilog

Methods

initBackend :: ClashOpts -> VerilogState Source #

hdlKind :: VerilogState -> HDL Source #

primDirs :: VerilogState -> IO [FilePath] Source #

name :: VerilogState -> String Source #

extension :: VerilogState -> String Source #

extractTypes :: VerilogState -> HashSet HWType Source #

genHDL :: ModName -> SrcSpan -> IdentifierSet -> Component -> Ap (State VerilogState) ((String, Doc), [(String, Doc)]) Source #

mkTyPackage :: ModName -> [HWType] -> Ap (State VerilogState) [(String, Doc)] Source #

hdlType :: Usage -> HWType -> Ap (State VerilogState) Doc Source #

hdlHWTypeKind :: HWType -> State VerilogState HWKind Source #

hdlTypeErrValue :: HWType -> Ap (State VerilogState) Doc Source #

hdlTypeMark :: HWType -> Ap (State VerilogState) Doc Source #

hdlRecSel :: HWType -> Int -> Ap (State VerilogState) Doc Source #

hdlSig :: Text -> HWType -> Ap (State VerilogState) Doc Source #

genStmt :: Bool -> State VerilogState Doc Source #

inst :: Declaration -> Ap (State VerilogState) (Maybe Doc) Source #

expr :: Bool -> Expr -> Ap (State VerilogState) Doc Source #

iwWidth :: State VerilogState Int Source #

toBV :: HWType -> Text -> Ap (State VerilogState) Doc Source #

fromBV :: HWType -> Text -> Ap (State VerilogState) Doc Source #

hdlSyn :: State VerilogState HdlSyn Source #

setModName :: ModName -> VerilogState -> VerilogState Source #

setSrcSpan :: SrcSpan -> State VerilogState () Source #

getSrcSpan :: State VerilogState SrcSpan Source #

blockDecl :: Identifier -> [Declaration] -> Ap (State VerilogState) Doc Source #

addIncludes :: [(String, Doc)] -> State VerilogState () Source #

addLibraries :: [Text] -> State VerilogState () Source #

addImports :: [Text] -> State VerilogState () Source #

addAndSetData :: FilePath -> State VerilogState String Source #

getDataFiles :: State VerilogState [(String, FilePath)] Source #

addMemoryDataFile :: (String, String) -> State VerilogState () Source #

getMemoryDataFiles :: State VerilogState [(String, String)] Source #

ifThenElseExpr :: VerilogState -> Bool Source #

aggressiveXOptBB :: State VerilogState AggressiveXOptBB Source #

renderEnums :: State VerilogState RenderEnums Source #

domainConfigurations :: State VerilogState DomainMap Source #

setDomainConfigurations :: DomainMap -> VerilogState -> VerilogState Source #

Backend VHDLState Source # 
Instance details

Defined in Clash.Backend.VHDL

Methods

initBackend :: ClashOpts -> VHDLState Source #

hdlKind :: VHDLState -> HDL Source #

primDirs :: VHDLState -> IO [FilePath] Source #

name :: VHDLState -> String Source #

extension :: VHDLState -> String Source #

extractTypes :: VHDLState -> HashSet HWType Source #

genHDL :: ModName -> SrcSpan -> IdentifierSet -> Component -> Ap (State VHDLState) ((String, Doc), [(String, Doc)]) Source #

mkTyPackage :: ModName -> [HWType] -> Ap (State VHDLState) [(String, Doc)] Source #

hdlType :: Usage -> HWType -> Ap (State VHDLState) Doc Source #

hdlHWTypeKind :: HWType -> State VHDLState HWKind Source #

hdlTypeErrValue :: HWType -> Ap (State VHDLState) Doc Source #

hdlTypeMark :: HWType -> Ap (State VHDLState) Doc Source #

hdlRecSel :: HWType -> Int -> Ap (State VHDLState) Doc Source #

hdlSig :: Text -> HWType -> Ap (State VHDLState) Doc Source #

genStmt :: Bool -> State VHDLState Doc Source #

inst :: Declaration -> Ap (State VHDLState) (Maybe Doc) Source #

expr :: Bool -> Expr -> Ap (State VHDLState) Doc Source #

iwWidth :: State VHDLState Int Source #

toBV :: HWType -> Text -> Ap (State VHDLState) Doc Source #

fromBV :: HWType -> Text -> Ap (State VHDLState) Doc Source #

hdlSyn :: State VHDLState HdlSyn Source #

setModName :: ModName -> VHDLState -> VHDLState Source #

setSrcSpan :: SrcSpan -> State VHDLState () Source #

getSrcSpan :: State VHDLState SrcSpan Source #

blockDecl :: Identifier -> [Declaration] -> Ap (State VHDLState) Doc Source #

addIncludes :: [(String, Doc)] -> State VHDLState () Source #

addLibraries :: [Text] -> State VHDLState () Source #

addImports :: [Text] -> State VHDLState () Source #

addAndSetData :: FilePath -> State VHDLState String Source #

getDataFiles :: State VHDLState [(String, FilePath)] Source #

addMemoryDataFile :: (String, String) -> State VHDLState () Source #

getMemoryDataFiles :: State VHDLState [(String, String)] Source #

ifThenElseExpr :: VHDLState -> Bool Source #

aggressiveXOptBB :: State VHDLState AggressiveXOptBB Source #

renderEnums :: State VHDLState RenderEnums Source #

domainConfigurations :: State VHDLState DomainMap Source #

setDomainConfigurations :: DomainMap -> VHDLState -> VHDLState Source #

Backend SystemVerilogState Source # 
Instance details

Defined in Clash.Backend.SystemVerilog

Methods

initBackend :: ClashOpts -> SystemVerilogState Source #

hdlKind :: SystemVerilogState -> HDL Source #

primDirs :: SystemVerilogState -> IO [FilePath] Source #

name :: SystemVerilogState -> String Source #

extension :: SystemVerilogState -> String Source #

extractTypes :: SystemVerilogState -> HashSet HWType Source #

genHDL :: ModName -> SrcSpan -> IdentifierSet -> Component -> Ap (State SystemVerilogState) ((String, Doc), [(String, Doc)]) Source #

mkTyPackage :: ModName -> [HWType] -> Ap (State SystemVerilogState) [(String, Doc)] Source #

hdlType :: Usage -> HWType -> Ap (State SystemVerilogState) Doc Source #

hdlHWTypeKind :: HWType -> State SystemVerilogState HWKind Source #

hdlTypeErrValue :: HWType -> Ap (State SystemVerilogState) Doc Source #

hdlTypeMark :: HWType -> Ap (State SystemVerilogState) Doc Source #

hdlRecSel :: HWType -> Int -> Ap (State SystemVerilogState) Doc Source #

hdlSig :: Text -> HWType -> Ap (State SystemVerilogState) Doc Source #

genStmt :: Bool -> State SystemVerilogState Doc Source #

inst :: Declaration -> Ap (State SystemVerilogState) (Maybe Doc) Source #

expr :: Bool -> Expr -> Ap (State SystemVerilogState) Doc Source #

iwWidth :: State SystemVerilogState Int Source #

toBV :: HWType -> Text -> Ap (State SystemVerilogState) Doc Source #

fromBV :: HWType -> Text -> Ap (State SystemVerilogState) Doc Source #

hdlSyn :: State SystemVerilogState HdlSyn Source #

setModName :: ModName -> SystemVerilogState -> SystemVerilogState Source #

setSrcSpan :: SrcSpan -> State SystemVerilogState () Source #

getSrcSpan :: State SystemVerilogState SrcSpan Source #

blockDecl :: Identifier -> [Declaration] -> Ap (State SystemVerilogState) Doc Source #

addIncludes :: [(String, Doc)] -> State SystemVerilogState () Source #

addLibraries :: [Text] -> State SystemVerilogState () Source #

addImports :: [Text] -> State SystemVerilogState () Source #

addAndSetData :: FilePath -> State SystemVerilogState String Source #

getDataFiles :: State SystemVerilogState [(String, FilePath)] Source #

addMemoryDataFile :: (String, String) -> State SystemVerilogState () Source #

getMemoryDataFiles :: State SystemVerilogState [(String, String)] Source #

ifThenElseExpr :: SystemVerilogState -> Bool Source #

aggressiveXOptBB :: State SystemVerilogState AggressiveXOptBB Source #

renderEnums :: State SystemVerilogState RenderEnums Source #

domainConfigurations :: State SystemVerilogState DomainMap Source #

setDomainConfigurations :: DomainMap -> SystemVerilogState -> SystemVerilogState Source #