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 |
XException
: An exception for uninitialized values
>>>
show (errorX "undefined" :: Integer, 4 :: Int)
"(*** Exception: X: undefined CallStack (from HasCallStack): ...>>>
showX (errorX "undefined" :: Integer, 4 :: Int)
"(undefined,4)"
Synopsis
- newtype XException = XException String
- showsX :: ShowX a => a -> ShowS
- showsPrecXWith :: (Int -> a -> ShowS) -> Int -> a -> ShowS
- showXWith :: (a -> ShowS) -> a -> ShowS
- class GShowX f where
- class GDeepErrorX f where
- gDeepErrorX :: HasCallStack => String -> f a
- class GHasUndefined f where
- gHasUndefined :: f a -> Bool
- class GEnsureSpine f where
- gEnsureSpine :: f a -> f a
- class GNFDataX arity f where
- data Zero
- data One
- data ShowType
- data RnfArgs arity a where
- class NFDataX1 f where
- liftRnfX :: (a -> ()) -> f a -> ()
- showListX__ :: (a -> ShowS) -> [a] -> ShowS
- genericShowsPrecX :: (Generic a, GShowX (Rep a)) => Int -> a -> ShowS
Documentation
newtype XException Source #
An exception representing an "uninitialized" value.
Instances
Show XException Source # | |
Defined in Clash.XException.Internal showsPrec :: Int -> XException -> ShowS # show :: XException -> String # showList :: [XException] -> ShowS # | |
Exception XException Source # | |
Defined in Clash.XException.Internal toException :: XException -> SomeException # fromException :: SomeException -> Maybe XException # displayException :: XException -> String # |
Printing XException
s as undefined
showsX :: ShowX a => a -> ShowS Source #
Like shows
, but values that normally throw an XException
are
converted to undefined
, 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 asundefined
.
Can be used like:
data T = ... instance Show T where ... instance ShowX T where showsPrecX = showsPrecXWith showsPrec
Internals
Instances
GShowX (U1 :: Type -> Type) Source # | |
GShowX (UChar :: Type -> Type) Source # | |
GShowX (UDouble :: Type -> Type) Source # | |
GShowX (UFloat :: Type -> Type) Source # | |
GShowX (UInt :: Type -> Type) Source # | |
GShowX (UWord :: Type -> Type) Source # | |
ShowX c => GShowX (K1 i c :: Type -> Type) Source # | |
(GShowX a, GShowX b) => GShowX (a :+: b) Source # | |
(GShowX a, GShowX b) => GShowX (a :*: b) Source # | |
GShowX a => GShowX (M1 D d a) Source # | |
(GShowX a, Constructor c) => GShowX (M1 C c a) Source # | |
(Selector s, GShowX a) => GShowX (M1 S s a) Source # | |
class GDeepErrorX f where Source #
gDeepErrorX :: HasCallStack => String -> f a Source #
Instances
GDeepErrorX (V1 :: Type -> Type) Source # | |
Defined in Clash.XException.Internal gDeepErrorX :: HasCallStack => String -> V1 a Source # | |
GDeepErrorX (U1 :: Type -> Type) Source # | |
Defined in Clash.XException.Internal gDeepErrorX :: HasCallStack => String -> U1 a Source # | |
NFDataX c => GDeepErrorX (K1 i c :: Type -> Type) Source # | |
Defined in Clash.XException.Internal gDeepErrorX :: HasCallStack => String -> K1 i c a Source # | |
GDeepErrorX (f :+: g) Source # | |
Defined in Clash.XException.Internal gDeepErrorX :: HasCallStack => String -> (f :+: g) a Source # | |
(GDeepErrorX f, GDeepErrorX g) => GDeepErrorX (f :*: g) Source # | |
Defined in Clash.XException.Internal gDeepErrorX :: HasCallStack => String -> (f :*: g) a Source # | |
GDeepErrorX a => GDeepErrorX (M1 m d a) Source # | |
Defined in Clash.XException.Internal gDeepErrorX :: HasCallStack => String -> M1 m d a a0 Source # |
class GHasUndefined f where Source #
gHasUndefined :: f a -> Bool Source #
Instances
GHasUndefined (V1 :: Type -> Type) Source # | |
Defined in Clash.XException.Internal gHasUndefined :: V1 a -> Bool Source # | |
GHasUndefined (U1 :: Type -> Type) Source # | |
Defined in Clash.XException.Internal gHasUndefined :: U1 a -> Bool Source # | |
NFDataX a => GHasUndefined (K1 i a :: Type -> Type) Source # | |
Defined in Clash.XException.Internal gHasUndefined :: K1 i a a0 -> Bool Source # | |
(GHasUndefined a, GHasUndefined b) => GHasUndefined (a :+: b) Source # | |
Defined in Clash.XException.Internal gHasUndefined :: (a :+: b) a0 -> Bool Source # | |
(GHasUndefined a, GHasUndefined b) => GHasUndefined (a :*: b) Source # | |
Defined in Clash.XException.Internal gHasUndefined :: (a :*: b) a0 -> Bool Source # | |
GHasUndefined a => GHasUndefined (M1 i c a) Source # | |
Defined in Clash.XException.Internal gHasUndefined :: M1 i c a a0 -> Bool Source # |
class GEnsureSpine f where Source #
gEnsureSpine :: f a -> f a Source #
Instances
GEnsureSpine (V1 :: Type -> Type) Source # | |
Defined in Clash.XException.Internal gEnsureSpine :: V1 a -> V1 a Source # | |
GEnsureSpine (U1 :: Type -> Type) Source # | |
Defined in Clash.XException.Internal gEnsureSpine :: U1 a -> U1 a Source # | |
NFDataX a => GEnsureSpine (K1 i a :: Type -> Type) Source # | |
Defined in Clash.XException.Internal gEnsureSpine :: K1 i a a0 -> K1 i a a0 Source # | |
(GEnsureSpine a, GEnsureSpine b) => GEnsureSpine (a :+: b) Source # | |
Defined in Clash.XException.Internal gEnsureSpine :: (a :+: b) a0 -> (a :+: b) a0 Source # | |
(GEnsureSpine a, GEnsureSpine b) => GEnsureSpine (a :*: b) Source # | |
Defined in Clash.XException.Internal gEnsureSpine :: (a :*: b) a0 -> (a :*: b) a0 Source # | |
GEnsureSpine a => GEnsureSpine (M1 i c a) Source # | |
Defined in Clash.XException.Internal 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
Instances
GNFDataX One Par1 Source # | |
GNFDataX arity (U1 :: Type -> Type) Source # | |
GNFDataX arity (V1 :: Type -> Type) Source # | |
NFDataX1 f => GNFDataX One (Rec1 f) Source # | |
(GNFDataX arity a, GNFDataX arity b) => GNFDataX arity (a :+: b) Source # | |
(GNFDataX arity a, GNFDataX arity b) => GNFDataX arity (a :*: b) Source # | |
NFDataX a => GNFDataX arity (K1 i a :: Type -> Type) Source # | |
GNFDataX arity a => GNFDataX arity (M1 i c a) Source # | |
(NFDataX1 f, GNFDataX One g) => GNFDataX One (f :.: g) Source # | |
class NFDataX1 f where Source #
A class of functors that can be fully evaluated, according to semantics of NFDataX.
Nothing
showListX__ :: (a -> ShowS) -> [a] -> ShowS Source #