| Copyright | (C) 2016 University of Twente 2017 Myrtle Software Ltd QBayLogic Google Inc. |
|---|---|
| License | BSD2 (see the file LICENSE) |
| Maintainer | Christiaan Baaij <christiaan.baaij@gmail.com> |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Clash.XException
Contents
Description
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)"
X: An exception for uninitialized values
data XException Source #
An exception representing an "uninitialised" value.
Instances
| Show XException Source # | |
Methods showsPrec :: Int -> XException -> ShowS # show :: XException -> String # showList :: [XException] -> ShowS # | |
| Exception XException Source # | |
Methods 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 :: NFData a => a -> Either String a Source #
Fully evaluate a value, returning if is throws Left msgXException.
isX 42 = Right 42 isX (XException msg) = Left msg isX _|_ = _|_
maybeX :: NFData a => a -> Maybe a Source #
Fully evaluate a value, returning Nothing if is throws XException.
maybeX 42 = Just 42 maybeX (XException msg) = Nothing 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)Methods
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.
showsPrecX :: (Generic a, GShowX (Rep a)) => 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.
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
Genericinstance for your data type - The
Genericderived 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
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 # | |