Copyright | (C) 2012-2016 University of Twente |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | None |
Language | Haskell2010 |
Assortment of utility function used in the Clash library
Synopsis
- class Monad m => MonadUnique m where
- getUniqueM :: m Int
- data ClashException = ClashException SrcSpan String (Maybe String)
- assertPanic :: String -> Int -> a
- assertPprPanic :: HasCallStack => String -> Int -> Doc ann -> a
- pprPanic :: String -> Doc ann -> a
- callStackDoc :: HasCallStack => Doc ann
- warnPprTrace :: HasCallStack => Bool -> String -> Int -> Doc ann -> a -> a
- pprTrace :: String -> Doc ann -> a -> a
- pprTraceDebug :: String -> Doc ann -> a -> a
- pprDebugAndThen :: (String -> a) -> Doc ann -> Doc ann -> a
- curLoc :: Q Exp
- makeCached :: (MonadState s m, Hashable k, Eq k) => k -> Lens' s (HashMap k v) -> m v -> m v
- makeCachedU :: (MonadState s m, Uniquable k) => k -> Lens' s (UniqMap v) -> m v -> m v
- makeCachedO :: (MonadState s m, Uniquable k) => k -> Lens' s (OMap Unique v) -> m v -> m v
- indexNote' :: HasCallStack => String -> Int -> [a] -> a
- indexNote :: HasCallStack => String -> [a] -> Int -> a
- clashLibVersion :: Version
- flogBase :: Integer -> Integer -> Maybe Int
- clogBase :: Integer -> Integer -> Maybe Int
- pkgIdFromTypeable :: Typeable a => a -> String
- reportTimeDiff :: UTCTime -> UTCTime -> String
- orElses :: [Maybe a] -> Maybe a
- wantedLanguageExtensions :: [Extension]
- unwantedLanguageExtensions :: [Extension]
- thenCompare :: Ordering -> Ordering -> Ordering
- hoistMaybe :: Applicative m => Maybe b -> MaybeT m b
- data SrcSpan
- noSrcSpan :: SrcSpan
Documentation
class Monad m => MonadUnique m where Source #
A class that can generate unique numbers
getUniqueM :: m Int Source #
Get a new unique
Instances
MonadUnique (RewriteMonad extra) Source # | |
Defined in Clash.Rewrite.Types getUniqueM :: RewriteMonad extra Int Source # | |
Monad m => MonadUnique (StateT Int m) Source # | |
Defined in Clash.Util |
data ClashException Source #
Instances
Show ClashException Source # | |
Defined in Clash.Util showsPrec :: Int -> ClashException -> ShowS # show :: ClashException -> String # showList :: [ClashException] -> ShowS # | |
Exception ClashException Source # | |
Defined in Clash.Util |
assertPanic :: String -> Int -> a Source #
assertPprPanic :: HasCallStack => String -> Int -> Doc ann -> a Source #
callStackDoc :: HasCallStack => Doc ann Source #
:: HasCallStack | |
=> Bool | Trigger warning? |
-> String | File name |
-> Int | Line number |
-> Doc ann | Message |
-> a | Pass value (like trace) |
-> a |
pprTraceDebug :: String -> Doc ann -> a -> a 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.
:: (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
:: (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
:: (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
:: 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
:: 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
pkgIdFromTypeable :: Typeable a => a -> String Source #
Get the package id of the type of a value
>>>
pkgIdFromTypeable (0 :: Unsigned 32)
"clash-prelude-...
hoistMaybe :: Applicative m => Maybe b -> MaybeT m b Source #
Source Span
A SrcSpan
identifies either a specific portion of a text file
or a human-readable description of a location.