clash-prelude-0.99.1: CAES Language for Synchronous Hardware - Prelude library

Copyright(C) 2016 University of Twente
2017 Myrtle Software Ltd QBayLogic Google Inc.
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010

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)"
Synopsis

X: An exception for uninitialized values

data XException Source #

An exception representing an "uninitialised" value.

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 Left msg if is throws XException.

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"

class ShowX a where Source #

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.

showX :: a -> String Source #

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
ShowX Bool Source # 
Instance details
ShowX Char Source # 
Instance details
ShowX Double Source # 
Instance details
ShowX Float Source # 
Instance details
ShowX Int Source # 
Instance details
ShowX Int8 Source # 
Instance details
ShowX Int16 Source # 
Instance details
ShowX Int32 Source # 
Instance details
ShowX Int64 Source # 
Instance details
ShowX Integer Source # 
Instance details
ShowX Word Source # 
Instance details
ShowX Word8 Source # 
Instance details
ShowX Word16 Source # 
Instance details
ShowX Word32 Source # 
Instance details
ShowX Word64 Source # 
Instance details
ShowX () Source # 
Instance details

Methods

showsPrecX :: Int -> () -> ShowS Source #

showX :: () -> String Source #

showListX :: [()] -> ShowS Source #

ShowX String Source # 
Instance details
ShowX Bit Source # 
Instance details
ShowX a => ShowX [a] Source # 
Instance details

Methods

showsPrecX :: Int -> [a] -> ShowS Source #

showX :: [a] -> String Source #

showListX :: [[a]] -> ShowS Source #

ShowX a => ShowX (Maybe a) Source # 
Instance details
ShowX a => ShowX (Ratio a) Source # 
Instance details
ShowX a => ShowX (Complex a) Source # 
Instance details
KnownNat n => ShowX (BitVector n) Source # 
Instance details
ShowX (Index n) Source # 
Instance details
KnownNat n => ShowX (BNat n) Source # 
Instance details
KnownNat n => ShowX (UNat n) Source # 
Instance details
ShowX (SNat n) Source # 
Instance details
ShowX (Unsigned n) Source # 
Instance details
ShowX (Signed n) Source # 
Instance details
(ShowX a, ShowX b) => ShowX (Either a b) Source # 
Instance details

Methods

showsPrecX :: Int -> Either a b -> ShowS Source #

showX :: Either a b -> String Source #

showListX :: [Either a b] -> ShowS Source #

(ShowX a, ShowX b) => ShowX (a, b) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b) -> ShowS Source #

showX :: (a, b) -> String Source #

showListX :: [(a, b)] -> ShowS Source #

ShowX a => ShowX (Vec n a) Source # 
Instance details

Methods

showsPrecX :: Int -> Vec n a -> ShowS Source #

showX :: Vec n a -> String Source #

showListX :: [Vec n a] -> ShowS Source #

ShowX a => ShowX (RTree n a) Source # 
Instance details

Methods

showsPrecX :: Int -> RTree n a -> ShowS Source #

showX :: RTree n a -> String Source #

showListX :: [RTree n a] -> ShowS Source #

(ShowX a, ShowX b, ShowX c) => ShowX (a, b, c) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c) -> ShowS Source #

showX :: (a, b, c) -> String Source #

showListX :: [(a, b, c)] -> ShowS Source #

(size ~ (int + frac), KnownNat frac, Integral (rep size)) => ShowX (Fixed rep int frac) Source # 
Instance details

Methods

showsPrecX :: Int -> Fixed rep int frac -> ShowS Source #

showX :: Fixed rep int frac -> String Source #

showListX :: [Fixed rep int frac] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d) => ShowX (a, b, c, d) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d) -> ShowS Source #

showX :: (a, b, c, d) -> String Source #

showListX :: [(a, b, c, d)] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d, ShowX e) => ShowX (a, b, c, d, e) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d, e) -> ShowS Source #

showX :: (a, b, c, d, e) -> String Source #

showListX :: [(a, b, c, d, e)] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d, ShowX e, ShowX f) => ShowX (a, b, c, d, e, f) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d, e, f) -> ShowS Source #

