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
- data Manifest = Manifest {
- manifestHash :: (Int, Maybe Int)
- portInNames :: [Text]
- portInTypes :: [Text]
- portOutNames :: [Text]
- portOutTypes :: [Text]
- componentNames :: [Text]
- data ClashException = ClashException SrcSpan String (Maybe String)
- 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_intWidth :: Int
- opt_hdlDir :: Maybe String
- opt_hdlSyn :: HdlSyn
- opt_errorExtra :: Bool
- opt_floatSupport :: Bool
- opt_allowZero :: Bool
- opt_importPaths :: [FilePath]
- data DebugLevel
- type BindingMap = HashMap TmOccName (TmName, Type, SrcSpan, InlineSpec, Term)
- data SrcSpan
- noSrcSpan :: SrcSpan
Documentation
Information about the generated HDL between (sub)runs of the compiler
Manifest | |
|
data ClashException Source #
Instances
Show ClashException Source # | |
Defined in Clash.Driver.Types showsPrec :: Int -> ClashException -> ShowS # show :: ClashException -> String # showList :: [ClashException] -> ShowS # | |
Exception ClashException Source # | |
Defined in Clash.Driver.Types |
ClashOpts | |
|
data DebugLevel Source #
Debug Message Verbosity
DebugNone | Don't show debug messages |
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] # |
type BindingMap = HashMap TmOccName (TmName, Type, SrcSpan, InlineSpec, Term) Source #
Global function binders
Global functions cannot be mutually recursive, only self-recursive
Source Span
A SrcSpan
identifies either a specific portion of a text file
or a human-readable description of a location.
Instances
Eq SrcSpan | |
Data SrcSpan | |
Defined in SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcSpan -> c SrcSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcSpan # toConstr :: SrcSpan -> Constr # dataTypeOf :: SrcSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcSpan) # gmapT :: (forall b. Data b => b -> b) -> SrcSpan -> SrcSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # | |
Ord SrcSpan | |
Show SrcSpan | |
Generic SrcSpan # | |
NFData SrcSpan | |
ToJson SrcSpan | |
Outputable SrcSpan | |
Hashable SrcSpan | |
Defined in GHC.SrcLoc.Extra | |
Alpha SrcSpan | |
Defined in GHC.SrcLoc.Extra aeq' :: AlphaCtx -> SrcSpan -> SrcSpan -> Bool fvAny' :: (Contravariant f, Applicative f) => AlphaCtx -> (AnyName -> f AnyName) -> SrcSpan -> f SrcSpan close :: AlphaCtx -> NamePatFind -> SrcSpan -> SrcSpan open :: AlphaCtx -> NthPatFind -> SrcSpan -> SrcSpan isPat :: SrcSpan -> DisjointSet AnyName nthPatFind :: SrcSpan -> NthPatFind namePatFind :: SrcSpan -> NamePatFind swaps' :: AlphaCtx -> Perm AnyName -> SrcSpan -> SrcSpan lfreshen' :: LFresh m => AlphaCtx -> SrcSpan -> (SrcSpan -> Perm AnyName -> m b) -> m b freshen' :: Fresh m => AlphaCtx -> SrcSpan -> m (SrcSpan, Perm AnyName) | |
type Rep SrcSpan # | |
Defined in GHC.SrcLoc.Extra type Rep SrcSpan = D1 (MetaData "SrcSpan" "SrcLoc" "ghc" False) (C1 (MetaCons "RealSrcSpan" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RealSrcSpan)) :+: C1 (MetaCons "UnhelpfulSpan" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FastString))) |