clash-lib-1.2.5: CAES Language for Synchronous Hardware - As a Library
Copyright(C) 2012-2016 University of Twente
2017 Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Netlist.BlackBox.Types

Description

Types used in BlackBox modules

Synopsis

Documentation

data BlackBoxMeta Source #

See Clash.Primitives.Types.BlackBox for documentation on this record's fields. (They are intentionally renamed to prevent name clashes.)

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 #

Constructors

TDecl 
TExpr 

Instances

Instances details
Eq TemplateKind Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Show TemplateKind Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Generic TemplateKind Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Associated Types

type Rep TemplateKind :: Type -> Type #

Hashable TemplateKind Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Binary TemplateKind Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

NFData TemplateKind Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

rnf :: TemplateKind -> () #

type Rep TemplateKind Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

type Rep TemplateKind = D1 ('MetaData "TemplateKind" "Clash.Netlist.BlackBox.Types" "clash-lib-1.2.5-inplace" 'False) (C1 ('MetaCons "TDecl" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TExpr" 'PrefixI 'False) (U1 :: Type -> Type))

data Element 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; Bool asserts escape marker stripping

Arg !Bool !Int

Input hole; Bool asserts escape marker stripping

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]

Create data file HOLE0 with contents HOLE1

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 True.

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 setName, defaults to the name of the closest binder

Instances

Instances details
Show Element Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Generic Element Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Associated Types

type Rep Element :: Type -> Type #

Methods

from :: Element -> Rep Element x #

to :: Rep Element x -> Element #

Hashable Element Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

hashWithSalt :: Int -> Element -> Int #

hash :: Element -> Int #

Binary Element Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

put :: Element -> Put #

get :: Get Element #

putList :: [Element] -> Put #

NFData Element Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

rnf :: Element -> () #

type Rep Element Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

type Rep Element = D1 ('MetaData "Element" "Clash.Netlist.BlackBox.Types" "clash-lib-1.2.5-inplace" 'False) (((((C1 ('MetaCons "Text" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "Component" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Decl)) :+: C1 ('MetaCons "Result" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))) :+: (C1 ('MetaCons "Arg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "ArgGen" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "Const" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))))) :+: ((C1 ('MetaCons "Lit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "Name" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "ToVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))) :+: (C1 ('MetaCons "Sym" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "Typ" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :+: C1 ('MetaCons "TypM" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))))))) :+: (((C1 ('MetaCons "Err" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :+: (C1 ('MetaCons "TypElem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element)) :+: C1 ('MetaCons "CompName" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "IncludeName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "IndexType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element)) :+: C1 ('MetaCons "Size" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element))))) :+: ((C1 ('MetaCons "Length" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element)) :+: (C1 ('MetaCons "Depth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element)) :+: C1 ('MetaCons "MaxIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element)))) :+: (C1 ('MetaCons "FilePath" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element)) :+: (C1 ('MetaCons "Template" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element])) :+: C1 ('MetaCons "Gen" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))))))) :+: ((((C1 ('MetaCons "IF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element]))) :+: (C1 ('MetaCons "And" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element])) :+: C1 ('MetaCons "IW64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CmpLE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element)) :+: (C1 ('MetaCons "HdlSyn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HdlSyn)) :+: C1 ('MetaCons "BV" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element)))))) :+: ((C1 ('MetaCons "Sel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Element) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "IsLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "IsVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))) :+: (C1 ('MetaCons "IsActiveHigh" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "Tag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "Period" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))))) :+: (((C1 ('MetaCons "ActiveEdge" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ActiveEdge) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "IsSync" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "IsInitDefined" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))) :+: (C1 ('MetaCons "IsActiveEnable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "StrCmp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "OutputWireReg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))))) :+: ((C1 ('MetaCons "Vars" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: (C1 ('MetaCons "GenSym" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "Repeat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element])))) :+: (C1 ('MetaCons "DevNull" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element])) :+: (C1 ('MetaCons "SigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Element]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :+: C1 ('MetaCons "CtxName" 'PrefixI 'False) (U1 :: Type -> Type)))))))

data Decl Source #

Component instantiation hole. First argument indicates which function argument to instantiate. Third 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

  • !Int

    Argument position of the function to instantiate

  • !Int

    Subposition of function: blackboxes can request multiple instances to be rendered of their given functions. This subposition indicates the nth function instance to be rendered (zero-indexed).

    This is a hack: the proper solution would postpone rendering the function until the very last moment. The blackbox language has no way to indicate the subposition, and every ~INST will default its subposition to zero. Haskell blackboxes can use this data type.

  • [(BlackBoxTemplate, BlackBoxTemplate)]

    (name of signal, type of signal)

Instances

Instances details
Show Decl Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

showsPrec :: Int -> Decl -> ShowS #

show :: Decl -> String #

showList :: [Decl] -> ShowS #

Generic Decl Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Associated Types

type Rep Decl :: Type -> Type #

Methods

from :: Decl -> Rep Decl x #

to :: Rep Decl x -> Decl #

Hashable Decl Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

hashWithSalt :: Int -> Decl -> Int #

hash :: Decl -> Int #

Binary Decl Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

put :: Decl -> Put #

get :: Get Decl #

putList :: [Decl] -> Put #

NFData Decl Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

rnf :: Decl -> () #

type Rep Decl Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

data HdlSyn Source #

Constructors

Vivado 
Quartus 
Other 

Instances

Instances details
Eq HdlSyn Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

(==) :: HdlSyn -> HdlSyn -> Bool #

(/=) :: HdlSyn -> HdlSyn -> Bool #

Read HdlSyn Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Show HdlSyn Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Generic HdlSyn Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Associated Types

type Rep HdlSyn :: Type -> Type #

Methods

from :: HdlSyn -> Rep HdlSyn x #

to :: Rep HdlSyn x -> HdlSyn #

Hashable HdlSyn Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

hashWithSalt :: Int -> HdlSyn -> Int #

hash :: HdlSyn -> Int #

Binary HdlSyn Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

put :: HdlSyn -> Put #

get :: Get HdlSyn #

putList :: [HdlSyn] -> Put #

NFData HdlSyn Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

rnf :: HdlSyn -> () #

type Rep HdlSyn Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

type Rep HdlSyn = D1 ('MetaData "HdlSyn" "Clash.Netlist.BlackBox.Types" "clash-lib-1.2.5-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

Instances details
Show RenderVoid Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Generic RenderVoid Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Associated Types

type Rep RenderVoid :: Type -> Type #

Hashable RenderVoid Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

FromJSON RenderVoid Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Binary RenderVoid Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

NFData RenderVoid Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

Methods

rnf :: RenderVoid -> () #

type Rep RenderVoid Source # 
Instance details

Defined in Clash.Netlist.BlackBox.Types

type Rep RenderVoid = D1 ('MetaData "RenderVoid" "Clash.Netlist.BlackBox.Types" "clash-lib-1.2.5-inplace" 'False) (C1 ('MetaCons "RenderVoid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoRenderVoid" 'PrefixI 'False) (U1 :: Type -> Type))