Copyright | (C) 2013-2016 University of Twente 2016-2017 Myrtle Software Ltd 2017 QBayLogic Google Inc. 2020-2022 QBayLogic 2022 Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | None |
Language | Haskell2010 |
Type definitions used by the Driver module
Synopsis
- data ClashEnv = ClashEnv {
- envOpts :: ClashOpts
- envTyConMap :: TyConMap
- envTupleTyCons :: IntMap TyConName
- envPrimitives :: CompiledPrimMap
- envCustomReprs :: CustomReprs
- envDomains :: DomainMap
- data ClashDesign = ClashDesign {}
- data IsPrim
- data Binding a = Binding {
- bindingId :: Id
- bindingLoc :: SrcSpan
- bindingSpec :: InlineSpec
- bindingIsPrim :: IsPrim
- bindingTerm :: a
- bindingRecursive :: Bool
- type BindingMap = VarEnv (Binding Term)
- type DomainMap = HashMap Text VDomainConfiguration
- data TransformationInfo
- data DebugOpts = DebugOpts {}
- isDebugging :: DebugOpts -> Bool
- hasDebugInfo :: TransformationInfo -> String -> DebugOpts -> Bool
- hasTransformationInfo :: TransformationInfo -> DebugOpts -> Bool
- debugNone :: DebugOpts
- debugSilent :: DebugOpts
- debugFinal :: DebugOpts
- debugCount :: DebugOpts
- debugName :: DebugOpts
- debugTry :: DebugOpts
- debugApplied :: DebugOpts
- debugAll :: DebugOpts
- data ClashOpts = ClashOpts {
- opt_werror :: Bool
- opt_inlineLimit :: Int
- opt_specLimit :: Int
- opt_inlineFunctionLimit :: Word
- opt_inlineConstantLimit :: Word
- opt_evaluatorFuelLimit :: Word
- opt_debug :: DebugOpts
- opt_cachehdl :: Bool
- opt_clear :: Bool
- opt_primWarn :: Bool
- opt_color :: OverridingBool
- opt_intWidth :: Int
- opt_hdlDir :: Maybe String
- opt_hdlSyn :: HdlSyn
- opt_errorExtra :: Bool
- opt_importPaths :: [FilePath]
- opt_componentPrefix :: Maybe Text
- opt_newInlineStrat :: Bool
- opt_escapedIds :: Bool
- opt_lowerCaseBasicIds :: PreserveCase
- opt_ultra :: Bool
- opt_forceUndefined :: Maybe (Maybe Int)
- opt_checkIDir :: Bool
- opt_aggressiveXOpt :: Bool
- opt_aggressiveXOptBB :: Bool
- opt_inlineWFCacheLimit :: Word
- opt_edalize :: Bool
- opt_renderEnums :: Bool
- opt_timescalePrecision :: Period
- opt_ignoreBrokenGhcs :: Bool
- defClashOpts :: ClashOpts
- newtype SdcInfo = SdcInfo {}
- pprSDC :: SdcInfo -> Doc ()
Documentation
ClashEnv | |
|
Instances
Generic ClashEnv Source # | |
NFData ClashEnv Source # | |
Defined in Clash.Driver.Types | |
type Rep ClashEnv Source # | |
Defined in Clash.Driver.Types type Rep ClashEnv = D1 ('MetaData "ClashEnv" "Clash.Driver.Types" "clash-lib-1.9.0-inplace" 'False) (C1 ('MetaCons "ClashEnv" 'PrefixI 'True) ((S1 ('MetaSel ('Just "envOpts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClashOpts) :*: (S1 ('MetaSel ('Just "envTyConMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TyConMap) :*: S1 ('MetaSel ('Just "envTupleTyCons") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IntMap TyConName)))) :*: (S1 ('MetaSel ('Just "envPrimitives") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CompiledPrimMap) :*: (S1 ('MetaSel ('Just "envCustomReprs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CustomReprs) :*: S1 ('MetaSel ('Just "envDomains") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DomainMap))))) |
data ClashDesign Source #
Instances
NFData ClashDesign Source # | |
Defined in Clash.Driver.Types rnf :: ClashDesign -> () Source # |
Binding | |
|
Instances
type BindingMap = VarEnv (Binding Term) Source #
Global function binders
Global functions cannot be mutually recursive, only self-recursive.
data TransformationInfo Source #
Information to show about transformations during compilation.
NB: The Ord
instance compares by amount of information.
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
Options related to debugging. See ClashOpts
DebugOpts | |
|
Instances
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.
debugSilent :: DebugOpts Source #
- fclash-debug DebugSilent
debugFinal :: DebugOpts Source #
- fclash-debug DebugFinal
debugCount :: DebugOpts Source #
- fclash-debug DebugCount
debugApplied :: DebugOpts Source #
- fclash-debug DebugApplied
Options passed to Clash compiler
ClashOpts | |
|
Instances
Synopsys Design Constraint (SDC) information for a component. Currently this limited to the names and periods of clocks for create_clock.