| Copyright | (C) 2012-2016 University of Twente 2016-2017 Myrtle Software Ltd 2018 Google Inc. | 
|---|---|
| License | BSD2 (see the file LICENSE) | 
| Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Clash.Primitives.Types
Description
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
- kind :: TemplateKind
- warning :: c
- outputReg :: Bool
- libraries :: [a]
- imports :: [a]
- functionPlurality :: [(Int, Int)]
- includes :: [((Text, Text), b)]
- resultName :: Maybe b
- resultInit :: Maybe 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 #
Constructors
| TFile FilePath | Template source stored in file on filesystem | 
| TInline Text | Template stored inline | 
Instances
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 # | |
data TemplateFormat Source #
Instances
| Show TemplateFormat Source # | |
| Defined in Clash.Primitives.Types Methods showsPrec :: Int -> TemplateFormat -> ShowS # show :: TemplateFormat -> String # showList :: [TemplateFormat] -> ShowS # | |
| Generic TemplateFormat Source # | |
| Defined in Clash.Primitives.Types Associated Types type Rep TemplateFormat :: Type -> Type # Methods from :: TemplateFormat -> Rep TemplateFormat x # to :: Rep TemplateFormat x -> TemplateFormat # | |
| Hashable TemplateFormat Source # | |
| Defined in Clash.Primitives.Types | |
| FromJSON UnresolvedPrimitive Source # | |
| Defined in Clash.Primitives.Types Methods parseJSON :: Value -> Parser UnresolvedPrimitive # parseJSONList :: Value -> Parser [UnresolvedPrimitive] # | |
| NFData TemplateFormat Source # | |
| Defined in Clash.Primitives.Types Methods rnf :: TemplateFormat -> () # | |
| 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.
Constructors
| BlackBoxFunctionName [String] String | 
Instances
data Primitive a b c d Source #
Externally defined primitive
Constructors
| BlackBox | Primitive template written in a Clash specific templating language | 
| Fields 
 | |
| BlackBoxHaskell | Primitive template rendered by a Haskell function (given as raw source code) | 
| Fields 
 | |
| 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
Constructors
| 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 BlackBoxTemplates and BlackBoxFunctions.
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.