clash-lib-1.5.0: Clash: a functional hardware description language - As a library
Copyright(C) 2012-2016 University of Twente
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Util

Description

Assortment of utility function used in the Clash library

Synopsis

Documentation

class Monad m => MonadUnique m where Source #

A class that can generate unique numbers

Methods

getUniqueM :: m Int Source #

Get a new unique

Instances

Instances details
MonadUnique (RewriteMonad extra) Source # 
Instance details

Defined in Clash.Rewrite.Types

Monad m => MonadUnique (StateT Int m) Source # 
Instance details

Defined in Clash.Util

pprPanic :: String -> Doc ann -> a Source #

warnPprTrace Source #

Arguments

:: HasCallStack 
=> Bool

Trigger warning?

-> String

File name

-> Int

Line number

-> Doc ann

Message

-> a

Pass value (like trace)

-> a 

pprTrace :: String -> Doc ann -> a -> a Source #

pprTraceDebug :: String -> Doc ann -> a -> a Source #

pprDebugAndThen :: (String -> a) -> Doc ann -> Doc ann -> a Source #

curLoc :: Q Exp Source #

Create a TH expression that returns the a formatted string containing the name of the module curLoc is spliced into, and the line where it was spliced.

makeCached Source #

Arguments

:: (MonadState s m, Hashable k, Eq k) 
=> k

The key the action is associated with

-> Lens' s (HashMap k v)

The Lens to the HashMap that is the cache

-> m v

The action to cache

-> m v 

Cache the result of a monadic action

makeCachedU Source #

Arguments

:: (MonadState s m, Uniquable k) 
=> k

Key the action is associated with

-> Lens' s (UniqMap v)

Lens to the cache

-> m v

Action to cache

-> m v 

Cache the result of a monadic action using a UniqMap

makeCachedO Source #

Arguments

:: (MonadState s m, Uniquable k) 
=> k

Key the action is associated with

-> Lens' s (OMap Unique v)

Lens to the cache

-> m v

Action to cache

-> m v 

Cache the result of a monadic action using a OMap

indexNote' Source #

Arguments

:: HasCallStack 
=> String

Error message to display

-> Int

Index n

-> [a]

List to index

-> a

Error or element n

Same as indexNote with last two arguments swapped

indexNote Source #

Arguments

:: HasCallStack 
=> String

Error message to display

-> [a]

List to index

-> Int

Index n

-> a

Error or element n

Unsafe indexing, return a custom error message when indexing fails

flogBase :: Integer -> Integer -> Maybe Int Source #

x y -> floor (logBase x y), x > 1 && y > 0

clogBase :: Integer -> Integer -> Maybe Int Source #

x y -> ceiling (logBase x y), x > 1 && y > 0

pkgIdFromTypeable :: Typeable a => a -> String Source #

Get the package id of the type of a value >>> pkgIdFromTypeable (undefined :: TopEntity) "clash-prelude-0.99.3-64904d90747cb49e17166bbc86fec8678918e4ead3847193a395b258e680373c"

orElses :: [Maybe a] -> Maybe a Source #

Left-biased choice on maybes

data SrcSpan #

Source Span

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

Instances

Instances details
Eq SrcSpan 
Instance details

Defined in SrcLoc

Methods

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

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

Data SrcSpan 
Instance details

Defined in SrcLoc

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 :: forall r r'. (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

Defined in SrcLoc

Show SrcSpan 
Instance details

Defined in SrcLoc

Generic SrcSpan Source # 
Instance details

Defined in GHC.SrcLoc.Extra

Associated Types

type Rep SrcSpan :: Type -> Type #

Methods

from :: SrcSpan -> Rep SrcSpan x #

to :: Rep SrcSpan x -> SrcSpan #

Hashable SrcSpan Source # 
Instance details

Defined in GHC.SrcLoc.Extra

Methods

hashWithSalt :: Int -> SrcSpan -> Int #

hash :: SrcSpan -> Int #

Binary SrcSpan Source # 
Instance details

Defined in GHC.SrcLoc.Extra

Methods

put :: SrcSpan -> Put #

get :: Get SrcSpan #

putList :: [SrcSpan] -> Put #

NFData SrcSpan 
Instance details

Defined in SrcLoc

Methods

rnf :: SrcSpan -> () #

ToJson SrcSpan 
Instance details

Defined in SrcLoc

Methods

json :: SrcSpan -> JsonDoc #

Outputable SrcSpan 
Instance details

Defined in SrcLoc

Methods

ppr :: SrcSpan -> SDoc #

pprPrec :: Rational -> SrcSpan -> SDoc #

PrettyPrec SrcSpan Source # 
Instance details

Defined in Clash.Core.Pretty

NamedThing e => NamedThing (Located e) 
Instance details

Defined in Name

HasSrcSpan (Located a) 
Instance details

Defined in SrcLoc

type Rep SrcSpan Source # 
Instance details

Defined in GHC.SrcLoc.Extra

noSrcSpan :: SrcSpan #

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