Copyright | (C) 2016 University of Twente 2017 QBayLogic Google Inc. 2017-2019 Myrtle Software Ltd |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
XException
: An exception for uninitialized values
>>>
show (errorX "undefined" :: Integer, 4 :: Int)
"(*** Exception: X: undefined CallStack (from HasCallStack): ...>>>
showX (errorX "undefined" :: Integer, 4 :: Int)
"(X,4)"
Synopsis
- newtype XException = XException String
- errorX :: HasCallStack => String -> a
- isX :: a -> Either String a
- hasX :: NFData a => a -> Either String a
- maybeIsX :: a -> Maybe a
- maybeHasX :: NFData a => a -> Maybe a
- fromJustX :: HasCallStack => Maybe a -> a
- undefined :: HasCallStack => a
- xToErrorCtx :: String -> a -> a
- xToError :: HasCallStack => a -> a
- class ShowX a where
- showsX :: ShowX a => a -> ShowS
- printX :: ShowX a => a -> IO ()
- showsPrecXWith :: (Int -> a -> ShowS) -> Int -> a -> ShowS
- seqX :: a -> b -> b
- forceX :: NFDataX a => a -> a
- deepseqX :: NFDataX a => a -> b -> b
- rwhnfX :: a -> ()
- defaultSeqX :: NFDataX a => a -> b -> b
- hwSeqX :: a -> b -> b
- class NFDataX a where
- deepErrorX :: HasCallStack => String -> a
- hasUndefined :: a -> Bool
- ensureSpine :: a -> a
- rnfX :: a -> ()
XException
: An exception for uninitialized values
newtype XException Source #
An exception representing an "uninitialized" value.
Instances
Show XException Source # | |
Defined in Clash.XException.Internal showsPrec :: Int -> XException -> ShowS # show :: XException -> String # showList :: [XException] -> ShowS # | |
Exception XException Source # | |
Defined in Clash.XException.Internal toException :: XException -> SomeException # fromException :: SomeException -> Maybe XException # displayException :: XException -> String # |
errorX :: HasCallStack => String -> a Source #
Like error
, but throwing an XException
instead of an ErrorCall
The ShowX
methods print these error-values as "X"; instead of error'ing
out with an exception.
isX :: a -> Either String a Source #
Evaluate a value to WHNF, returning
if is a Left
msgXException
.
isX 42 = Right 42 isX (XException msg) = Left msg isX (3, XException msg) = Right (3, XException msg) isX (3, _|_) = Right (3, _|_) isX _|_ = _|_
hasX :: NFData a => a -> Either String a Source #
Fully evaluate a value, returning
if it throws Left
msgXException
.
If you want to determine if a value contains undefined parts, use
hasUndefined
instead.
hasX 42 = Right 42 hasX (XException msg) = Left msg hasX (3, XException msg) = Left msg hasX (3, _|_) = _|_ hasX _|_ = _|_
If a data structure contains multiple XException
s, the "first" message is
picked according to the implementation of rnf
.
maybeIsX :: a -> Maybe a Source #
Evaluate a value to WHNF, returning Nothing
if it throws XException
.
maybeIsX 42 = Just 42 maybeIsX (XException msg) = Nothing maybeIsX (3, XException msg) = Just (3, XException msg) maybeIsX (3, _|_) = Just (3, _|_) maybeIsX _|_ = _|_
maybeHasX :: NFData a => a -> Maybe a Source #
Fully evaluate a value, returning Nothing
if it throws XException
.
maybeHasX 42 = Just 42 maybeHasX (XException msg) = Nothing maybeHasX (3, XException msg) = Nothing maybeHasX (3, _|_) = _|_ maybeHasX _|_ = _|_
fromJustX :: HasCallStack => Maybe a -> a Source #
Same as fromJust
, but returns a bottom/undefined value that
other Clash constructs are aware of.
undefined :: HasCallStack => a Source #
Call to errorX
with default string
xToErrorCtx :: String -> a -> a Source #
Convert XException
to ErrorCall
This is useful when tracking the source of XException
that gets eaten up by
pack
inside of your circuit; since
pack
translates XException
into undefined bits.
So for example if you have some large function f:
f a b = ... pack a ... pack b ...
Where it is basically an error if either a or b ever throws an XException
,
and so you want that to be reported the moment a or b is used, instead of
it being thrown when evaluating the result of f, then do:
{-# LANGUAGE ViewPatterns #-} f (xToErrorCtx "a is X" -> a) (xToErrorCtx "b is X" -> b) = ...
Where we pass an extra string, for context, to know which argument evaluated
to an XException
. We can also use BangPatterns to report the potential
XException
being thrown by a or b even earlier, i.e. when f is applied:
{-# LANGUAGE ViewPatterns, BangPatterns #-} f (xToErrorCtx "a is X" -> !a) (xToErrorCtx "b is X" -> !b) = ...
NB: Fully synthesizable, so doesn't have to be removed before synthesis
Example
>>>
:set -XViewPatterns -XDataKinds
>>>
import Clash.Sized.BitVector
>>>
import GHC.Stack
>>>
:{
let h, h' :: Bit -> BitVector 8 -> BitVector 8 h (xToErrorCtx "a is X" -> a) (xToErrorCtx "b is X" -> b) = slice d7 d0 (pack a ++# b) h' a b = slice d7 d0 (pack a ++# b) :}
>>>
h' (errorX "QQ") 3
0000_0011>>>
h (errorX "QQ") 3
*** Exception: a is X X: QQ CallStack (from HasCallStack): errorX, called at ...
xToError :: HasCallStack => a -> a Source #
Convert XException
to ErrorCall
This is useful when tracking the source of XException
that gets eaten up by
pack
inside of your circuit; since
pack
translates XException
into undefined bits.
So for example if you have some large function f:
f a b = ... pack a ... pack b ...
Where it is basically an error if either a or b ever throws an XException
,
and so you want that to be reported the moment a or b is used, instead of
it being thrown when evaluating the result of f, then do:
{-# LANGUAGE ViewPatterns #-} f (xToError -> a) (xToError -> b) = ...
Unlike xToErrorCtx
, where we have an extra String argument to distinguish
one call to xToError
to the other, xToError
will use the CallStack
mechanism to aid the user in distinguishing different call to xToError
.
We can also use BangPatterns to report the potential XException
being
thrown by a or b even earlier, i.e. when f is applied:
{-# LANGUAGE ViewPatterns, BangPatterns #-} f (xToError -> !a) (xToError -> !b) = ...
NB: Fully synthesizable, so doesn't have to be removed before synthesis
Example
>>>
:set -XViewPatterns -XDataKinds
>>>
import Clash.Sized.BitVector
>>>
import GHC.Stack
>>>
:{
let f, g, h, h' :: HasCallStack => Bit -> BitVector 8 -> BitVector 8 f = g g = h h (xToError -> a) (xToError -> b) = slice d7 d0 (pack a ++# b) h' a b = slice d7 d0 (pack a ++# b) :}
>>>
h' (errorX "QQ") 3
0000_0011>>>
f (errorX "QQ") 3
*** Exception: CallStack (from HasCallStack): xToError, called at ... h, called at ... g, called at ... f, called at ... X: QQ CallStack (from HasCallStack): errorX, called at ...
Printing XException
s as "X"
Like the Show
class, but values that normally throw an XException
are
converted to "X", instead of error'ing out with an exception.
>>>
show (errorX "undefined" :: Integer, 4 :: Int)
"(*** Exception: X: undefined CallStack (from HasCallStack): ...>>>
showX (errorX "undefined" :: Integer, 4 :: Int)
"(X,4)"
Can be derived using Generics
:
{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} import Clash.Prelude import GHC.Generics data T = MkTA Int | MkTB Bool deriving (Show,Generic,ShowX)
Nothing
showsPrecX :: Int -> a -> ShowS Source #
Like showsPrec
, but values that normally throw an XException
are
converted to "X", instead of error'ing out with an exception.
Like show
, but values that normally throw an XException
are
converted to "X", instead of error'ing out with an exception.
showListX :: [a] -> ShowS Source #
Like showList
, but values that normally throw an XException
are
converted to "X", instead of error'ing out with an exception.
Instances
showsX :: ShowX a => a -> ShowS Source #
Like shows
, but values that normally throw an XException
are
converted to "X", instead of error'ing out with an exception.
printX :: ShowX a => a -> IO () Source #
Like print
, but values that normally throw an XException
are
converted to "X", instead of error'ing out with an exception
showsPrecXWith :: (Int -> a -> ShowS) -> Int -> a -> ShowS Source #
Use when you want to create a ShowX
instance where:
- There is no
Generic
instance for your data type - The
Generic
derived ShowX method would traverse into the (hidden) implementation details of your data type, and you just want to show the entire value as "X".
Can be used like:
data T = ... instance Show T where ... instance ShowX T where showsPrecX = showsPrecXWith showsPrec
Strict evaluation
forceX :: NFDataX a => a -> a Source #
a variant of deepseqX
that is useful in some circumstances:
forceX x = x `deepseqX` x
deepseqX :: NFDataX a => a -> b -> b infixr 0 Source #
deepseqX
: fully evaluates the first argument, before returning the
second. Does not propagate XException
s.
defaultSeqX :: NFDataX a => a -> b -> b infixr 0 Source #
hwSeqX :: a -> b -> b infixr 0 Source #
Like seqX
in simulation, but will force its first argument to be rendered
in HDL. This is useful for components that need to be rendered in hardware,
but otherwise have no meaning in simulation. An example of such a component
would be an ILA: a component monitoring an internal signal of a design. The
output of such a component (typically a unit) can be passed as the first
argument to hwSeqX
to ensure the ILA ends up in the generated HDL.
NB: the result of hwSeqX
must (indirectly) be used at the very top of
a design. If it's not, Clash will remove it like it does for any other unused
circuit parts.
NB: Make sure the blackbox for the component with zero-width results
uses RenderVoid
Structured undefined / deep evaluation with undefined values
class NFDataX a where Source #
Class that houses functions dealing with undefined values in Clash. See
deepErrorX
and rnfX
.
Nothing
deepErrorX :: HasCallStack => String -> a Source #
Create a value where all the elements have an errorX
,
but the spine is defined.
default deepErrorX :: (HasCallStack, Generic a, GDeepErrorX (Rep a)) => String -> a Source #
hasUndefined :: a -> Bool Source #
Determines whether any of parts of a given construct contain undefined parts. Note that a negative answer does not mean its bit representation is fully defined. For example:
>>>
m = Nothing :: Maybe Bool
>>>
hasUndefined m
False>>>
pack m
0.>>>
hasUndefined (pack m)
True
default hasUndefined :: (Generic a, GHasUndefined (Rep a)) => a -> Bool Source #
ensureSpine :: a -> a Source #
Create a value where at the very least the spine is defined. For example:
>>>
spined = ensureSpine (errorX "?" :: (Int, Int))
>>>
case spined of (_, _) -> 'a'
'a'>>>
fmap (const 'b') (ensureSpine undefined :: Vec 3 Int)
<'b','b','b'>>>>
fmap (const 'c') (ensureSpine undefined :: RTree 2 Int)
<<'c','c'>,<'c','c'>>
For users familiar with lazyV
: this is the generalized
version of it.
default ensureSpine :: (Generic a, GEnsureSpine (Rep a)) => a -> a Source #
Evaluate a value to NF. As opposed to NFData
s
rnf
, it does not bubble up XException
s.