Copyright | (C) 2013-2016 University of Twente 2016-2017 Myrtle Software Ltd 2017 QBayLogic Google Inc. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Type definitions used by the Driver module
Synopsis
- type BindingMap = VarEnv (Id, SrcSpan, InlineSpec, Term)
- data DebugLevel
- data ClashOpts = ClashOpts {
- opt_inlineLimit :: Int
- opt_specLimit :: Int
- opt_inlineFunctionLimit :: Word
- opt_inlineConstantLimit :: Word
- opt_dbgLevel :: DebugLevel
- opt_cachehdl :: Bool
- opt_cleanhdl :: Bool
- opt_primWarn :: Bool
- opt_color :: OverridingBool
- opt_intWidth :: Int
- opt_hdlDir :: Maybe String
- opt_hdlSyn :: HdlSyn
- opt_errorExtra :: Bool
- opt_floatSupport :: Bool
- opt_importPaths :: [FilePath]
- opt_componentPrefix :: Maybe String
- opt_newInlineStrat :: Bool
- opt_escapedIds :: Bool
- opt_ultra :: Bool
- opt_forceUndefined :: Maybe (Maybe Int)
- opt_checkIDir :: Bool
- defClashOpts :: ClashOpts
- data Manifest = Manifest {
- manifestHash :: (Int, Maybe Int)
- portInNames :: [Text]
- portInTypes :: [Text]
- portOutNames :: [Text]
- portOutTypes :: [Text]
- componentNames :: [Text]
Documentation
type BindingMap = VarEnv (Id, SrcSpan, InlineSpec, Term) Source #
Global function binders
Global functions cannot be mutually recursive, only self-recursive
data DebugLevel Source #
Debug Message Verbosity
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 | Names of applied transformations |
DebugApplied | Show sub-expressions after a successful rewrite |
DebugAll | Show all sub-expressions on which a rewrite is attempted |
Instances
Eq DebugLevel Source # | |
Defined in Clash.Driver.Types (==) :: DebugLevel -> DebugLevel -> Bool # (/=) :: DebugLevel -> DebugLevel -> Bool # | |
Ord DebugLevel Source # | |
Defined in Clash.Driver.Types compare :: DebugLevel -> DebugLevel -> Ordering # (<) :: DebugLevel -> DebugLevel -> Bool # (<=) :: DebugLevel -> DebugLevel -> Bool # (>) :: DebugLevel -> DebugLevel -> Bool # (>=) :: DebugLevel -> DebugLevel -> Bool # max :: DebugLevel -> DebugLevel -> DebugLevel # min :: DebugLevel -> DebugLevel -> DebugLevel # | |
Read DebugLevel Source # | |
Defined in Clash.Driver.Types readsPrec :: Int -> ReadS DebugLevel # readList :: ReadS [DebugLevel] # readPrec :: ReadPrec DebugLevel # readListPrec :: ReadPrec [DebugLevel] # |
ClashOpts | |
|
Information about the generated HDL between (sub)runs of the compiler
Manifest | |
|