clash-lib-1.7.0: 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-2022 QBayLogic
2022 Google Inc.
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 ClashEnv Source #

Instances

Instances details
Generic ClashEnv Source # 
Instance details

Defined in Clash.Driver.Types

Associated Types

type Rep ClashEnv :: Type -> Type #

Methods

from :: ClashEnv -> Rep ClashEnv x #

to :: Rep ClashEnv x -> ClashEnv #

NFData ClashEnv Source # 
Instance details

Defined in Clash.Driver.Types

Methods

rnf :: ClashEnv -> () #

type Rep ClashEnv Source # 
Instance details

Defined in Clash.Driver.Types

data ClashDesign Source #

Instances

Instances details
NFData ClashDesign Source # 
Instance details

Defined in Clash.Driver.Types

Methods

rnf :: ClashDesign -> () #

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.7.0-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).

  • bindingRecursive :: Bool

    Whether the binding is recursive.

    TODO Ideally the BindingMap would store recursive and non-recursive bindings in a way similar to Let / Letrec. GHC also does this.

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.

type DomainMap = HashMap Text VDomainConfiguration Source #

data TransformationInfo Source #

Information to show about transformations during compilation.

NB: The Ord instance compares by amount of information.

Constructors

None

Show no information about transformations.

FinalTerm

Show the final term after all applied transformations.

AppliedName

Show the name of every transformation that is applied.

AppliedTerm

Show the name and result of every transformation that is applied.

TryName

Show the name of every transformation that is attempted, and the result of every transformation that is applied.

TryTerm

Show the name and input to every transformation that is applied, and the result of every transformation that is applied.

Instances

Instances details
Eq TransformationInfo Source # 
Instance details

Defined in Clash.Driver.Types

Ord TransformationInfo Source # 
Instance details

Defined in Clash.Driver.Types

Read TransformationInfo Source # 
Instance details

Defined in Clash.Driver.Types

Show TransformationInfo Source # 
Instance details

Defined in Clash.Driver.Types

Generic TransformationInfo Source # 
Instance details

Defined in Clash.Driver.Types

Associated Types

type Rep TransformationInfo :: Type -> Type #

Hashable TransformationInfo Source # 
Instance details

Defined in Clash.Driver.Types

NFData TransformationInfo Source # 
Instance details

Defined in Clash.Driver.Types

Methods

rnf :: TransformationInfo -> () #

type Rep TransformationInfo Source # 
Instance details

Defined in Clash.Driver.Types

