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 :: NFData a => a -> Maybe a
- maybeHasX :: NFData a => a -> Maybe 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
- class NFDataX a where
- deepErrorX :: HasCallStack => String -> 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
.
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 :: NFData a => 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 _|_ = _|_
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 Source #
deepseqX
: fully evaluates the first argument, before returning the
second. Does not propagate XException
s.
defaultSeqX :: NFDataX a => a -> b -> b 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
.
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 #
Evaluate a value to NF. As opposed to NFData
s rnf
, it does not bubble
up XException
s.
Instances
Orphan instances
Generic (a, b, c, d, e, f, g, h) Source # | |
Generic (a, b, c, d, e, f, g, h, i) Source # | |
Generic (a, b, c, d, e, f, g, h, i, j) Source # | |
Generic (a, b, c, d, e, f, g, h, i, j, k) Source # | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |