clash-lib-1.4.6: Clash: a functional hardware description language - As a library
Copyright(C) 2013-2016 University of Twente
2016-2017 Myrtle Software Ltd
2017 QBayLogic Google Inc.
2020 QBayLogic
LicenseBSD2 (see the file LICENSE)
MaintainerQBayLogic B.V. <devops@qbaylogic.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Driver.Types

Description

Type definitions used by the Driver module

Synopsis

Documentation

data IsPrim Source #

Constructors

IsPrim

The binding is the unfolding for a primitive.

IsFun

The binding is an ordinary function.

Instances

Instances details
Eq IsPrim Source # 
Instance details

Defined in Clash.Driver.Types

Methods

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

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

Show IsPrim Source # 
Instance details

Defined in Clash.Driver.Types

Generic IsPrim Source # 
Instance details

Defined in Clash.Driver.Types

Associated Types

type Rep IsPrim :: Type -> Type #

Methods

from :: IsPrim -> Rep IsPrim x #

to :: Rep IsPrim x -> IsPrim #

Binary IsPrim Source # 
Instance details

Defined in Clash.Driver.Types

Methods

put :: IsPrim -> Put #

get :: Get IsPrim #

putList :: [IsPrim] -> Put #

NFData IsPrim Source # 
Instance details

Defined in Clash.Driver.Types

Methods

rnf :: IsPrim -> () #

type Rep IsPrim Source # 
Instance details

Defined in Clash.Driver.Types

type Rep IsPrim = D1 ('MetaData "IsPrim" "Clash.Driver.Types" "clash-lib-1.4.6-inplace" 'False) (C1 ('MetaCons "IsPrim" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IsFun" 'PrefixI 'False) (U1 :: Type -> Type))

data Binding a Source #

Constructors

Binding 

Fields

  • bindingId :: Id

    The core identifier for this binding.

  • bindingLoc :: SrcSpan

    The source location of this binding in the original source code.

  • bindingSpec :: InlineSpec

    the inline specification for this binding, in the original source code.

  • bindingIsPrim :: IsPrim

    Is the binding a core term corresponding to a primitive with a known implementation? If so, it can potentially be inlined despite being marked as NOINLINE in source.

  • bindingTerm :: a

    The term representation for this binding. This is polymorphic so alternate representations can be used if more appropriate (i.e. in the evaluator this can be Value for evaluated bindings).

Instances

Instances details
Functor Binding Source # 
Instance details

Defined in Clash.Driver.Types

Methods

fmap :: (a -> b) -> Binding a -> Binding b #

(<$) :: a -> Binding b -> Binding a #

Show a => Show (Binding a) Source # 
Instance details

Defined in Clash.Driver.Types

Methods

showsPrec :: Int -> Binding a -> ShowS #

show :: Binding a -> String #

showList :: [Binding a] -> ShowS #

Generic (Binding a) Source # 
Instance details

Defined in Clash.Driver.Types

Associated Types

type Rep (Binding a) :: Type -> Type #

Methods

from :: Binding a -> Rep (Binding a) x #

to :: Rep (Binding a) x -> Binding a #

Binary a => Binary (Binding a) Source # 
Instance details

Defined in Clash.Driver.Types

Methods

put :: Binding a -> Put #

get :: Get (Binding a) #

putList :: [Binding a] -> Put #

NFData a => NFData (Binding a) Source # 
Instance details

Defined in Clash.Driver.Types

Methods

rnf :: Binding a -> () #

type Rep (Binding a) Source # 
Instance details

Defined in Clash.Driver.Types

type BindingMap = VarEnv (Binding Term) 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.4.6-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 #

Options passed to Clash compiler

Constructors

ClashOpts 

Fields

  • opt_inlineLimit :: Int

    Change the number of times a function f can undergo inlining inside some other function g. This prevents the size of g growing dramatically.

    Command line flag: -fclash-inline-limit

  • opt_specLimit :: Int

    Change the number of times a function can undergo specialization.

    Command line flag: -fclash-spec-limit

  • opt_inlineFunctionLimit :: Word

    Set the threshold for function size. Below this threshold functions are always inlined (if it is not recursive).

    Command line flag: -fclash-inline-function-limit

  • opt_inlineConstantLimit :: Word

    Set the threshold for constant size. Below this threshold constants are always inlined. A value of 0 inlines all constants.

    Command line flag: -fclash-inline-constant-limit

  • opt_evaluatorFuelLimit :: Word

    Set the threshold for maximum unfolding depth in the evaluator. A value of zero means no potentially non-terminating binding is unfolded.

    Command line flag: -fclash-evaluator-fuel-limit

  • opt_dbgLevel :: DebugLevel

    Set the debugging mode for the compiler, exposing additional output. See DebugLevel for the available options.

    Command line flag: -fclash-debug

  • opt_dbgTransformations :: Set String

    List the transformations that are to be debugged.

    Command line flag: -fclash-debug-transformations

  • opt_dbgTransformationsFrom :: Int

    Only output debug information from (applied) transformation n

    Command line flag: -fclash-debug-transformations-from

  • opt_dbgTransformationsLimit :: Int

    Only output debug information for n (applied) transformations. If this limit is exceeded, Clash will stop normalizing.

    Command line flag: -fclash-debug-transformations-limit

  • opt_dbgRewriteHistoryFile :: Maybe FilePath

    Save all applied rewrites to a file

    Command line flag: -fclash-debug-history

  • opt_cachehdl :: Bool

    Reuse previously generated output from Clash. Only caches topentities.

    Command line flag: -fclash-no-cache

  • opt_clear :: Bool

    Remove HDL directories before writing to them. By default, Clash will only write to non-empty directories if it can prove all files in it are generated by a previous run. This option applies to directories of the various top entities, i.e., the subdirectories made in the directory passed in with -fclash-hdldir. Note that Clash will still use a cache if it can.

    Command line flag: -fclash-clear

  • opt_primWarn :: Bool

    Disable warnings for primitives

    Command line flag: -fclash-no-prim-warn

  • opt_color :: OverridingBool

    Show colors in debug output

    Command line flag: -fclash-no-prim-warn

  • opt_intWidth :: Int

    Set the bit width for the IntWordInteger types. The only allowed values are 32 or 64.

  • opt_hdlDir :: Maybe String

    Directory to save HDL files to

  • opt_hdlSyn :: HdlSyn

    Synthesis target. See HdlSyn for available options.

  • opt_errorExtra :: Bool

    Show additional information in error messages

  • opt_floatSupport :: Bool

    Treat floats as a BitVector. Note that operations on floating are still not supported, use vendor primitives instead.

  • opt_importPaths :: [FilePath]

    Paths where Clash should look for modules

  • opt_componentPrefix :: Maybe Text

    Prefix components with given string

  • opt_newInlineStrat :: Bool

    Use new inline strategy. Functions marked NOINLINE will get their own HDL module.

  • opt_escapedIds :: Bool
  • opt_lowerCaseBasicIds :: PreserveCase

    Force all generated basic identifiers to lowercase. Among others, this affects module and file names.

  • opt_ultra :: Bool

    Perform a high-effort compile, trading improved performance for potentially much longer compile times.

    Name inspired by Design Compiler's compile_ultra flag.

  • opt_forceUndefined :: Maybe (Maybe Int)
    • Nothing: generate undefined's in the HDL
    • Just Nothing: replace undefined's by a constant in the HDL; the compiler decides what's best
    • Just (Just x): replace undefined's by x in the HDL
  • opt_checkIDir :: Bool

    Check whether paths specified in opt_importPaths exists on the filesystem.

  • opt_aggressiveXOpt :: Bool

    Enable aggressive X optimization, which may remove undefineds from generated HDL by replaced with defined alternatives.

  • opt_aggressiveXOptBB :: Bool

    Enable aggressive X optimization, which may remove undefineds from HDL generated by blackboxes. This enables the ~ISUNDEFINED template tag.

  • opt_inlineWFCacheLimit :: Word

    At what size do we cache normalized work-free top-level binders.

  • opt_edalize :: Bool

    Generate an EDAM file for use with Edalize.

Instances

Instances details
Eq ClashOpts Source # 
Instance details

Defined in Clash.Driver.Types

Hashable ClashOpts Source # 
Instance details

Defined in Clash.Driver.Types

newtype SdcInfo Source #

Synopsys Design Constraint (SDC) information for a component. Currently this limited to the names and periods of clocks for create_clock.

Constructors

SdcInfo 

Fields

Instances

Instances details
Show SdcInfo Source # 
Instance details

Defined in Clash.Driver.Types

pprSDC :: SdcInfo -> Doc () Source #

Render an SDC file from an SdcInfo. The clock periods, waveforms, and targets are all hardcoded.