showX :: (a, b, c, d, e, f) -> String Source #

showListX :: [(a, b, c, d, e, f)] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d, ShowX e, ShowX f, ShowX g) => ShowX (a, b, c, d, e, f, g) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d, e, f, g) -> ShowS Source #

showX :: (a, b, c, d, e, f, g) -> String Source #

showListX :: [(a, b, c, d, e, f, g)] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d, ShowX e, ShowX f, ShowX g, ShowX h) => ShowX (a, b, c, d, e, f, g, h) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d, e, f, g, h) -> ShowS Source #

showX :: (a, b, c, d, e, f, g, h) -> String Source #

showListX :: [(a, b, c, d, e, f, g, h)] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d, ShowX e, ShowX f, ShowX g, ShowX h, ShowX i) => ShowX (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d, e, f, g, h, i) -> ShowS Source #

showX :: (a, b, c, d, e, f, g, h, i) -> String Source #

showListX :: [(a, b, c, d, e, f, g, h, i)] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d, ShowX e, ShowX f, ShowX g, ShowX h, ShowX i, ShowX j) => ShowX (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d, e, f, g, h, i, j) -> ShowS Source #

showX :: (a, b, c, d, e, f, g, h, i, j) -> String Source #

showListX :: [(a, b, c, d, e, f, g, h, i, j)] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d, ShowX e, ShowX f, ShowX g, ShowX h, ShowX i, ShowX j, ShowX k) => ShowX (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d, e, f, g, h, i, j, k) -> ShowS Source #

showX :: (a, b, c, d, e, f, g, h, i, j, k) -> String Source #

showListX :: [(a, b, c, d, e, f, g, h, i, j, k)] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d, ShowX e, ShowX f, ShowX g, ShowX h, ShowX i, ShowX j, ShowX k, ShowX l) => ShowX (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l) -> ShowS Source #

showX :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String Source #

showListX :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d, ShowX e, ShowX f, ShowX g, ShowX h, ShowX i, ShowX j, ShowX k, ShowX l, ShowX m) => ShowX (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> ShowS Source #

showX :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> String Source #

showListX :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d, ShowX e, ShowX f, ShowX g, ShowX h, ShowX i, ShowX j, ShowX k, ShowX l, ShowX m, ShowX n) => ShowX (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ShowS Source #

showX :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> String Source #

showListX :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> ShowS Source #

(ShowX a, ShowX b, ShowX c, ShowX d, ShowX e, ShowX f, ShowX g, ShowX h, ShowX i, ShowX j, ShowX k, ShowX l, ShowX m, ShowX n, ShowX o) => ShowX (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Methods

showsPrecX :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ShowS Source #

showX :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> String Source #

showListX :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> ShowS Source #

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

seqX :: a -> b -> b infixr 0 Source #

Like seq, however, whereas seq will always do:

seq  _|_              b = _|_

seqX will do:

seqX (XException msg) b = b
seqX _|_              b = _|_

Orphan instances

Generic (a, b, c, d, e, f, g, h) Source # 
Instance details

Associated Types

type Rep (a, b, c, d, e, f, g, h) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g, h) -> Rep (a, b, c, d, e, f, g, h) x #

to :: Rep (a, b, c, d, e, f, g, h) x -> (a, b, c, d, e, f, g, h) #

Generic (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Associated Types

type Rep (a, b, c, d, e, f, g, h, i) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g, h, i) -> Rep (a, b, c, d, e, f, g, h, i) x #

to :: Rep (a, b, c, d, e, f, g, h, i) x -> (a, b, c, d, e, f, g, h, i) #

Generic (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g, h, i, j) -> Rep (a, b, c, d, e, f, g, h, i, j) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j) x -> (a, b, c, d, e, f, g, h, i, j) #

Generic (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k) -> Rep (a, b, c, d, e, f, g, h, i, j, k) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k) x -> (a, b, c, d, e, f, g, h, i, j, k) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l) x -> (a, b, c, d, e, f, g, h, i, j, k, l) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #