| Copyright | (C) 2012-2016 University of Twente 2017 Myrtle Software Ltd | 
|---|---|
| License | BSD2 (see the file LICENSE) | 
| Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Clash.Netlist.BlackBox.Types
Description
Types used in BlackBox modules
Synopsis
- data BlackBoxMeta = BlackBoxMeta {- bbOutputReg :: Bool
- bbKind :: TemplateKind
- bbLibrary :: [BlackBoxTemplate]
- bbImports :: [BlackBoxTemplate]
- bbFunctionPlurality :: [(Int, Int)]
- bbIncludes :: [((Text, Text), BlackBox)]
- bbRenderVoid :: RenderVoid
 
- emptyBlackBoxMeta :: BlackBoxMeta
- type BlackBoxFunction = Bool -> Text -> [Either Term Type] -> Type -> NetlistMonad (Either String (BlackBoxMeta, BlackBox))
- type BlackBoxTemplate = [Element]
- data TemplateKind
- data Element- = Text !Text
- | Component !Decl
- | Result !Bool
- | Arg !Bool !Int
- | ArgGen !Int !Int
- | Const !Int
- | Lit !Int
- | Name !Int
- | ToVar [Element] !Int
- | Sym !Text !Int
- | Typ !(Maybe Int)
- | TypM !(Maybe Int)
- | Err !(Maybe Int)
- | TypElem !Element
- | CompName
- | IncludeName !Int
- | IndexType !Element
- | Size !Element
- | Length !Element
- | Depth !Element
- | MaxIndex !Element
- | FilePath !Element
- | Template [Element] [Element]
- | Gen !Bool
- | IF !Element [Element] [Element]
- | And [Element]
- | IW64
- | CmpLE !Element !Element
- | HdlSyn HdlSyn
- | BV !Bool [Element] !Element
- | Sel !Element !Int
- | IsLit !Int
- | IsVar !Int
- | IsActiveHigh !Int
- | Tag !Int
- | Period !Int
- | ActiveEdge !ActiveEdge !Int
- | IsSync !Int
- | IsInitDefined !Int
- | IsActiveEnable !Int
- | StrCmp [Element] !Int
- | OutputWireReg !Int
- | Vars !Int
- | GenSym [Element] !Int
- | Repeat [Element] [Element]
- | DevNull [Element]
- | SigD [Element] !(Maybe Int)
- | CtxName
 
- data Decl = Decl !Int !Int [(BlackBoxTemplate, BlackBoxTemplate)]
- data HdlSyn
- data RenderVoid
Documentation
data BlackBoxMeta Source #
See Clash.Primitives.Types.BlackBox for documentation on this record's
 fields. (They are intentionally renamed to prevent name clashes.)
Constructors
| BlackBoxMeta | |
| Fields 
 | |
emptyBlackBoxMeta :: BlackBoxMeta Source #
Use this value in your blackbox template function if you do want to
 accept the defaults as documented in Clash.Primitives.Types.BlackBox.
type BlackBoxFunction Source #
Arguments
| = Bool | Indicates whether caller needs a declaration. If set, the function is still free to return an expression, but the caller will convert it to a declaration. | 
| -> Text | Name of primitive | 
| -> [Either Term Type] | Arguments | 
| -> Type | Result type | 
| -> NetlistMonad (Either String (BlackBoxMeta, BlackBox)) | 
A BlackBox function generates a blackbox template, given the inputs and result type of the function it should provide a blackbox for. This is useful when having a need for blackbox functions, ... TODO: docs
type BlackBoxTemplate = [Element] Source #
A BlackBox Template is a List of Elements TODO: Add name of function for better error messages
data TemplateKind Source #
Instances
| Eq TemplateKind Source # | |
| Defined in Clash.Netlist.BlackBox.Types | |
| Show TemplateKind Source # | |
| Defined in Clash.Netlist.BlackBox.Types Methods showsPrec :: Int -> TemplateKind -> ShowS # show :: TemplateKind -> String # showList :: [TemplateKind] -> ShowS # | |
| Generic TemplateKind Source # | |
| Defined in Clash.Netlist.BlackBox.Types Associated Types type Rep TemplateKind :: Type -> Type # | |
| Hashable TemplateKind Source # | |
| Defined in Clash.Netlist.BlackBox.Types | |
| Binary TemplateKind Source # | |
| Defined in Clash.Netlist.BlackBox.Types | |
| NFData TemplateKind Source # | |
| Defined in Clash.Netlist.BlackBox.Types Methods rnf :: TemplateKind -> () # | |
| type Rep TemplateKind Source # | |
Elements of a blackbox context. If you extend this list, make sure to update the following functions:
- Clash.Netlist.BlackBox.Types.prettyElem
- Clash.Netlist.BlackBox.Types.renderElem
- Clash.Netlist.BlackBox.Types.renderTag
- Clash.Netlist.BlackBox.Types.setSym
- Clash.Netlist.BlackBox.Types.getUsedArguments
- Clash.Netlist.BlackBox.Types.usedVariables
- Clash.Netlist.BlackBox.Types.verifyBlackBoxContext
- Clash.Netlist.BlackBox.Types.walkElement
Constructors
| Text !Text | Dumps given text without processing in HDL | 
| Component !Decl | Component instantiation hole | 
| Result !Bool | Output hole;  | 
| Arg !Bool !Int | Input hole;  | 
| ArgGen !Int !Int | Like Arg, but its first argument is the scoping level. For use in in generated code only. | 
| Const !Int | Like Arg, but input hole must be a constant. | 
| Lit !Int | Like Arg, but input hole must be a literal | 
| Name !Int | Name hole | 
| ToVar [Element] !Int | Like Arg but only insert variable reference (creating an assignment elsewhere if necessary). | 
| Sym !Text !Int | Symbol hole | 
| Typ !(Maybe Int) | Type declaration hole | 
| TypM !(Maybe Int) | Type root hole | 
| Err !(Maybe Int) | Error value hole | 
| TypElem !Element | Select element type from a vector type | 
| CompName | Hole for the name of the component in which the blackbox is instantiated | 
| IncludeName !Int | |
| IndexType !Element | Index data type hole, the field is the (exclusive) maximum index | 
| Size !Element | Size of a type hole | 
| Length !Element | Length of a vector hole | 
| Depth !Element | Depth of a tree hole | 
| MaxIndex !Element | Max index into a vector | 
| FilePath !Element | Hole containing a filepath for a data file | 
| Template [Element] [Element] | |
| Gen !Bool | Hole marking beginning (True) or end (False) of a generative construct | 
| IF !Element [Element] [Element] | |
| And [Element] | |
| IW64 | Hole indicating whether IntWordInteger are 64-Bit | 
| CmpLE !Element !Element | Compare less-or-equal | 
| HdlSyn HdlSyn | Hole indicating which synthesis tool we're generating HDL for | 
| BV !Bool [Element] !Element | Convert to (True)/from(False) a bit-vector | 
| Sel !Element !Int | Record selector of a type | 
| IsLit !Int | |
| IsVar !Int | |
| IsActiveHigh !Int | Whether a domain's reset lines are synchronous. | 
| Tag !Int | Tag of a domain. | 
| Period !Int | Period of a domain. | 
| ActiveEdge !ActiveEdge !Int | Test active edge of memory elements in a certain domain | 
| IsSync !Int | Whether a domain's reset lines are synchronous. Errors if not applied to a KnownDomain. | 
| IsInitDefined !Int | |
| IsActiveEnable !Int | Whether given enable line is active. More specifically, whether the
 enable line is NOT set to a constant  | 
| StrCmp [Element] !Int | |
| OutputWireReg !Int | |
| Vars !Int | |
| GenSym [Element] !Int | |
| Repeat [Element] [Element] | Repeat hole n times | 
| DevNull [Element] | Evaluate hole but swallow output | 
| SigD [Element] !(Maybe Int) | |
| CtxName | The "context name", name set by  | 
Instances
Component instantiation hole. First argument indicates which function argument to instantiate. Second argument corresponds to output and input assignments, where the first element is the output assignment, and the subsequent elements are the consecutive input assignments.
The LHS of the tuple is the name of the signal, while the RHS of the tuple is the type of the signal
Constructors
| Decl | |
| Fields 
 | |
Instances
| Show Decl Source # | |
| Generic Decl Source # | |
| Hashable Decl Source # | |
| Defined in Clash.Netlist.BlackBox.Types | |
| Binary Decl Source # | |
| NFData Decl Source # | |
| Defined in Clash.Netlist.BlackBox.Types | |
| type Rep Decl Source # | |
| Defined in Clash.Netlist.BlackBox.Types type Rep Decl = D1 ('MetaData "Decl" "Clash.Netlist.BlackBox.Types" "clash-lib-1.2.3-inplace" 'False) (C1 ('MetaCons "Decl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(BlackBoxTemplate, BlackBoxTemplate)])))) | |
Instances
| Eq HdlSyn Source # | |
| Read HdlSyn Source # | |
| Show HdlSyn Source # | |
| Generic HdlSyn Source # | |
| Hashable HdlSyn Source # | |
| Defined in Clash.Netlist.BlackBox.Types | |
| Binary HdlSyn Source # | |
| NFData HdlSyn Source # | |
| Defined in Clash.Netlist.BlackBox.Types | |
| type Rep HdlSyn Source # | |
| Defined in Clash.Netlist.BlackBox.Types type Rep HdlSyn = D1 ('MetaData "HdlSyn" "Clash.Netlist.BlackBox.Types" "clash-lib-1.2.3-inplace" 'False) (C1 ('MetaCons "Vivado" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Quartus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Other" 'PrefixI 'False) (U1 :: Type -> Type))) | |
data RenderVoid Source #
Whether this primitive should be rendered when its result type is void.
 Defaults to NoRenderVoid.
Constructors
| RenderVoid | Render blackbox, even if result type is void | 
| NoRenderVoid | Don't render blackbox result type is void. Default for all blackboxes. | 
Instances
| Show RenderVoid Source # | |
| Defined in Clash.Netlist.BlackBox.Types Methods showsPrec :: Int -> RenderVoid -> ShowS # show :: RenderVoid -> String # showList :: [RenderVoid] -> ShowS # | |
| Generic RenderVoid Source # | |
| Defined in Clash.Netlist.BlackBox.Types Associated Types type Rep RenderVoid :: Type -> Type # | |
| Hashable RenderVoid Source # | |
| Defined in Clash.Netlist.BlackBox.Types | |
| FromJSON RenderVoid Source # | |
| Defined in Clash.Netlist.BlackBox.Types | |
| Binary RenderVoid Source # | |
| Defined in Clash.Netlist.BlackBox.Types | |
| NFData RenderVoid Source # | |
| Defined in Clash.Netlist.BlackBox.Types Methods rnf :: RenderVoid -> () # | |
| type Rep RenderVoid Source # | |