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

Clash.Driver.Types

Description

Type definitions used by the Driver module

Synopsis

Documentation

data Binding Source #

Instances

Instances details
Show Binding Source # 
Instance details

Defined in Clash.Driver.Types

Generic Binding Source # 
Instance details

Defined in Clash.Driver.Types

Associated Types

type Rep Binding :: Type -> Type #

Methods

from :: Binding -> Rep Binding x #

to :: Rep Binding x -> Binding #

Binary Binding Source # 
Instance details

Defined in Clash.Driver.Types

Methods

put :: Binding -> Put #

get :: Get Binding #

putList :: [Binding] -> Put #

NFData Binding Source # 
Instance details

Defined in Clash.Driver.Types

Methods

rnf :: Binding -> () #

type Rep Binding Source # 
Instance details

Defined in Clash.Driver.Types

type Rep Binding = D1 ('MetaData "Binding" "Clash.Driver.Types" "clash-lib-1.2.5-inplace" 'False) (C1 ('MetaCons "Binding" 'PrefixI 'True) ((S1 ('MetaSel ('Just "bindingId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: S1 ('MetaSel ('Just "bindingLoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan)) :*: (S1 ('MetaSel ('Just "bindingSpec") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InlineSpec) :*: S1 ('MetaSel ('Just "bindingTerm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Term))))

type BindingMap = VarEnv Binding Source #

Global function binders

Global functions cannot be mutually recursive, only self-recursive.

data DebugLevel Source #

Debug Message Verbosity

Constructors

DebugNone

Don't show debug messages

DebugSilent

Run invariant checks and err if violated (enabled by any debug flag)

DebugFinal

Show completely normalized expressions

DebugName

Show names of applied transformations

DebugTry

Show names of tried AND applied transformations

DebugApplied

Show sub-expressions after a successful rewrite

DebugAll

Show all sub-expressions on which a rewrite is attempted

Instances

Instances details
Enum DebugLevel Source # 
Instance details

Defined in Clash.Driver.Types

Eq DebugLevel Source # 
Instance details

Defined in Clash.Driver.Types

Ord DebugLevel Source # 
Instance details

Defined in Clash.Driver.Types

Read DebugLevel Source # 
Instance details

Defined in Clash.Driver.Types

Generic DebugLevel Source # 
Instance details

Defined in Clash.Driver.Types

Associated Types

type Rep DebugLevel :: Type -> Type #

Hashable DebugLevel Source # 
Instance details

Defined in Clash.Driver.Types

type Rep DebugLevel Source # 
Instance details

Defined in Clash.Driver.Types

type Rep DebugLevel = D1 ('MetaData "DebugLevel" "Clash.Driver.Types" "clash-lib-1.2.5-inplace" 'False) ((C1 ('MetaCons "DebugNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DebugSilent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DebugFinal" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DebugName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DebugTry" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DebugApplied" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DebugAll" 'PrefixI 'False) (U1 :: Type -> Type))))

data ClashOpts Source #

Constructors

ClashOpts 

Fields

Instances

Instances details
Hashable ClashOpts Source # 
Instance details

Defined in Clash.Driver.Types

data Manifest Source #

Information about the generated HDL between (sub)runs of the compiler

Constructors

Manifest 

Fields

  • manifestHash :: (Int, Maybe Int)

    Hash of the TopEntity and all its dependencies + (maybe) Hash of the TestBench and all its dependencies

  • successFlags :: (Int, Int, Bool)

    Compiler flags used to achieve successful compilation:

    • opt_inlineLimit
    • opt_specLimit
    • opt_floatSupport
  • portInNames :: [Text]
     
  • portInTypes :: [Text]

    The rendered versions of the types of the input ports of the TopEntity

    Used when dealing with multiple TopEntitys who have different names for types which are structurally equal

  • portOutNames :: [Text]
     
  • portOutTypes :: [Text]

    The rendered versions of the types of the output ports of the TopEntity

    Used when dealing with multiple TopEntitys who have different names for types which are structurally equal

  • componentNames :: [Text]

    Names of all the generated components for the TopEntity (does not include the names of the components of the TestBench accompanying the TopEntity).

Instances

Instances details
Read Manifest Source # 
Instance details

Defined in Clash.Driver.Types

Show Manifest Source # 
Instance details

Defined in Clash.Driver.Types