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

Clash.Primitives.Types

Description

Type and instance definitions for Primitive

Synopsis

Documentation

data TemplateSource Source #

Constructors

TFile FilePath

Template source stored in file on filesystem

TInline Text

Template stored inline

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 TemplateFormat Source #

Constructors

TTemplate 
THaskell 

Instances

Instances details
Show TemplateFormat Source # 
Instance details

Defined in Clash.Primitives.Types

Generic TemplateFormat Source # 
Instance details

Defined in Clash.Primitives.Types

Associated Types

type Rep TemplateFormat :: Type -> Type #

Hashable TemplateFormat Source # 
Instance details

Defined in Clash.Primitives.Types

FromJSON UnresolvedPrimitive Source # 
Instance details

Defined in Clash.Primitives.Types

NFData TemplateFormat Source # 
Instance details

Defined in Clash.Primitives.Types

Methods

rnf :: TemplateFormat -> () #

type Rep TemplateFormat Source # 
Instance details

Defined in Clash.Primitives.Types

type Rep TemplateFormat = D1 ('MetaData "TemplateFormat" "Clash.Primitives.Types" "clash-lib-1.2.5-inplace" 'False) (C1 ('MetaCons "TTemplate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THaskell" 'PrefixI 'False) (U1 :: Type -> Type))

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

Instances details
Eq BlackBoxFunctionName Source # 
Instance details

Defined in Clash.Primitives.Types

Show BlackBoxFunctionName Source # 
Instance details

Defined in Clash.Primitives.Types

Generic BlackBoxFunctionName Source # 
Instance details

Defined in Clash.Primitives.Types

Associated Types

type Rep BlackBoxFunctionName :: Type -> Type #

Hashable BlackBoxFunctionName Source # 
Instance details

Defined in Clash.Primitives.Types

FromJSON UnresolvedPrimitive Source # 
Instance details

Defined in Clash.Primitives.Types

Binary BlackBoxFunctionName Source # 
Instance details

Defined in Clash.Primitives.Types

NFData BlackBoxFunctionName Source # 
Instance details

Defined in Clash.Primitives.Types

Methods

rnf :: BlackBoxFunctionName -> () #

type Rep BlackBoxFunctionName Source # 
Instance details

Defined in Clash.Primitives.Types

type Rep BlackBoxFunctionName = D1 ('MetaData "BlackBoxFunctionName" "Clash.Primitives.Types" "clash-lib-1.2.5-inplace" 'False) (C1 ('MetaCons "BlackBoxFunctionName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data Primitive a b c d Source #

Externally defined primitive

Constructors

BlackBox

Primitive template written in a Clash specific templating language

Fields

  • name :: !Text

    Name of the primitive

  • workInfo :: WorkInfo

    Whether the primitive does any work, i.e. takes chip area

  • renderVoid :: RenderVoid

    Whether this primitive should be rendered when its result type is void. Defaults to NoRenderVoid.

  • kind :: TemplateKind

    Whether this results in an expression or a declaration

  • warning :: c

    A warning to be outputted when the primitive is instantiated. This is intended to be used as a warning for primitives that are not synthesizable, but may also be used for other purposes.

  • outputReg :: Bool

    Verilog only: whether the result should be a reg(True) or wire (False); when not specified in the .json file, the value will default to False (i.e. wire).

  • libraries :: [a]

    VHDL only: add library declarations for the given names

  • imports :: [a]

    VHDL only: add use declarations for the given names

  • functionPlurality :: [(Int, Int)]

    Indicates how often a function will be instantiated in a blackbox. For example, consider the following higher-order function that creates a tree structure:

    fold :: (a -> a -> a) -> Vec n a -> a

    In order to generate HDL for an instance of fold we need log2(n) calls to the first argument, `a -> a -> a` (plus a few more if n is not a power of two). Note that this only targets multiple textual instances of the function. If you can generate the HDL using a for-loop and only need to call ~INST once, you don't have to worry about this option. See the blackbox for map for an example of this.

    Right now, option can only be generated by BlackBoxHaskell. It cannot be used within JSON primitives. To see how to use this, see the Haskell blackbox for fold.

  • includes :: [((Text, Text), b)]

    Create files to be included with the generated primitive. The fields are ((name, extension), content), where content is a template of the file Defaults to [] when not specified in the .json file

  • resultName :: Maybe b

    (Maybe) Control the generated name of the result

  • resultInit :: Maybe b

    (Maybe) Control the initial/power-up value of the result

  • template :: b

    Used to indiciate type of template (declaration or expression). Will be filled with Template or an Either decl expr.

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: mapSignal in GHC2Core.coreToTerm.

Fields

Instances

Instances details
FromJSON UnresolvedPrimitive Source # 
Instance details

Defined in Clash.Primitives.Types

Functor (Primitive a b c) Source # 
Instance details

Defined in Clash.Primitives.Types

Methods

fmap :: (a0 -> b0) -> Primitive a b c a0 -> Primitive a b c b0 #

(<$) :: a0 -> Primitive a b c b0 -> Primitive a b c a0 #

(Show c, Show a, Show b, Show d) => Show (Primitive a b c d) Source # 
Instance details

Defined in Clash.Primitives.Types

Methods

showsPrec :: Int -> Primitive a b c d -> ShowS #

show :: Primitive a b c d -> String #

showList :: [Primitive a b c d] -> ShowS #

Generic (Primitive a b c d) Source # 
Instance details

Defined in Clash.Primitives.Types

Associated Types

type Rep (Primitive a b c d) :: Type -> Type #

Methods

from :: Primitive a b c d -> Rep (Primitive a b c d) x #

to :: Rep (Primitive a b c d) x -> Primitive a b c d #

(Hashable c, Hashable a, Hashable b, Hashable d) => Hashable (Primitive a b c d) Source # 
Instance details

Defined in Clash.Primitives.Types

Methods

hashWithSalt :: Int -> Primitive a b c d -> Int #

hash :: Primitive a b c d -> Int #

(Binary c, Binary a, Binary b, Binary d) => Binary (Primitive a b c d) Source # 
Instance details

Defined in Clash.Primitives.Types

Methods

put :: Primitive a b c d -> Put #

get :: Get (Primitive a b c d) #

putList :: [Primitive a b c d] -> Put #

(NFData c, NFData a, NFData b, NFData d) => NFData (Primitive a b c d) Source # 
Instance details

Defined in Clash.Primitives.Types

Methods

rnf :: Primitive a b c d -> () #

type Rep (Primitive a b c d) Source # 
Instance details

Defined in Clash.Primitives.Types

type Rep (Primitive a b c d) = D1 ('MetaData "Primitive" "Clash.Primitives.Types" "clash-lib-1.2.5-inplace" 'False) (C1 ('MetaCons "BlackBox" 'PrefixI 'True) (((S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "workInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WorkInfo) :*: S1 ('MetaSel ('Just "renderVoid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RenderVoid))) :*: (S1 ('MetaSel ('Just "kind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TemplateKind) :*: (S1 ('MetaSel ('Just "warning") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Just "outputReg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "libraries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]) :*: (S1 ('MetaSel ('Just "imports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]) :*: S1 ('MetaSel ('Just "functionPlurality") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Int, Int)]))) :*: ((S1 ('MetaSel ('Just "includes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [((Text, Text), b)]) :*: S1 ('MetaSel ('Just "resultName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe b))) :*: (S1 ('MetaSel ('Just "resultInit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe b)) :*: S1 ('MetaSel ('Just "template") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))))) :+: (C1 ('MetaCons "BlackBoxHaskell" 'PrefixI 'True) ((S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "workInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WorkInfo)) :*: (S1 ('MetaSel ('Just "usedArguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UsedArguments) :*: (S1 ('MetaSel ('Just "functionName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlackBoxFunctionName) :*: S1 ('MetaSel ('Just "function") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d)))) :+: C1 ('MetaCons "Primitive" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "workInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WorkInfo) :*: S1 ('MetaSel ('Just "primSort") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))))

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

Instances details
Show UsedArguments Source # 
Instance details

Defined in Clash.Primitives.Types

Generic UsedArguments Source # 
Instance details

Defined in Clash.Primitives.Types

Associated Types

type Rep UsedArguments :: Type -> Type #

Hashable UsedArguments Source # 
Instance details

Defined in Clash.Primitives.Types

Binary UsedArguments Source # 
Instance details

Defined in Clash.Primitives.Types

NFData UsedArguments Source # 
Instance details

Defined in Clash.Primitives.Types

Methods

rnf :: UsedArguments -> () #

type Rep UsedArguments Source # 
Instance details

Defined in Clash.Primitives.Types

type Rep UsedArguments = D1 ('MetaData "UsedArguments" "Clash.Primitives.Types" "clash-lib-1.2.5-inplace" 'False) (C1 ('MetaCons "UsedArguments" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])) :+: C1 ('MetaCons "IgnoredArguments" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])))

type PrimMap a = HashMap Text a Source #

A PrimMap maps primitive names to a Primitive

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.