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 |
X
: 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
- 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 -> ()
X
: An exception for uninitialized values
newtype XException Source #
An exception representing an "uninitialized" value.
Instances
Show XException Source # | |
Defined in Clash.XException showsPrec :: Int -> XException -> ShowS # show :: XException -> String # showList :: [XException] -> ShowS # | |
Exception XException Source # | |
Defined in Clash.XException 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, _|_) = (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
.
maybeX 42 = Just 42 maybeX (XException msg) = Nothing maybeX (3, XException msg) = Nothing maybeX (3, _|_) = _|_ maybeX _|_ = _|_
fromJustX :: HasCallStack => Maybe a -> a Source #
Same as "Data.Maybe.fromJust", but returns a bottom/undefined value that other Clash constructs are aware of.
undefined :: HasCallStack => a Source #
Printing X
exceptions as "X"
Like the Show
class, but values that normally throw an X
exception 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 X
exception are
converted to "X", instead of error'ing out with an exception.
Like show
, but values that normally throw an X
exception are
converted to "X", instead of error'ing out with an exception.
showListX :: [a] -> ShowS Source #
Like showList
, but values that normally throw an X
exception 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 X
exception 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 X
exception 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 #
Either seqX
or deepSeqX
depending on the value of the cabal flag
'-fsuper-strict'. If enabled, defaultSeqX
will be deepseqX
, otherwise
seqX
. Flag defaults to false and thus seqX
.
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
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.
Instances
NFDataX Bool Source # | |
Defined in Clash.XException | |
NFDataX Char Source # | |
Defined in Clash.XException | |
NFDataX Double Source # | |
Defined in Clash.XException | |
NFDataX Float Source # | |
Defined in Clash.XException | |
NFDataX Int Source # | |
Defined in Clash.XException | |
NFDataX Int8 Source # | |
Defined in Clash.XException | |
NFDataX Int16 Source # | |
Defined in Clash.XException | |
NFDataX Int32 Source # | |
Defined in Clash.XException | |
NFDataX Int64 Source # | |
Defined in Clash.XException | |
NFDataX Integer Source # | |
Defined in Clash.XException | |
NFDataX Natural Source # | |
Defined in Clash.XException | |
NFDataX Word Source # | |
Defined in Clash.XException | |
NFDataX Word8 Source # | |
Defined in Clash.XException | |
NFDataX Word16 Source # | |
Defined in Clash.XException | |
NFDataX Word32 Source # | |
Defined in Clash.XException | |
NFDataX Word64 Source # | |
Defined in Clash.XException | |
NFDataX () Source # | |
Defined in Clash.XException deepErrorX :: String -> () Source # hasUndefined :: () -> Bool Source # ensureSpine :: () -> () Source # | |
NFDataX All Source # | |
Defined in Clash.XException | |
NFDataX Any Source # | |
Defined in Clash.XException | |
NFDataX CUShort Source # | |
Defined in Clash.XException | |
NFDataX Half Source # | |
Defined in Clash.XException | |
NFDataX Bit Source # | |
Defined in Clash.Sized.Internal.BitVector | |
NFDataX a => NFDataX [a] Source # | |
Defined in Clash.XException deepErrorX :: String -> [a] Source # hasUndefined :: [a] -> Bool Source # ensureSpine :: [a] -> [a] Source # | |
NFDataX a => NFDataX (Maybe a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Ratio a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Complex a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Min a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Max a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (First a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Last a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Option a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (First a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Last a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Dual a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Endo a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Sum a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Product a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Down a) Source # | |
Defined in Clash.XException | |
NFDataX a => NFDataX (Seq a) Source # | |
Defined in Clash.XException | |
NFDataX (BitVector n) Source # | |
Defined in Clash.Sized.Internal.BitVector | |
NFDataX (Index n) Source # | |
Defined in Clash.Sized.Internal.Index | |
NFDataX (Unsigned n) Source # | |
Defined in Clash.Sized.Internal.Unsigned | |
NFDataX (Signed n) Source # | |
Defined in Clash.Sized.Internal.Signed | |
NFDataX b => NFDataX (a -> b) Source # | |
Defined in Clash.XException deepErrorX :: String -> a -> b Source # hasUndefined :: (a -> b) -> Bool Source # ensureSpine :: (a -> b) -> a -> b Source # | |
(NFDataX a, NFDataX b) => NFDataX (Either a b) Source # | |
Defined in Clash.XException | |
(NFDataX a0, NFDataX a1) => NFDataX (a0, a1) Source # | |
Defined in Clash.XException deepErrorX :: String -> (a0, a1) Source # hasUndefined :: (a0, a1) -> Bool Source # ensureSpine :: (a0, a1) -> (a0, a1) Source # | |
(NFDataX a, NFDataX b) => NFDataX (Arg a b) Source # | |
Defined in Clash.XException | |
(NFDataX a, KnownNat n) => NFDataX (Vec n a) Source # | |
Defined in Clash.Sized.Vector | |
NFDataX a => NFDataX (Signal domain a) Source # | |
Defined in Clash.Signal.Internal | |
(KnownNat d, NFDataX a) => NFDataX (RTree d a) Source # | |
Defined in Clash.Sized.RTree | |
(NFDataX a0, NFDataX a1, NFDataX a2) => NFDataX (a0, a1, a2) Source # | |
Defined in Clash.XException deepErrorX :: String -> (a0, a1, a2) Source # hasUndefined :: (a0, a1, a2) -> Bool Source # ensureSpine :: (a0, a1, a2) -> (a0, a1, a2) Source # | |
NFDataX (rep (int + frac)) => NFDataX (Fixed rep int frac) Source # | |
Defined in Clash.Sized.Fixed | |
(NFDataX a0, NFDataX a1, NFDataX a2, NFDataX a3) => NFDataX (a0, a1, a2, a3) Source # | |
Defined in Clash.XException deepErrorX :: String -> (a0, a1, a2, a3) Source # hasUndefined :: (a0, a1, a2, a3) -> Bool Source # ensureSpine :: (a0, a1, a2, a3) -> (a0, a1, a2, a3) Source # | |
(NFDataX a0, NFDataX a1, NFDataX a2, NFDataX a3, NFDataX a4) => NFDataX (a0, a1, a2, a3, a4) Source # | |
Defined in Clash.XException deepErrorX :: String -> (a0, a1, a2, a3, a4) Source # hasUndefined :: (a0, a1, a2, a3, a4) -> Bool Source # ensureSpine :: (a0, a1, a2, a3, a4) -> (a0, a1, a2, a3, a4) Source # | |
(NFDataX a0, NFDataX a1, NFDataX a2, NFDataX a3, NFDataX a4, NFDataX a5) => NFDataX (a0, a1, a2, a3, a4, a5) Source # | |
Defined in Clash.XException deepErrorX :: String -> (a0, a1, a2, a3, a4, a5) Source # hasUndefined :: (a0, a1, a2, a3, a4, a5) -> Bool Source # ensureSpine :: (a0, a1, a2, a3, a4, a5) -> (a0, a1, a2, a3, a4, a5) Source # | |
(NFDataX a0, NFDataX a1, NFDataX a2, NFDataX a3, NFDataX a4, NFDataX a5, NFDataX a6) => NFDataX (a0, a1, a2, a3, a4, a5, a6) Source # | |
Defined in Clash.XException deepErrorX :: String -> (a0, a1, a2, a3, a4, a5, a6) Source # hasUndefined :: (a0, a1, a2, a3, a4, a5, a6) -> Bool Source # ensureSpine :: (a0, a1, a2, a3, a4, a5, a6) -> (a0, a1, a2, a3, a4, a5, a6) Source # | |
(NFDataX a0, NFDataX a1, NFDataX a2, NFDataX a3, NFDataX a4, NFDataX a5, NFDataX a6, NFDataX a7) => NFDataX (a0, a1, a2, a3, a4, a5, a6, a7) Source # | |
Defined in Clash.XException deepErrorX :: String -> (a0, a1, a2, a3, a4, a5, a6, a7) Source # hasUndefined :: (a0, a1, a2, a3, a4, a5, a6, a7) -> Bool Source # ensureSpine :: (a0, a1, a2, a3, a4, a5, a6, a7) -> (a0, a1, a2, a3, a4, a5, a6, a7) Source # | |
(NFDataX a0, NFDataX a1, NFDataX a2, NFDataX a3, NFDataX a4, NFDataX a5, NFDataX a6, NFDataX a7, NFDataX a8) => NFDataX (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source # | |
Defined in Clash.XException deepErrorX :: String -> (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source # hasUndefined :: (a0, a1, a2, a3, a4, a5, a6, a7, a8) -> Bool Source # ensureSpine :: (a0, a1, a2, a3, a4, a5, a6, a7, a8) -> (a0, a1, a2, a3, a4, a5, a6, a7, a8) Source # | |
(NFDataX a0, NFDataX a1, NFDataX a2, NFDataX a3, NFDataX a4, NFDataX a5, NFDataX a6, NFDataX a7, NFDataX a8, NFDataX a9) => NFDataX (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9) Source # | |
Defined in Clash.XException deepErrorX :: String -> (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9) Source # hasUndefined :: (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9) -> Bool Source # ensureSpine :: (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9) -> (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9) Source # rnfX :: (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9) -> () Source # | |
(NFDataX a0, NFDataX a1, NFDataX a2, NFDataX a3, NFDataX a4, NFDataX a5, NFDataX a6, NFDataX a7, NFDataX a8, NFDataX a9, NFDataX a10) => NFDataX (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # | |
Defined in Clash.XException deepErrorX :: String -> (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # hasUndefined :: (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> Bool Source # ensureSpine :: (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) Source # rnfX :: (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10) -> () Source # | |
(NFDataX a0, NFDataX a1, NFDataX a2, NFDataX a3, NFDataX a4, NFDataX a5, NFDataX a6, NFDataX a7, NFDataX a8, NFDataX a9, NFDataX a10, NFDataX a11) => NFDataX (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # | |
Defined in Clash.XException deepErrorX :: String -> (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # hasUndefined :: (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> Bool Source # ensureSpine :: (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) Source # rnfX :: (a0, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11) -> () Source # |