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 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
- liftState :: MonadState s m => Lens' s s' -> State s' a -> m a
- firstM :: Functor f => (a -> f c) -> (a, b) -> f (c, b)
- secondM :: Functor f => (b -> f c) -> (a, b) -> f (a, c)
- combineM :: Applicative f => (a -> f b) -> (c -> f d) -> (a, c) -> f (b, d)
- traceIf :: Bool -> String -> a -> a
- partitionM :: Monad m => (a -> m Bool) -> [a] -> m ([a], [a])
- mapAccumLM :: Monad m => (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y])
- ifThenElse :: (a -> Bool) -> (a -> b) -> (a -> b) -> a -> b
- (<:>) :: Applicative f => f a -> f [a] -> f [a]
- indexMaybe :: [a] -> Int -> Maybe a
- indexNote :: String -> [a] -> Int -> a
- headMaybe :: [a] -> Maybe a
- tailMaybe :: [a] -> Maybe [a]
- splitAtList :: [b] -> [a] -> ([a], [a])
- clashLibVersion :: Version
- countEq :: Eq a => a -> [a] -> Int
- flogBase :: Integer -> Integer -> Maybe Int
- clogBase :: Integer -> Integer -> Maybe Int
- equalLength :: [a] -> [b] -> Bool
- neLength :: [a] -> [b] -> Bool
- zipEqual :: [a] -> [b] -> [(a, b)]
- debugIsOn :: Bool
- anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool
- pkgIdFromTypeable :: Typeable a => a -> String
- reportTimeDiff :: UTCTime -> UTCTime -> String
- uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
- allM :: Monad m => (a -> m Bool) -> [a] -> m Bool
- orElse :: Maybe a -> Maybe a -> Maybe a
- orElses :: [Maybe a] -> Maybe a
- class Functor f => Applicative (f :: Type -> Type) where
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- first :: Arrow a => a b c -> a (b, d) (c, d)
- (***) :: Arrow a => a b c -> a b' c' -> a (b, b') (c, c')
- second :: Arrow a => a b c -> a (d, b) (d, c)
- (&&&) :: Arrow a => a b c -> a b c' -> a b (c, c')
- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
- makeLenses :: Name -> DecsQ
- data SrcSpan
- noSrcSpan :: SrcSpan
- type HasCallStack = ?callStack :: CallStack
Documentation
class 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 | |
=> Lens' s s' | Lens to the State in the higher-layer monad |
-> State s' a | The State-action to perform |
-> m a |
Run a State-action using the State that is stored in a higher-layer Monad
combineM :: Applicative f => (a -> f b) -> (c -> f d) -> (a, c) -> f (b, d) Source #
mapAccumLM :: Monad m => (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y]) Source #
Monadic version of mapAccumL
ifThenElse :: (a -> Bool) -> (a -> b) -> (a -> b) -> a -> b Source #
if-then-else as a function on an argument
(<:>) :: Applicative f => f a -> f [a] -> f [a] infixr 5 Source #
Applicative version of 'GHC.Types.(:)'
indexMaybe :: [a] -> Int -> Maybe a Source #
Safe indexing, returns a Nothing
if the index does not exist
indexNote :: String -> [a] -> Int -> a Source #
Unsafe indexing, return a custom error message when indexing fails
splitAtList :: [b] -> [a] -> ([a], [a]) Source #
Split the second list at the length of the first list
Return number of occurrences of an item in a list
equalLength :: [a] -> [b] -> Bool Source #
Determine whether two lists are of equal length
zipEqual :: [a] -> [b] -> [(a, b)] Source #
Zip two lists of equal length
NB Errors out for a 1 compiler when the two lists are not of equal length
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"
uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d Source #
Converts a curried function to a function on a triple
class Functor f => Applicative (f :: Type -> Type) where #
A functor with application, providing operations to
A minimal complete definition must include implementations of pure
and of either <*>
or liftA2
. If it defines both, then they must behave
the same as their default definitions:
(<*>
) =liftA2
id
liftA2
f x y = f<$>
x<*>
y
Further, any definition must satisfy the following:
- Identity
pure
id
<*>
v = v- Composition
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w)- Homomorphism
pure
f<*>
pure
x =pure
(f x)- Interchange
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
It may be useful to note that supposing
forall x y. p (q x y) = f x . g y
it follows from the above that
liftA2
p (liftA2
q u v) =liftA2
f u .liftA2
g v
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*>
that is more
efficient than the default one.
Instances
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap
.
The name of this operator is an allusion to $
.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $
is function application, <$>
is function
application lifted over a Functor
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an
Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #
Left-to-right composition of Kleisli arrows.
first :: Arrow a => a b c -> a (b, d) (c, d) #
Send the first component of the input through the argument arrow, and copy the rest unchanged to the output.
(***) :: Arrow a => a b c -> a b' c' -> a (b, b') (c, c') infixr 3 #
Split the input between the two argument arrows and combine their output. Note that this is in general not a functor.
The default definition may be overridden with a more efficient version if desired.
second :: Arrow a => a b c -> a (d, b) (d, c) #
A mirror image of first
.
The default definition may be overridden with a more efficient version if desired.
(&&&) :: Arrow a => a b c -> a b c' -> a b (c, c') infixr 3 #
Fanout: send the input to both argument arrows and combine their output.
The default definition may be overridden with a more efficient version if desired.
makeLenses :: Name -> DecsQ #
Build lenses (and traversals) with a sensible default configuration.
e.g.
data FooBar = Foo { _x, _y ::Int
} | Bar { _x ::Int
}makeLenses
''FooBar
will create
x ::Lens'
FooBarInt
x f (Foo a b) = (\a' -> Foo a' b) <$> f a x f (Bar a) = Bar <$> f a y ::Traversal'
FooBarInt
y f (Foo a b) = (\b' -> Foo a b') <$> f b y _ c@(Bar _) = pure c
makeLenses
=makeLensesWith
lensRules
Source Span
A SrcSpan
identifies either a specific portion of a text file
or a human-readable description of a location.
Instances
type HasCallStack = ?callStack :: CallStack #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack
is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: base-4.9.0.0