clash-prelude-1.0.0: CAES Language for Synchronous Hardware - Prelude library
Copyright(C) 2016 University of Twente
2017 QBayLogic Google Inc.
2017-2019 Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell2010

Clash.XException

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

newtype XException Source #

An exception representing an "uninitialized" value.

Constructors

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

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

hasX 42                  = Right 42
hasX (XException msg)    = Left msg
hasX (3, XException msg) = Left msg
hasX (3, _|_)            = _|_
hasX _|_                 = _|_

If a data structure contains multiple XExceptions, 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"

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)

Minimal complete definition

Nothing

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.

default showsPrecX :: (Generic a, GShowX (Rep a)) => Int -> a -> ShowS Source #

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.

Instances

Instances details
ShowX Bool Source # 
Instance details

Defined in Clash.XException

ShowX Char Source # 
Instance details

Defined in Clash.XException

ShowX Double Source # 
Instance details

Defined in Clash.XException

ShowX Float Source # 
Instance details

Defined in Clash.XException

ShowX Int Source # 
Instance details

Defined in Clash.XException

ShowX Int8 Source # 
Instance details

Defined in Clash.XException

ShowX Int16 Source # 
Instance details

Defined in Clash.XException

ShowX Int32 Source # 
Instance details

Defined in Clash.XException

ShowX Int64 Source # 
Instance details

Defined in Clash.XException

ShowX Integer Source # 
Instance details

Defined in Clash.XException

ShowX Natural Source # 
Instance details

Defined in Clash.XException

ShowX Word Source # 
Instance details

Defined in Clash.XException

ShowX Word8 Source # 
Instance details

Defined in Clash.XException

ShowX Word16 Source # 
Instance details

Defined in Clash.XException

ShowX Word32 Source # 
Instance details

Defined in Clash.XException

ShowX Word64 Source # 
Instance details

Defined in Clash.XException

ShowX () Source # 
Instance details

Defined in Clash.XException

Methods

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

showX :: () -> String Source #

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

ShowX String Source # 
Instance details

Defined in Clash.XException

ShowX Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

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

Defined in Clash.XException

Methods

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

showX :: [a] -> String Source #

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

ShowX a => ShowX (Maybe a) Source # 
Instance details

Defined in Clash.XException

ShowX a => ShowX (Ratio a) Source # 
Instance details

Defined in Clash.XException

ShowX a => ShowX (Complex a) Source # 
Instance details

Defined in Clash.XException

ShowX a => ShowX (Down a) Source # 
Instance details

Defined in Clash.XException

ShowX a => ShowX (Seq a) Source # 
Instance details

Defined in Clash.XException

Methods

showsPrecX :: Int -> Seq a -> ShowS Source #

showX :: Seq a -> String Source #

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

