clash-lib-0.99.1: CAES Language for Synchronous Hardware - As a Library

Copyright(C) 2013-2016 University of Twente
2016-2017 Myrtle Software Ltd
2017 QBayLogic Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Driver.Types

Description

Type definitions used by the Driver module

Synopsis

Documentation

data Manifest Source #

Information about the generated HDL between (sub)runs of the compiler

Constructors

Manifest 

Fields

  • manifestHash :: (Int, Maybe Int)

    Hash of the TopEntity and all its dependencies + (maybe) Hash of the TestBench and all its dependencies

  • portInNames :: [Text]
     
  • portInTypes :: [Text]

    The rendered versions of the types of the input ports of the TopEntity

    Used when dealing with multiple TopEntitys who have different names for types which are structurally equal

  • portOutNames :: [Text]
     
  • portOutTypes :: [Text]

    The rendered versions of the types of the output ports of the TopEntity

    Used when dealing with multiple TopEntitys who have different names for types which are structurally equal

  • componentNames :: [Text]

    Names of all the generated components for the TopEntity (does not include the names of the components of the TestBench accompanying the TopEntity).

data DebugLevel Source #

Debug Message Verbosity

Constructors

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

type BindingMap = HashMap TmOccName (TmName, Type, SrcSpan, InlineSpec, Term) Source #

Global function binders

Global functions cannot be mutually recursive, only self-recursive

data SrcSpan #

Source Span

A SrcSpan identifies either a specific portion of a text file or a human-readable description of a location.

Instances
Eq SrcSpan 
Instance details

Methods

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

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

Data SrcSpan 
Instance details

Methods

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 
Instance details
Show SrcSpan 
Instance details
Generic SrcSpan # 
Instance details

Associated Types

type Rep SrcSpan :: * -> * #

Methods

from :: SrcSpan -> Rep SrcSpan x #

to :: Rep SrcSpan x -> SrcSpan #

NFData SrcSpan 
Instance details

Methods

rnf :: SrcSpan -> () #

ToJson SrcSpan 
Instance details

Methods

json :: SrcSpan -> JsonDoc #

Outputable SrcSpan 
Instance details

Methods

ppr :: SrcSpan -> SDoc #

pprPrec :: Rational -> SrcSpan -> SDoc #

Hashable SrcSpan 
Instance details

Methods

hashWithSalt :: Int -> SrcSpan -> Int

hash :: SrcSpan -> Int

Alpha SrcSpan 
Instance details

Methods

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

isTerm :: SrcSpan -> All

isEmbed :: SrcSpan -> Bool

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)

acompare' :: AlphaCtx -> SrcSpan -> SrcSpan -> Ordering

type Rep SrcSpan # 
Instance details

noSrcSpan :: SrcSpan #

Built-in "bad" SrcSpans for common sources of location uncertainty