Copyright | (C) 2012-2016 University of Twente 2016-2017 Myrtle Software Ltd 2018 Google Inc. 2021 QBayLogic B.V. 2022 Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | None |
Language | Haskell2010 |
Type and instance definitions for Primitive
Synopsis
- data TemplateSource
- data TemplateKind
- data TemplateFormat
- data BlackBoxFunctionName = BlackBoxFunctionName [String] String
- data Primitive a b c d
- = BlackBox {
- name :: !Text
- workInfo :: WorkInfo
- renderVoid :: RenderVoid
- multiResult :: Bool
- kind :: TemplateKind
- warning :: c
- outputUsage :: Usage
- libraries :: [a]
- imports :: [a]
- functionPlurality :: [(Int, Int)]
- includes :: [((Text, Text), b)]
- resultNames :: [b]
- resultInits :: [b]
- template :: b
- | BlackBoxHaskell { }
- | Primitive { }
- = BlackBox {
- data UsedArguments
- = UsedArguments [Int]
- | IgnoredArguments [Int]
- type GuardedCompiledPrimitive = PrimitiveGuard CompiledPrimitive
- type GuardedResolvedPrimitive = PrimitiveGuard ResolvedPrimitive
- type PrimMap a = HashMap Text a
- type UnresolvedPrimitive = Primitive Text ((TemplateFormat, BlackBoxFunctionName), Maybe TemplateSource) (Maybe Text) (Maybe TemplateSource)
- type ResolvedPrimitive = Primitive Text ((TemplateFormat, BlackBoxFunctionName), Maybe Text) () (Maybe Text)
- type ResolvedPrimMap = PrimMap GuardedResolvedPrimitive
- type CompiledPrimitive = Primitive BlackBoxTemplate BlackBox () (Int, BlackBoxFunction)
- type CompiledPrimMap = PrimMap GuardedCompiledPrimitive
Documentation
data TemplateSource Source #
Instances
data TemplateKind Source #
Instances
Eq TemplateKind Source # | |
Defined in Clash.Netlist.BlackBox.Types (==) :: TemplateKind -> TemplateKind -> Bool Source # (/=) :: TemplateKind -> TemplateKind -> Bool Source # | |
Show TemplateKind Source # | |
Defined in Clash.Netlist.BlackBox.Types | |
Generic TemplateKind Source # | |
Defined in Clash.Netlist.BlackBox.Types from :: TemplateKind -> Rep TemplateKind x Source # to :: Rep TemplateKind x -> TemplateKind Source # | |
Hashable TemplateKind Source # | |
Defined in Clash.Netlist.BlackBox.Types hashWithSalt :: Int -> TemplateKind -> Int Source # hash :: TemplateKind -> Int Source # | |
Binary TemplateKind Source # | |
Defined in Clash.Netlist.BlackBox.Types put :: TemplateKind -> Put Source # get :: Get TemplateKind Source # putList :: [TemplateKind] -> Put Source # | |
NFData TemplateKind Source # | |
Defined in Clash.Netlist.BlackBox.Types rnf :: TemplateKind -> () Source # | |
type Rep TemplateKind Source # | |
data TemplateFormat Source #
Instances
Eq TemplateFormat Source # | |
Defined in Clash.Primitives.Types (==) :: TemplateFormat -> TemplateFormat -> Bool Source # (/=) :: TemplateFormat -> TemplateFormat -> Bool Source # | |
Show TemplateFormat Source # | |
Defined in Clash.Primitives.Types | |
Generic TemplateFormat Source # | |
Defined in Clash.Primitives.Types from :: TemplateFormat -> Rep TemplateFormat x Source # to :: Rep TemplateFormat x -> TemplateFormat Source # | |
Hashable TemplateFormat Source # | |
Defined in Clash.Primitives.Types hashWithSalt :: Int -> TemplateFormat -> Int Source # hash :: TemplateFormat -> Int Source # | |
FromJSON UnresolvedPrimitive Source # | |
Defined in Clash.Primitives.Types | |
NFData TemplateFormat Source # | |
Defined in Clash.Primitives.Types rnf :: TemplateFormat -> () Source # | |
type Rep TemplateFormat Source # | |
data BlackBoxFunctionName Source #
A BBFN is a parsed version of a fully qualified function name. It is guaranteed to have at least one module name which is not Main.
Instances
data Primitive a b c d Source #
Externally defined primitive
BlackBox | Primitive template written in a Clash specific templating language |
| |
BlackBoxHaskell | Primitive template rendered by a Haskell function (given as raw source code) |
| |
Primitive | A primitive that carries additional information. These are "real"
primitives, hardcoded in the compiler. For example: |
Instances
data UsedArguments Source #
Data type to indicate what arguments are in use by a BlackBox
UsedArguments [Int] | Only these are used |
IgnoredArguments [Int] | All but these are used |
Instances
type GuardedCompiledPrimitive = PrimitiveGuard CompiledPrimitive Source #
type GuardedResolvedPrimitive = PrimitiveGuard ResolvedPrimitive Source #
type UnresolvedPrimitive = Primitive Text ((TemplateFormat, BlackBoxFunctionName), Maybe TemplateSource) (Maybe Text) (Maybe TemplateSource) Source #
An unresolved primitive still contains pointers to files.
type ResolvedPrimitive = Primitive Text ((TemplateFormat, BlackBoxFunctionName), Maybe Text) () (Maybe Text) Source #
A parsed primitive does not contain pointers to filesystem files anymore,
but holds uncompiled BlackBoxTemplate
s and BlackBoxFunction
s.
type CompiledPrimitive = Primitive BlackBoxTemplate BlackBox () (Int, BlackBoxFunction) Source #
A compiled primitive has compiled all templates and functions from its
ResolvedPrimitive
counterpart. The Int in the tuple is a hash of the
(uncompiled) BlackBoxFunction.