clash-prelude-1.4.7: Clash: a functional hardware description language - 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.Internal

Description

XException: 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

Documentation

newtype XException Source #

An exception representing an "uninitialized" value.

Constructors

XException String 

Printing XExceptions as "X"

showsX :: ShowX a => a -> ShowS Source #

Like shows, but values that normally throw an XException 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

showXWith :: (a -> ShowS) -> a -> ShowS Source #

Internals

class GShowX f where Source #

Minimal complete definition

gshowsPrecX

Methods

gshowsPrecX :: ShowType -> Int -> f a -> ShowS Source #

isNullary :: f a -> Bool Source #

Instances

Instances details
GShowX (U1 :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gshowsPrecX :: ShowType -> Int -> U1 a -> ShowS Source #

isNullary :: U1 a -> Bool Source #

GShowX (UChar :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

GShowX (UDouble :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

GShowX (UFloat :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

GShowX (UInt :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

GShowX (UWord :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

ShowX c => GShowX (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gshowsPrecX :: ShowType -> Int -> K1 i c a -> ShowS Source #

isNullary :: K1 i c a -> Bool Source #

(GShowX a, GShowX b) => GShowX (a :+: b) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gshowsPrecX :: ShowType -> Int -> (a :+: b) a0 -> ShowS Source #

isNullary :: (a :+: b) a0 -> Bool Source #

(GShowX a, GShowX b) => GShowX (a :*: b) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gshowsPrecX :: ShowType -> Int -> (a :*: b) a0 -> ShowS Source #

isNullary :: (a :*: b) a0 -> Bool Source #

GShowX a => GShowX (M1 D d a) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gshowsPrecX :: ShowType -> Int -> M1 D d a a0 -> ShowS Source #

isNullary :: M1 D d a a0 -> Bool Source #

(GShowX a, Constructor c) => GShowX (M1 C c a) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gshowsPrecX :: ShowType -> Int -> M1 C c a a0 -> ShowS Source #

isNullary :: M1 C c a a0 -> Bool Source #

(Selector s, GShowX a) => GShowX (M1 S s a) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gshowsPrecX :: ShowType -> Int -> M1 S s a a0 -> ShowS Source #

isNullary :: M1 S s a a0 -> Bool Source #

class GDeepErrorX f where Source #

Methods

gDeepErrorX :: HasCallStack => String -> f a Source #

Instances

Instances details
GDeepErrorX (V1 :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

GDeepErrorX (U1 :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

NFDataX c => GDeepErrorX (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gDeepErrorX :: HasCallStack => String -> K1 i c a Source #

GDeepErrorX (f :+: g) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gDeepErrorX :: HasCallStack => String -> (f :+: g) a Source #

(GDeepErrorX f, GDeepErrorX g) => GDeepErrorX (f :*: g) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gDeepErrorX :: HasCallStack => String -> (f :*: g) a Source #

GDeepErrorX a => GDeepErrorX (M1 m d a) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gDeepErrorX :: HasCallStack => String -> M1 m d a a0 Source #

class GHasUndefined f where Source #

Methods

gHasUndefined :: f a -> Bool Source #

Instances

Instances details
GHasUndefined (V1 :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gHasUndefined :: V1 a -> Bool Source #

GHasUndefined (U1 :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gHasUndefined :: U1 a -> Bool Source #

NFDataX a => GHasUndefined (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gHasUndefined :: K1 i a a0 -> Bool Source #

(GHasUndefined a, GHasUndefined b) => GHasUndefined (a :+: b) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gHasUndefined :: (a :+: b) a0 -> Bool Source #

(GHasUndefined a, GHasUndefined b) => GHasUndefined (a :*: b) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gHasUndefined :: (a :*: b) a0 -> Bool Source #

GHasUndefined a => GHasUndefined (M1 i c a) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gHasUndefined :: M1 i c a a0 -> Bool Source #

class GEnsureSpine f where Source #

Methods

gEnsureSpine :: f a -> f a Source #

Instances

Instances details
GEnsureSpine (V1 :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gEnsureSpine :: V1 a -> V1 a Source #

GEnsureSpine (U1 :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gEnsureSpine :: U1 a -> U1 a Source #

NFDataX a => GEnsureSpine (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gEnsureSpine :: K1 i a a0 -> K1 i a a0 Source #

(GEnsureSpine a, GEnsureSpine b) => GEnsureSpine (a :+: b) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gEnsureSpine :: (a :+: b) a0 -> (a :+: b) a0 Source #

(GEnsureSpine a, GEnsureSpine b) => GEnsureSpine (a :*: b) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gEnsureSpine :: (a :*: b) a0 -> (a :*: b) a0 Source #

GEnsureSpine a => GEnsureSpine (M1 i c a) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

gEnsureSpine :: M1 i c a a0 -> M1 i c a a0 Source #

class GNFDataX arity f where Source #

Hidden internal type-class. Adds a generic implementation for the "NFData" part of NFDataX

Methods

grnfX :: RnfArgs arity a -> f a -> () Source #

Instances

Instances details
GNFDataX One Par1 Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs One a -> Par1 a -> () Source #

GNFDataX arity (U1 :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs arity a -> U1 a -> () Source #

GNFDataX arity (V1 :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs arity a -> V1 a -> () Source #

NFDataX1 f => GNFDataX One (Rec1 f) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs One a -> Rec1 f a -> () Source #

(GNFDataX arity a, GNFDataX arity b) => GNFDataX arity (a :+: b) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs arity a0 -> (a :+: b) a0 -> () Source #

(GNFDataX arity a, GNFDataX arity b) => GNFDataX arity (a :*: b) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs arity a0 -> (a :*: b) a0 -> () Source #

NFDataX a => GNFDataX arity (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs arity a0 -> K1 i a a0 -> () Source #

GNFDataX arity a => GNFDataX arity (M1 i c a) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs arity a0 -> M1 i c a a0 -> () Source #

(NFDataX1 f, GNFDataX One g) => GNFDataX One (f :.: g) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs One a -> (f :.: g) a -> () Source #

data One Source #

Instances

Instances details
GNFDataX One Par1 Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs One a -> Par1 a -> () Source #

NFDataX1 f => GNFDataX One (Rec1 f) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs One a -> Rec1 f a -> () Source #

(NFDataX1 f, GNFDataX One g) => GNFDataX One (f :.: g) Source # 
Instance details

Defined in Clash.XException.Internal

Methods

grnfX :: RnfArgs One a -> (f :.: g) a -> () Source #

data ShowType Source #

Constructors

Rec 
Tup 
Pref 
Inf String 

data RnfArgs arity a where Source #

Constructors

RnfArgs0 :: RnfArgs Zero a 
RnfArgs1 :: (a -> ()) -> RnfArgs One a 

class NFDataX1 f where Source #

A class of functors that can be fully evaluated, according to semantics of NFDataX.

Minimal complete definition

Nothing

Methods

liftRnfX :: (a -> ()) -> f a -> () Source #

liftRnfX should reduce its argument to normal form (that is, fully evaluate all sub-components), given an argument to reduce a arguments, and then return ().

See rnfX for the generic deriving.

default liftRnfX :: (Generic1 f, GNFDataX One (Rep1 f)) => (a -> ()) -> f a -> () Source #

showListX__ :: (a -> ShowS) -> [a] -> ShowS Source #