KnownNat n => ShowX (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

ShowX (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

KnownNat n => ShowX (BNat n) Source # 
Instance details

Defined in Clash.Promoted.Nat

KnownNat n => ShowX (UNat n) Source # 
Instance details

Defined in Clash.Promoted.Nat

ShowX (SNat n) Source # 
Instance details

Defined in Clash.Promoted.Nat

ShowX (Unsigned n) Source # 
Instance details

Defined in Clash.Sized.Internal.Unsigned

ShowX (Signed n) Source # 
Instance details

Defined in Clash.Sized.Internal.Signed

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

Defined in Clash.XException

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

Defined in Clash.XException

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

Defined in Clash.Sized.Vector

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

Defined in Clash.Sized.RTree

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

Defined in Clash.XException

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

Defined in Clash.Sized.Fixed

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

Defined in Clash.XException

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

Defined in Clash.XException

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

Defined in Clash.XException

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

Defined in Clash.XException

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

Defined in Clash.XException

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

Defined in Clash.XException

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

Defined in Clash.XException

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

Defined in Clash.XException

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

Defined in Clash.XException

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

Defined in Clash.XException

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

Defined in Clash.XException

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

Defined in Clash.XException

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 = _|_

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 XExceptions.

rwhnfX :: a -> () Source #

Reduce to weak head normal form

Equivalent to \x -> seqX x ().

Useful for defining rnfX for types for which NF=WHNF holds.

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.

Minimal complete definition

Nothing

Methods

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 #

rnfX :: a -> () Source #

Evaluate a value to NF. As opposed to NFDatas rnf, it does not bubble up XExceptions.

default rnfX :: (Generic a, GNFDataX Zero (Rep a)) => a -> () Source #

Instances

Instances details
NFDataX Bool Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Bool Source #

rnfX :: Bool -> () Source #

NFDataX Char Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Char Source #

rnfX :: Char -> () Source #

NFDataX Double Source # 
Instance details

Defined in Clash.XException

NFDataX Float Source # 
Instance details

Defined in Clash.XException

NFDataX Int Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Int Source #

rnfX :: Int -> () Source #

NFDataX Int8 Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Int8 Source #

rnfX :: Int8 -> () Source #

NFDataX Int16 Source # 
Instance details

Defined in Clash.XException

NFDataX Int32 Source # 
Instance details

Defined in Clash.XException

NFDataX Int64 Source # 
Instance details

Defined in Clash.XException

NFDataX Integer Source # 
Instance details

Defined in Clash.XException

NFDataX Natural Source # 
Instance details

Defined in Clash.XException

NFDataX Word Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Word Source #

rnfX :: Word -> () Source #

NFDataX Word8 Source # 
Instance details

Defined in Clash.XException

NFDataX Word16 Source # 
Instance details

Defined in Clash.XException

NFDataX Word32 Source # 
Instance details

Defined in Clash.XException

NFDataX Word64 Source # 
Instance details

Defined in Clash.XException

NFDataX () Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> () Source #

rnfX :: () -> () Source #

NFDataX All Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> All Source #

rnfX :: All -> () Source #

NFDataX Any Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Any Source #

rnfX :: Any -> () Source #

NFDataX Half Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Half Source #

rnfX :: Half -> () Source #

NFDataX Bit Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

Methods

deepErrorX :: String -> Bit Source #

rnfX :: Bit -> () Source #

NFDataX a => NFDataX [a] Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> [a] Source #

rnfX :: [a] -> () Source #

NFDataX a => NFDataX (Maybe a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Maybe a Source #

rnfX :: Maybe a -> () Source #

NFDataX a => NFDataX (Ratio a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Ratio a Source #

rnfX :: Ratio a -> () Source #

NFDataX a => NFDataX (Complex a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Complex a Source #

rnfX :: Complex a -> () Source #

NFDataX a => NFDataX (Min a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Min a Source #

rnfX :: Min a -> () Source #

NFDataX a => NFDataX (Max a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Max a Source #

rnfX :: Max a -> () Source #

NFDataX a => NFDataX (First a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> First a Source #

rnfX :: First a -> () Source #

NFDataX a => NFDataX (Last a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Last a Source #

rnfX :: Last a -> () Source #

NFDataX a => NFDataX (Option a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Option a Source #

rnfX :: Option a -> () Source #

NFDataX a => NFDataX (Dual a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Dual a Source #

rnfX :: Dual a -> () Source #

NFDataX a => NFDataX (Endo a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Endo a Source #

rnfX :: Endo a -> () Source #

NFDataX a => NFDataX (Sum a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Sum a Source #

rnfX :: Sum a -> () Source #

NFDataX a => NFDataX (Product a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Product a Source #

rnfX :: Product a -> () Source #

NFDataX a => NFDataX (Down a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Down a Source #

rnfX :: Down a -> () Source #

NFDataX a => NFDataX (Seq a) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Seq a Source #

rnfX :: Seq a -> () Source #

NFDataX (BitVector n) Source # 
Instance details

Defined in Clash.Sized.Internal.BitVector

NFDataX (Index n) Source # 
Instance details

Defined in Clash.Sized.Internal.Index

Methods

deepErrorX :: String -> Index n Source #

rnfX :: Index n -> () Source #

NFDataX (Unsigned n) Source # 
Instance details

Defined in Clash.Sized.Internal.Unsigned

NFDataX (Signed n) Source # 
Instance details

Defined in Clash.Sized.Internal.Signed

Methods

deepErrorX :: String -> Signed n Source #

rnfX :: Signed n -> () Source #

NFDataX b => NFDataX (a -> b) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> a -> b Source #

rnfX :: (a -> b) -> () Source #

(NFDataX a, NFDataX b) => NFDataX (Either a b) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Either a b Source #

rnfX :: Either a b -> () Source #

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

Defined in Clash.XException

Methods

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

rnfX :: (a, b) -> () Source #

(NFDataX a, NFDataX b) => NFDataX (Arg a b) Source # 
Instance details

Defined in Clash.XException

Methods

deepErrorX :: String -> Arg a b Source #

rnfX :: Arg a b -> () Source #

(NFDataX a, KnownNat n) => NFDataX (Vec n a) Source # 
Instance details

Defined in Clash.Sized.Vector

Methods

deepErrorX :: String -> Vec n a Source #

rnfX :: Vec n a -> () Source #

(KnownNat d, NFDataX a) => NFDataX (RTree d a) Source # 
Instance details

Defined in Clash.Sized.RTree

Methods

deepErrorX :: String -> RTree d a Source #

rnfX :: RTree d a -> () Source #

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

Defined in Clash.XException

Methods

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

rnfX :: (a, b, c) -> () Source #

NFDataX (rep (int + frac)) => NFDataX (Fixed rep int frac) Source # 
Instance details

Defined in Clash.Sized.Fixed

Methods

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

rnfX :: Fixed rep int frac -> () Source #

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

Defined in Clash.XException

Methods

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

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

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

Defined in Clash.XException

Methods

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

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

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

Defined in Clash.XException

Methods

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

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

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

Defined in Clash.XException

Methods

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

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

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

Defined in Clash.XException

Methods

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

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

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

Defined in Clash.XException

Methods

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

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

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

Defined in Clash.XException

Methods

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

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

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

Defined in Clash.XException

Methods

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

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

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

Defined in Clash.XException

Methods

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

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

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

Defined in Clash.XException

Methods

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

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

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

Defined in Clash.XException

Methods

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

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

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

Defined in Clash.XException

Methods

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

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

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) #