type Rep TransformationInfo = D1 ('MetaData "TransformationInfo" "Clash.Driver.Types" "clash-lib-1.7.0-inplace" 'False) ((C1 ('MetaCons "None" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FinalTerm" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AppliedName" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "AppliedTerm" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TryName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TryTerm" 'PrefixI 'False) (U1 :: Type -> Type))))

data DebugOpts Source #

Options related to debugging. See ClashOpts

Constructors

DebugOpts 

Fields

  • dbg_invariants :: Bool

    Check that the results of applied transformations do not violate the invariants for rewriting (e.g. no accidental shadowing, or type changes).

    Command line flag: -fclash-debug-invariants

  • dbg_transformationInfo :: TransformationInfo

    The information to show when debugging a transformation. See the TransformationInfo type for different configurations.

    Command line flag: -fclash-debug-info (None|FinalTerm|AppliedName|AppliedTerm|TryName|TryTerm)

  • dbg_transformations :: Set String

    List the transformations that are being debugged. When the set is empty, all transformations are debugged.

    Command line flag: -fclash-debug-transformations t1[,t2...]

  • dbg_countTransformations :: Bool

    Count how many times transformations are applied and provide a summary at the end of normalization. This includes all transformations, not just those in dbg_transformations.

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

  • dbg_transformationsFrom :: Maybe Word

    Debug transformations applied after the nth transformation applied. This includes all transformations, not just those in dbg_transformations.

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

  • dbg_transformationsLimit :: Maybe Word

    Debug up to the nth applied transformation. If this limit is exceeded then Clash will error. This includes all transformations, not just those in dbg_transformations.

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

  • dbg_historyFile :: Maybe FilePath

    Save information about all applied transformations to a history file for use with clash-term.

    Command line flag: -fclash-debug-history[=FILE]

Instances

Instances details
Eq DebugOpts Source # 
Instance details

Defined in Clash.Driver.Types

Show DebugOpts Source # 
Instance details

Defined in Clash.Driver.Types

Generic DebugOpts Source # 
Instance details

Defined in Clash.Driver.Types

Associated Types

type Rep DebugOpts :: Type -> Type #

Hashable DebugOpts Source # 
Instance details

Defined in Clash.Driver.Types

NFData DebugOpts Source # 
Instance details

Defined in Clash.Driver.Types

Methods

rnf :: DebugOpts -> () #

type Rep DebugOpts Source # 
Instance details

Defined in Clash.Driver.Types

type Rep DebugOpts = D1 ('MetaData "DebugOpts" "Clash.Driver.Types" "clash-lib-1.7.0-inplace" 'False) (C1 ('MetaCons "DebugOpts" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dbg_invariants") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "dbg_transformationInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TransformationInfo) :*: S1 ('MetaSel ('Just "dbg_transformations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set String)))) :*: ((S1 ('MetaSel ('Just "dbg_countTransformations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "dbg_transformationsFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word))) :*: (S1 ('MetaSel ('Just "dbg_transformationsLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word)) :*: S1 ('MetaSel ('Just "dbg_historyFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath))))))

isDebugging :: DebugOpts -> Bool Source #

Check whether the debugging options mean the compiler is debugging. This is true only if at least one debugging feature is enabled, namely one of

  • checking for invariants
  • showing info for transformations
  • counting applied transformations
  • limiting the number of transformations

Other flags, such as writing to a history file or offsetting which applied transformation to show information from do not affect the result, as it is possible to enable these but still not perform any debugging checks in functions like applyDebug. If this is no longer the case, this function will need to be changed.

hasDebugInfo :: TransformationInfo -> String -> DebugOpts -> Bool Source #

Check whether the requested information is available to the specified transformation according to the options. e.g.

traceIf (hasDebugInfo AppliedName name opts) ("Trace something using: " <> show name)

This accounts for the set of transformations which are being debugged. For a check which is agnostic to the a transformation, see hasTransformationInfo.

hasTransformationInfo :: TransformationInfo -> DebugOpts -> Bool Source #

Check that the transformation info shown supports the requested info. If the call-site is in the context of a particular transformation, hasDebugInfo should be used instead.

debugNone :: DebugOpts Source #

  • fclash-debug DebugNone

debugSilent :: DebugOpts Source #

  • fclash-debug DebugSilent

debugFinal :: DebugOpts Source #

  • fclash-debug DebugFinal

debugCount :: DebugOpts Source #

  • fclash-debug DebugCount

debugName :: DebugOpts Source #

  • fclash-debug DebugName

debugTry :: DebugOpts Source #

  • fclash-debug DebugTry

debugApplied :: DebugOpts Source #

  • fclash-debug DebugApplied

debugAll :: DebugOpts Source #

  • fclash-debug DebugAll

data ClashOpts Source #

Options passed to Clash compiler

Constructors

ClashOpts 

Fields

  • opt_werror :: Bool

    Are warnings treated as errors.

    Command line flag: -Werror

  • 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_debug :: DebugOpts

    Options which control debugging. See DebugOpts.

  • 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: -fdiagnostics-color

  • 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_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.

  • opt_renderEnums :: Bool

    Render sum types with all zero-width fields as enums where supported, as opposed to rendering them as bitvectors.

  • opt_timescalePrecision :: Period

    Timescale precision set in Verilog files. E.g., setting this would sets the second part of `timescale 100fs/100fs.

Instances

Instances details
Eq ClashOpts Source # 
Instance details

Defined in Clash.Driver.Types

Show ClashOpts Source # 
Instance details

Defined in Clash.Driver.Types

Hashable ClashOpts Source # 
Instance details

Defined in Clash.Driver.Types

NFData ClashOpts Source # 
Instance details

Defined in Clash.Driver.Types

Methods

rnf :: ClashOpts -> () #

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

pprSDC :: SdcInfo -> Doc () Source #

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