convertible-text-0.0.0: Typeclasses and instances for converting between typesSource codeContentsIndex
Data.Convertible.Base
Portabilityportable
Stabilityprovisional
MaintainerMichael Snoyman <michael@snoyman.com>
Description
Synopsis
class ConvertAttempt a b where
convertAttempt :: a -> Attempt b
class ConvertAttempt a b => ConvertSuccess a b where
convertSuccess :: a -> b
data ConversionException = forall e . Exception e => ConversionException e
convertUnsafe :: ConvertAttempt a b => a -> b
convertAttemptWrap :: (ConvertAttempt a b, MonadFailure ConversionException m) => a -> m b
Documentation
class ConvertAttempt a b whereSource
A typeclass that represents something that can attempt a conversion. An ConvertAttempt a b instance represents an a that might be convertible to a b.
Methods
convertAttempt :: a -> Attempt bSource
Convert a to b, returning Success on success and Failure on error.
show/hide Instances
ConvertAttempt Char Int
ConvertAttempt Char Int
ConvertAttempt Char Int8
ConvertAttempt Char Int8
ConvertAttempt Char Int16
ConvertAttempt Char Int16
ConvertAttempt Char Int32
ConvertAttempt Char Int32
ConvertAttempt Char Int64
ConvertAttempt Char Int64
ConvertAttempt Char Word
ConvertAttempt Char Word
ConvertAttempt Char Word8
ConvertAttempt Char Word8
ConvertAttempt Char Word16
ConvertAttempt Char Word16
ConvertAttempt Char Word32
ConvertAttempt Char Word32
ConvertAttempt Char Word64
ConvertAttempt Char Word64
ConvertAttempt Char CChar
ConvertAttempt Char CChar
ConvertAttempt Char CSChar
ConvertAttempt Char CSChar
ConvertAttempt Char CUChar
ConvertAttempt Char CUChar
ConvertAttempt Char CShort
ConvertAttempt Char CShort
ConvertAttempt Char CUShort
ConvertAttempt Char CUShort
ConvertAttempt Char CInt
ConvertAttempt Char CInt
ConvertAttempt Char CUInt
ConvertAttempt Char CUInt
ConvertAttempt Char CLong
ConvertAttempt Char CLong
ConvertAttempt Char CULong
ConvertAttempt Char CULong
ConvertAttempt Char CLLong
ConvertAttempt Char CLLong
ConvertAttempt Char CULLong
ConvertAttempt Char CULLong
ConvertAttempt Char CSize
ConvertAttempt Char CSize
ConvertAttempt Char CWchar
ConvertAttempt Char CWchar
ConvertAttempt Double Int
ConvertAttempt Double Int
ConvertAttempt Double Int8
ConvertAttempt Double Int8
ConvertAttempt Double Int16
ConvertAttempt Double Int16
ConvertAttempt Double Int32
ConvertAttempt Double Int32
ConvertAttempt Double Int64
ConvertAttempt Double Int64
ConvertAttempt Double Word
ConvertAttempt Double Word
ConvertAttempt Double Word8
ConvertAttempt Double Word8
ConvertAttempt Double Word16
ConvertAttempt Double Word16
ConvertAttempt Double Word32
ConvertAttempt Double Word32
ConvertAttempt Double Word64
ConvertAttempt Double Word64
ConvertAttempt Double CTime
ConvertAttempt Double CTime
ConvertAttempt Double TimeDiff
ConvertAttempt Double TimeDiff
ConvertAttempt Double POSIXTime
ConvertAttempt Double POSIXTime
ConvertAttempt Double UTCTime
ConvertAttempt Double UTCTime
ConvertAttempt Float Int
ConvertAttempt Float Int
ConvertAttempt Float Int8
ConvertAttempt Float Int8
ConvertAttempt Float Int16
ConvertAttempt Float Int16
ConvertAttempt Float Int32
ConvertAttempt Float Int32
ConvertAttempt Float Int64
ConvertAttempt Float Int64
ConvertAttempt Float Word
ConvertAttempt Float Word
ConvertAttempt Float Word8
ConvertAttempt Float Word8
ConvertAttempt Float Word16
ConvertAttempt Float Word16
ConvertAttempt Float Word32
ConvertAttempt Float Word32
ConvertAttempt Float Word64
ConvertAttempt Float Word64
ConvertAttempt Int Char
ConvertAttempt Int Char
ConvertAttempt Int Int8
ConvertAttempt Int Int8
ConvertAttempt Int Int16
ConvertAttempt Int Int16
ConvertAttempt Int Int32
ConvertAttempt Int Int32
ConvertAttempt Int Int64
ConvertAttempt Int Int64
ConvertAttempt Int Word
ConvertAttempt Int Word
ConvertAttempt Int Word8
ConvertAttempt Int Word8
ConvertAttempt Int Word16
ConvertAttempt Int Word16
ConvertAttempt Int Word32
ConvertAttempt Int Word32
ConvertAttempt Int Word64
ConvertAttempt Int Word64
ConvertAttempt Int CChar
ConvertAttempt Int CChar
ConvertAttempt Int CSChar
ConvertAttempt Int CSChar
ConvertAttempt Int CUChar
ConvertAttempt Int CUChar
ConvertAttempt Int CShort
ConvertAttempt Int CShort
ConvertAttempt Int CUShort
ConvertAttempt Int CUShort
ConvertAttempt Int CInt
ConvertAttempt Int CInt
ConvertAttempt Int CUInt
ConvertAttempt Int CUInt
ConvertAttempt Int CLong
ConvertAttempt Int CLong
ConvertAttempt Int CULong
ConvertAttempt Int CULong
ConvertAttempt Int CLLong
ConvertAttempt Int CLLong
ConvertAttempt Int CULLong
ConvertAttempt Int CULLong
ConvertAttempt Int CSize
ConvertAttempt Int CSize
ConvertAttempt Int CWchar
ConvertAttempt Int CWchar
ConvertAttempt Int CTime
ConvertAttempt Int CTime
ConvertAttempt Int POSIXTime
ConvertAttempt Int POSIXTime
ConvertAttempt Int UTCTime
ConvertAttempt Int UTCTime
ConvertAttempt Int8 Char
ConvertAttempt Int8 Char
ConvertAttempt Int8 Int
ConvertAttempt Int8 Int
ConvertAttempt Int8 Int16
ConvertAttempt Int8 Int16
ConvertAttempt Int8 Int32
ConvertAttempt Int8 Int32
ConvertAttempt Int8 Int64
ConvertAttempt Int8 Int64
ConvertAttempt Int8 Word
ConvertAttempt Int8 Word
ConvertAttempt Int8 Word8
ConvertAttempt Int8 Word8
ConvertAttempt Int8 Word16
ConvertAttempt Int8 Word16
ConvertAttempt Int8 Word32
ConvertAttempt Int8 Word32
ConvertAttempt Int8 Word64
ConvertAttempt Int8 Word64
ConvertAttempt Int8 CChar
ConvertAttempt Int8 CChar
ConvertAttempt Int8 CSChar
ConvertAttempt Int8 CSChar
ConvertAttempt Int8 CUChar
ConvertAttempt Int8 CUChar
ConvertAttempt Int8 CShort
ConvertAttempt Int8 CShort
ConvertAttempt Int8 CUShort
ConvertAttempt Int8 CUShort
ConvertAttempt Int8 CInt
ConvertAttempt Int8 CInt
ConvertAttempt Int8 CUInt
ConvertAttempt Int8 CUInt
ConvertAttempt Int8 CLong
ConvertAttempt Int8 CLong
ConvertAttempt Int8 CULong
ConvertAttempt Int8 CULong
ConvertAttempt Int8 CLLong
ConvertAttempt Int8 CLLong
ConvertAttempt Int8 CULLong
ConvertAttempt Int8 CULLong
ConvertAttempt Int8 CSize
ConvertAttempt Int8 CSize
ConvertAttempt Int8 CWchar
ConvertAttempt Int8 CWchar
ConvertAttempt Int16 Char
ConvertAttempt Int16 Char
ConvertAttempt Int16 Int
ConvertAttempt Int16 Int
ConvertAttempt Int16 Int8
ConvertAttempt Int16 Int8
ConvertAttempt Int16 Int32
ConvertAttempt Int16 Int32
ConvertAttempt Int16 Int64
ConvertAttempt Int16 Int64
ConvertAttempt Int16 Word
ConvertAttempt Int16 Word
ConvertAttempt Int16 Word8
ConvertAttempt Int16 Word8
ConvertAttempt Int16 Word16
ConvertAttempt Int16 Word16
ConvertAttempt Int16 Word32
ConvertAttempt Int16 Word32
ConvertAttempt Int16 Word64
ConvertAttempt Int16 Word64
ConvertAttempt Int16 CChar
ConvertAttempt Int16 CChar
ConvertAttempt Int16 CSChar
ConvertAttempt Int16 CSChar
ConvertAttempt Int16 CUChar
ConvertAttempt Int16 CUChar
ConvertAttempt Int16 CShort
ConvertAttempt Int16 CShort
ConvertAttempt Int16 CUShort
ConvertAttempt Int16 CUShort
ConvertAttempt Int16 CInt
ConvertAttempt Int16 CInt
ConvertAttempt Int16 CUInt
ConvertAttempt Int16 CUInt
ConvertAttempt Int16 CLong
ConvertAttempt Int16 CLong
ConvertAttempt Int16 CULong
ConvertAttempt Int16 CULong
ConvertAttempt Int16 CLLong
ConvertAttempt Int16 CLLong
ConvertAttempt Int16 CULLong
ConvertAttempt Int16 CULLong
ConvertAttempt Int16 CSize
ConvertAttempt Int16 CSize
ConvertAttempt Int16 CWchar
ConvertAttempt Int16 CWchar
ConvertAttempt Int32 Char
ConvertAttempt Int32 Char
ConvertAttempt Int32 Int
ConvertAttempt Int32 Int
ConvertAttempt Int32 Int8
ConvertAttempt Int32 Int8
ConvertAttempt Int32 Int16
ConvertAttempt Int32 Int16
ConvertAttempt Int32 Int64
ConvertAttempt Int32 Int64
ConvertAttempt Int32 Word
ConvertAttempt Int32 Word
ConvertAttempt Int32 Word8
ConvertAttempt Int32 Word8
ConvertAttempt Int32 Word16
ConvertAttempt Int32 Word16
ConvertAttempt Int32 Word32
ConvertAttempt Int32 Word32
ConvertAttempt Int32 Word64
ConvertAttempt Int32 Word64
ConvertAttempt Int32 CChar
ConvertAttempt Int32 CChar
ConvertAttempt Int32 CSChar
ConvertAttempt Int32 CSChar
ConvertAttempt Int32 CUChar
ConvertAttempt Int32 CUChar
ConvertAttempt Int32 CShort
ConvertAttempt Int32 CShort
ConvertAttempt Int32 CUShort
ConvertAttempt Int32 CUShort
ConvertAttempt Int32 CInt
ConvertAttempt Int32 CInt
ConvertAttempt Int32 CUInt
ConvertAttempt Int32 CUInt
ConvertAttempt Int32 CLong
ConvertAttempt Int32 CLong
ConvertAttempt Int32 CULong
ConvertAttempt Int32 CULong
ConvertAttempt Int32 CLLong
ConvertAttempt Int32 CLLong
ConvertAttempt Int32 CULLong
ConvertAttempt Int32 CULLong
ConvertAttempt Int32 CSize
ConvertAttempt Int32 CSize
ConvertAttempt Int32 CWchar
ConvertAttempt Int32 CWchar
ConvertAttempt Int64 Char
ConvertAttempt Int64 Char
ConvertAttempt Int64 Int
ConvertAttempt Int64 Int
ConvertAttempt Int64 Int8
ConvertAttempt Int64 Int8
ConvertAttempt Int64 Int16
ConvertAttempt Int64 Int16
ConvertAttempt Int64 Int32
ConvertAttempt Int64 Int32
ConvertAttempt Int64 Word
ConvertAttempt Int64 Word
ConvertAttempt Int64 Word8
ConvertAttempt Int64 Word8
ConvertAttempt Int64 Word16
ConvertAttempt Int64 Word16
ConvertAttempt Int64 Word32
ConvertAttempt Int64 Word32
ConvertAttempt Int64 Word64
ConvertAttempt Int64 Word64
ConvertAttempt Int64 CChar
ConvertAttempt Int64 CChar
ConvertAttempt Int64 CSChar
ConvertAttempt Int64 CSChar
ConvertAttempt Int64 CUChar
ConvertAttempt Int64 CUChar
ConvertAttempt Int64 CShort
ConvertAttempt Int64 CShort
ConvertAttempt Int64 CUShort
ConvertAttempt Int64 CUShort
ConvertAttempt Int64 CInt
ConvertAttempt Int64 CInt
ConvertAttempt Int64 CUInt
ConvertAttempt Int64 CUInt
ConvertAttempt Int64 CLong
ConvertAttempt Int64 CLong
ConvertAttempt Int64 CULong
ConvertAttempt Int64 CULong
ConvertAttempt Int64 CLLong
ConvertAttempt Int64 CLLong
ConvertAttempt Int64 CULLong
ConvertAttempt Int64 CULLong
ConvertAttempt Int64 CSize
ConvertAttempt Int64 CSize
ConvertAttempt Int64 CWchar
ConvertAttempt Int64 CWchar
ConvertAttempt Integer Int
ConvertAttempt Integer Int
ConvertAttempt Integer Int8
ConvertAttempt Integer Int8
ConvertAttempt Integer Int16
ConvertAttempt Integer Int16
ConvertAttempt Integer Int32
ConvertAttempt Integer Int32
ConvertAttempt Integer Int64
ConvertAttempt Integer Int64
ConvertAttempt Integer Word
ConvertAttempt Integer Word
ConvertAttempt Integer Word8
ConvertAttempt Integer Word8
ConvertAttempt Integer Word16
ConvertAttempt Integer Word16
ConvertAttempt Integer Word32
ConvertAttempt Integer Word32
ConvertAttempt Integer Word64
ConvertAttempt Integer Word64
ConvertAttempt Integer CChar
ConvertAttempt Integer CChar
ConvertAttempt Integer CSChar
ConvertAttempt Integer CSChar
ConvertAttempt Integer CUChar
ConvertAttempt Integer CUChar
ConvertAttempt Integer CShort
ConvertAttempt Integer CShort
ConvertAttempt Integer CUShort
ConvertAttempt Integer CUShort
ConvertAttempt Integer CInt
ConvertAttempt Integer CInt
ConvertAttempt Integer CUInt
ConvertAttempt Integer CUInt
ConvertAttempt Integer CLong
ConvertAttempt Integer CLong
ConvertAttempt Integer CULong
ConvertAttempt Integer CULong
ConvertAttempt Integer CLLong
ConvertAttempt Integer CLLong
ConvertAttempt Integer CULLong
ConvertAttempt Integer CULLong
ConvertAttempt Integer CSize
ConvertAttempt Integer CSize
ConvertAttempt Integer CWchar
ConvertAttempt Integer CWchar
ConvertAttempt Integer CTime
ConvertAttempt Integer CTime
ConvertAttempt Integer ClockTime
ConvertAttempt Integer ClockTime
ConvertAttempt Integer TimeDiff
ConvertAttempt Integer TimeDiff
ConvertAttempt Integer POSIXTime
ConvertAttempt Integer POSIXTime
ConvertAttempt Integer UTCTime
ConvertAttempt Integer UTCTime
ConvertAttempt Rational Int
ConvertAttempt Rational Int
ConvertAttempt Rational Int8
ConvertAttempt Rational Int8
ConvertAttempt Rational Int16
ConvertAttempt Rational Int16
ConvertAttempt Rational Int32
ConvertAttempt Rational Int32
ConvertAttempt Rational Int64
ConvertAttempt Rational Int64
ConvertAttempt Rational Word
ConvertAttempt Rational Word
ConvertAttempt Rational Word8
ConvertAttempt Rational Word8
ConvertAttempt Rational Word16
ConvertAttempt Rational Word16
ConvertAttempt Rational Word32
ConvertAttempt Rational Word32
ConvertAttempt Rational Word64
ConvertAttempt Rational Word64
ConvertAttempt Rational POSIXTime
ConvertAttempt Rational POSIXTime
ConvertAttempt Rational UTCTime
ConvertAttempt Rational UTCTime
ConvertAttempt Word Char
ConvertAttempt Word Char
ConvertAttempt Word Int
ConvertAttempt Word Int
ConvertAttempt Word Int8
ConvertAttempt Word Int8
ConvertAttempt Word Int16
ConvertAttempt Word Int16
ConvertAttempt Word Int32
ConvertAttempt Word Int32
ConvertAttempt Word Int64
ConvertAttempt Word Int64
ConvertAttempt Word Word8
ConvertAttempt Word Word8
ConvertAttempt Word Word16
ConvertAttempt Word Word16
ConvertAttempt Word Word32
ConvertAttempt Word Word32
ConvertAttempt Word Word64
ConvertAttempt Word Word64
ConvertAttempt Word CChar
ConvertAttempt Word CChar
ConvertAttempt Word CSChar
ConvertAttempt Word CSChar
ConvertAttempt Word CUChar
ConvertAttempt Word CUChar
ConvertAttempt Word CShort
ConvertAttempt Word CShort
ConvertAttempt Word CUShort
ConvertAttempt Word CUShort
ConvertAttempt Word CInt
ConvertAttempt Word CInt
ConvertAttempt Word CUInt
ConvertAttempt Word CUInt
ConvertAttempt Word CLong
ConvertAttempt Word CLong
ConvertAttempt Word CULong
ConvertAttempt Word CULong
ConvertAttempt Word CLLong
ConvertAttempt Word CLLong
ConvertAttempt Word CULLong
ConvertAttempt Word CULLong
ConvertAttempt Word CSize
ConvertAttempt Word CSize
ConvertAttempt Word CWchar
ConvertAttempt Word CWchar
ConvertAttempt Word8 Char
ConvertAttempt Word8 Char
ConvertAttempt Word8 Int
ConvertAttempt Word8 Int
ConvertAttempt Word8 Int8
ConvertAttempt Word8 Int8
ConvertAttempt Word8 Int16
ConvertAttempt Word8 Int16
ConvertAttempt Word8 Int32
ConvertAttempt Word8 Int32
ConvertAttempt Word8 Int64
ConvertAttempt Word8 Int64
ConvertAttempt Word8 Word
ConvertAttempt Word8 Word
ConvertAttempt Word8 Word16
ConvertAttempt Word8 Word16
ConvertAttempt Word8 Word32
ConvertAttempt Word8 Word32
ConvertAttempt Word8 Word64
ConvertAttempt Word8 Word64
ConvertAttempt Word8 CChar
ConvertAttempt Word8 CChar
ConvertAttempt Word8 CSChar
ConvertAttempt Word8 CSChar
ConvertAttempt Word8 CUChar
ConvertAttempt Word8 CUChar
ConvertAttempt Word8 CShort
ConvertAttempt Word8 CShort
ConvertAttempt Word8 CUShort
ConvertAttempt Word8 CUShort
ConvertAttempt Word8 CInt
ConvertAttempt Word8 CInt
ConvertAttempt Word8 CUInt
ConvertAttempt Word8 CUInt
ConvertAttempt Word8 CLong
ConvertAttempt Word8 CLong
ConvertAttempt Word8 CULong
ConvertAttempt Word8 CULong
ConvertAttempt Word8 CLLong
ConvertAttempt Word8 CLLong
ConvertAttempt Word8 CULLong
ConvertAttempt Word8 CULLong
ConvertAttempt Word8 CSize
ConvertAttempt Word8 CSize
ConvertAttempt Word8 CWchar
ConvertAttempt Word8 CWchar
ConvertAttempt Word16 Char
ConvertAttempt Word16 Char
ConvertAttempt Word16 Int
ConvertAttempt Word16 Int
ConvertAttempt Word16 Int8
ConvertAttempt Word16 Int8
ConvertAttempt Word16 Int16
ConvertAttempt Word16 Int16
ConvertAttempt Word16 Int32
ConvertAttempt Word16 Int32
ConvertAttempt Word16 Int64
ConvertAttempt Word16 Int64
ConvertAttempt Word16 Word
ConvertAttempt Word16 Word
ConvertAttempt Word16 Word8
ConvertAttempt Word16 Word8
ConvertAttempt Word16 Word32
ConvertAttempt Word16 Word32
ConvertAttempt Word16 Word64
ConvertAttempt Word16 Word64
ConvertAttempt Word16 CChar
ConvertAttempt Word16 CChar
ConvertAttempt Word16 CSChar
ConvertAttempt Word16 CSChar
ConvertAttempt Word16 CUChar
ConvertAttempt Word16 CUChar
ConvertAttempt Word16 CShort
ConvertAttempt Word16 CShort
ConvertAttempt Word16 CUShort
ConvertAttempt Word16 CUShort
ConvertAttempt Word16 CInt
ConvertAttempt Word16 CInt
ConvertAttempt Word16 CUInt
ConvertAttempt Word16 CUInt
ConvertAttempt Word16 CLong
ConvertAttempt Word16 CLong
ConvertAttempt Word16 CULong
ConvertAttempt Word16 CULong
ConvertAttempt Word16 CLLong
ConvertAttempt Word16 CLLong
ConvertAttempt Word16 CULLong
ConvertAttempt Word16 CULLong
ConvertAttempt Word16 CSize
ConvertAttempt Word16 CSize
ConvertAttempt Word16 CWchar
ConvertAttempt Word16 CWchar
ConvertAttempt Word32 Char
ConvertAttempt Word32 Char
ConvertAttempt Word32 Int
ConvertAttempt Word32 Int
ConvertAttempt Word32 Int8
ConvertAttempt Word32 Int8
ConvertAttempt Word32 Int16
ConvertAttempt Word32 Int16
ConvertAttempt Word32 Int32
ConvertAttempt Word32 Int32
ConvertAttempt Word32 Int64
ConvertAttempt Word32 Int64
ConvertAttempt Word32 Word
ConvertAttempt Word32 Word
ConvertAttempt Word32 Word8
ConvertAttempt Word32 Word8
ConvertAttempt Word32 Word16
ConvertAttempt Word32 Word16
ConvertAttempt Word32 Word64
ConvertAttempt Word32 Word64
ConvertAttempt Word32 CChar
ConvertAttempt Word32 CChar
ConvertAttempt Word32 CSChar
ConvertAttempt Word32 CSChar
ConvertAttempt Word32 CUChar
ConvertAttempt Word32 CUChar
ConvertAttempt Word32 CShort
ConvertAttempt Word32 CShort
ConvertAttempt Word32 CUShort
ConvertAttempt Word32 CUShort
ConvertAttempt Word32 CInt
ConvertAttempt Word32 CInt
ConvertAttempt Word32 CUInt
ConvertAttempt Word32 CUInt
ConvertAttempt Word32 CLong
ConvertAttempt Word32 CLong
ConvertAttempt Word32 CULong
ConvertAttempt Word32 CULong
ConvertAttempt Word32 CLLong
ConvertAttempt Word32 CLLong
ConvertAttempt Word32 CULLong
ConvertAttempt Word32 CULLong
ConvertAttempt Word32 CSize
ConvertAttempt Word32 CSize
ConvertAttempt Word32 CWchar
ConvertAttempt Word32 CWchar
ConvertAttempt Word64 Char
ConvertAttempt Word64 Char
ConvertAttempt Word64 Int
ConvertAttempt Word64 Int
ConvertAttempt Word64 Int8
ConvertAttempt Word64 Int8
ConvertAttempt Word64 Int16
ConvertAttempt Word64 Int16
ConvertAttempt Word64 Int32
ConvertAttempt Word64 Int32
ConvertAttempt Word64 Int64
ConvertAttempt Word64 Int64
ConvertAttempt Word64 Word
ConvertAttempt Word64 Word
ConvertAttempt Word64 Word8
ConvertAttempt Word64 Word8
ConvertAttempt Word64 Word16
ConvertAttempt Word64 Word16
ConvertAttempt Word64 Word32
ConvertAttempt Word64 Word32
ConvertAttempt Word64 CChar
ConvertAttempt Word64 CChar
ConvertAttempt Word64 CSChar
ConvertAttempt Word64 CSChar
ConvertAttempt Word64 CUChar
ConvertAttempt Word64 CUChar
ConvertAttempt Word64 CShort
ConvertAttempt Word64 CShort
ConvertAttempt Word64 CUShort
ConvertAttempt Word64 CUShort
ConvertAttempt Word64 CInt
ConvertAttempt Word64 CInt
ConvertAttempt Word64 CUInt
ConvertAttempt Word64 CUInt
ConvertAttempt Word64 CLong
ConvertAttempt Word64 CLong
ConvertAttempt Word64 CULong
ConvertAttempt Word64 CULong
ConvertAttempt Word64 CLLong
ConvertAttempt Word64 CLLong
ConvertAttempt Word64 CULLong
ConvertAttempt Word64 CULLong
ConvertAttempt Word64 CSize
ConvertAttempt Word64 CSize
ConvertAttempt Word64 CWchar
ConvertAttempt Word64 CWchar
ConvertAttempt CChar Char
ConvertAttempt CChar Char
ConvertAttempt CChar Int
ConvertAttempt CChar Int
ConvertAttempt CChar Int8
ConvertAttempt CChar Int8
ConvertAttempt CChar Int16
ConvertAttempt CChar Int16
ConvertAttempt CChar Int32
ConvertAttempt CChar Int32
ConvertAttempt CChar Int64
ConvertAttempt CChar Int64
ConvertAttempt CChar Word
ConvertAttempt CChar Word
ConvertAttempt CChar Word8
ConvertAttempt CChar Word8
ConvertAttempt CChar Word16
ConvertAttempt CChar Word16
ConvertAttempt CChar Word32
ConvertAttempt CChar Word32
ConvertAttempt CChar Word64
ConvertAttempt CChar Word64
ConvertAttempt CChar CSChar
ConvertAttempt CChar CSChar
ConvertAttempt CChar CUChar
ConvertAttempt CChar CUChar
ConvertAttempt CChar CShort
ConvertAttempt CChar CShort
ConvertAttempt CChar CUShort
ConvertAttempt CChar CUShort
ConvertAttempt CChar CInt
ConvertAttempt CChar CInt
ConvertAttempt CChar CUInt
ConvertAttempt CChar CUInt
ConvertAttempt CChar CLong
ConvertAttempt CChar CLong
ConvertAttempt CChar CULong
ConvertAttempt CChar CULong
ConvertAttempt CChar CLLong
ConvertAttempt CChar CLLong
ConvertAttempt CChar CULLong
ConvertAttempt CChar CULLong
ConvertAttempt CChar CSize
ConvertAttempt CChar CSize
ConvertAttempt CChar CWchar
ConvertAttempt CChar CWchar
ConvertAttempt CSChar Char
ConvertAttempt CSChar Char
ConvertAttempt CSChar Int
ConvertAttempt CSChar Int
ConvertAttempt CSChar Int8
ConvertAttempt CSChar Int8
ConvertAttempt CSChar Int16
ConvertAttempt CSChar Int16
ConvertAttempt CSChar Int32
ConvertAttempt CSChar Int32
ConvertAttempt CSChar Int64
ConvertAttempt CSChar Int64
ConvertAttempt CSChar Word
ConvertAttempt CSChar Word
ConvertAttempt CSChar Word8
ConvertAttempt CSChar Word8
ConvertAttempt CSChar Word16
ConvertAttempt CSChar Word16
ConvertAttempt CSChar Word32
ConvertAttempt CSChar Word32
ConvertAttempt CSChar Word64
ConvertAttempt CSChar Word64
ConvertAttempt CSChar CChar
ConvertAttempt CSChar CChar
ConvertAttempt CSChar CUChar
ConvertAttempt CSChar CUChar
ConvertAttempt CSChar CShort
ConvertAttempt CSChar CShort
ConvertAttempt CSChar CUShort
ConvertAttempt CSChar CUShort
ConvertAttempt CSChar CInt
ConvertAttempt CSChar CInt
ConvertAttempt CSChar CUInt
ConvertAttempt CSChar CUInt
ConvertAttempt CSChar CLong
ConvertAttempt CSChar CLong
ConvertAttempt CSChar CULong
ConvertAttempt CSChar CULong
ConvertAttempt CSChar CLLong
ConvertAttempt CSChar CLLong
ConvertAttempt CSChar CULLong
ConvertAttempt CSChar CULLong
ConvertAttempt CSChar CSize
ConvertAttempt CSChar CSize
ConvertAttempt CSChar CWchar
ConvertAttempt CSChar CWchar
ConvertAttempt CUChar Char
ConvertAttempt CUChar Char
ConvertAttempt CUChar Int
ConvertAttempt CUChar Int
ConvertAttempt CUChar Int8
ConvertAttempt CUChar Int8
ConvertAttempt CUChar Int16
ConvertAttempt CUChar Int16
ConvertAttempt CUChar Int32
ConvertAttempt CUChar Int32
ConvertAttempt CUChar Int64
ConvertAttempt CUChar Int64
ConvertAttempt CUChar Word
ConvertAttempt CUChar Word
ConvertAttempt CUChar Word8
ConvertAttempt CUChar Word8
ConvertAttempt CUChar Word16
ConvertAttempt CUChar Word16
ConvertAttempt CUChar Word32
ConvertAttempt CUChar Word32
ConvertAttempt CUChar Word64
ConvertAttempt CUChar Word64
ConvertAttempt CUChar CChar
ConvertAttempt CUChar CChar
ConvertAttempt CUChar CSChar
ConvertAttempt CUChar CSChar
ConvertAttempt CUChar CShort
ConvertAttempt CUChar CShort
ConvertAttempt CUChar CUShort
ConvertAttempt CUChar CUShort
ConvertAttempt CUChar CInt
ConvertAttempt CUChar CInt
ConvertAttempt CUChar CUInt
ConvertAttempt CUChar CUInt
ConvertAttempt CUChar CLong
ConvertAttempt CUChar CLong
ConvertAttempt CUChar CULong
ConvertAttempt CUChar CULong
ConvertAttempt CUChar CLLong
ConvertAttempt CUChar CLLong
ConvertAttempt CUChar CULLong
ConvertAttempt CUChar CULLong
ConvertAttempt CUChar CSize
ConvertAttempt CUChar CSize
ConvertAttempt CUChar CWchar
ConvertAttempt CUChar CWchar
ConvertAttempt CShort Char
ConvertAttempt CShort Char
ConvertAttempt CShort Int
ConvertAttempt CShort Int
ConvertAttempt CShort Int8
ConvertAttempt CShort Int8
ConvertAttempt CShort Int16
ConvertAttempt CShort Int16
ConvertAttempt CShort Int32
ConvertAttempt CShort Int32
ConvertAttempt CShort Int64
ConvertAttempt CShort Int64
ConvertAttempt CShort Word
ConvertAttempt CShort Word
ConvertAttempt CShort Word8
ConvertAttempt CShort Word8
ConvertAttempt CShort Word16
ConvertAttempt CShort Word16
ConvertAttempt CShort Word32
ConvertAttempt CShort Word32
ConvertAttempt CShort Word64
ConvertAttempt CShort Word64
ConvertAttempt CShort CChar
ConvertAttempt CShort CChar
ConvertAttempt CShort CSChar
ConvertAttempt CShort CSChar
ConvertAttempt CShort CUChar
ConvertAttempt CShort CUChar
ConvertAttempt CShort CUShort
ConvertAttempt CShort CUShort
ConvertAttempt CShort CInt
ConvertAttempt CShort CInt
ConvertAttempt CShort CUInt
ConvertAttempt CShort CUInt
ConvertAttempt CShort CLong
ConvertAttempt CShort CLong
ConvertAttempt CShort CULong
ConvertAttempt CShort CULong
ConvertAttempt CShort CLLong
ConvertAttempt CShort CLLong
ConvertAttempt CShort CULLong
ConvertAttempt CShort CULLong
ConvertAttempt CShort CSize
ConvertAttempt CShort CSize
ConvertAttempt CShort CWchar
ConvertAttempt CShort CWchar
ConvertAttempt CUShort Char
ConvertAttempt CUShort Char
ConvertAttempt CUShort Int
ConvertAttempt CUShort Int
ConvertAttempt CUShort Int8
ConvertAttempt CUShort Int8
ConvertAttempt CUShort Int16
ConvertAttempt CUShort Int16
ConvertAttempt CUShort Int32
ConvertAttempt CUShort Int32
ConvertAttempt CUShort Int64
ConvertAttempt CUShort Int64
ConvertAttempt CUShort Word
ConvertAttempt CUShort Word
ConvertAttempt CUShort Word8
ConvertAttempt CUShort Word8
ConvertAttempt CUShort Word16
ConvertAttempt CUShort Word16
ConvertAttempt CUShort Word32
ConvertAttempt CUShort Word32
ConvertAttempt CUShort Word64
ConvertAttempt CUShort Word64
ConvertAttempt CUShort CChar
ConvertAttempt CUShort CChar
ConvertAttempt CUShort CSChar
ConvertAttempt CUShort CSChar
ConvertAttempt CUShort CUChar
ConvertAttempt CUShort CUChar
ConvertAttempt CUShort CShort
ConvertAttempt CUShort CShort
ConvertAttempt CUShort CInt
ConvertAttempt CUShort CInt
ConvertAttempt CUShort CUInt
ConvertAttempt CUShort CUInt
ConvertAttempt CUShort CLong
ConvertAttempt CUShort CLong
ConvertAttempt CUShort CULong
ConvertAttempt CUShort CULong
ConvertAttempt CUShort CLLong
ConvertAttempt CUShort CLLong
ConvertAttempt CUShort CULLong
ConvertAttempt CUShort CULLong
ConvertAttempt CUShort CSize
ConvertAttempt CUShort CSize
ConvertAttempt CUShort CWchar
ConvertAttempt CUShort CWchar
ConvertAttempt CInt Char
ConvertAttempt CInt Char
ConvertAttempt CInt Int
ConvertAttempt CInt Int
ConvertAttempt CInt Int8
ConvertAttempt CInt Int8
ConvertAttempt CInt Int16
ConvertAttempt CInt Int16
ConvertAttempt CInt Int32
ConvertAttempt CInt Int32
ConvertAttempt CInt Int64
ConvertAttempt CInt Int64
ConvertAttempt CInt Word
ConvertAttempt CInt Word
ConvertAttempt CInt Word8
ConvertAttempt CInt Word8
ConvertAttempt CInt Word16
ConvertAttempt CInt Word16
ConvertAttempt CInt Word32
ConvertAttempt CInt Word32
ConvertAttempt CInt Word64
ConvertAttempt CInt Word64
ConvertAttempt CInt CChar
ConvertAttempt CInt CChar
ConvertAttempt CInt CSChar
ConvertAttempt CInt CSChar
ConvertAttempt CInt CUChar
ConvertAttempt CInt CUChar
ConvertAttempt CInt CShort
ConvertAttempt CInt CShort
ConvertAttempt CInt CUShort
ConvertAttempt CInt CUShort
ConvertAttempt CInt CUInt
ConvertAttempt CInt CUInt
ConvertAttempt CInt CLong
ConvertAttempt CInt CLong
ConvertAttempt CInt CULong
ConvertAttempt CInt CULong
ConvertAttempt CInt CLLong
ConvertAttempt CInt CLLong
ConvertAttempt CInt CULLong
ConvertAttempt CInt CULLong
ConvertAttempt CInt CSize
ConvertAttempt CInt CSize
ConvertAttempt CInt CWchar
ConvertAttempt CInt CWchar
ConvertAttempt CUInt Char
ConvertAttempt CUInt Char
ConvertAttempt CUInt Int
ConvertAttempt CUInt Int
ConvertAttempt CUInt Int8
ConvertAttempt CUInt Int8
ConvertAttempt CUInt Int16
ConvertAttempt CUInt Int16
ConvertAttempt CUInt Int32
ConvertAttempt CUInt Int32
ConvertAttempt CUInt Int64
ConvertAttempt CUInt Int64
ConvertAttempt CUInt Word
ConvertAttempt CUInt Word
ConvertAttempt CUInt Word8
ConvertAttempt CUInt Word8
ConvertAttempt CUInt Word16
ConvertAttempt CUInt Word16
ConvertAttempt CUInt Word32
ConvertAttempt CUInt Word32
ConvertAttempt CUInt Word64
ConvertAttempt CUInt Word64
ConvertAttempt CUInt CChar
ConvertAttempt CUInt CChar
ConvertAttempt CUInt CSChar
ConvertAttempt CUInt CSChar
ConvertAttempt CUInt CUChar
ConvertAttempt CUInt CUChar
ConvertAttempt CUInt CShort
ConvertAttempt CUInt CShort
ConvertAttempt CUInt CUShort
ConvertAttempt CUInt CUShort
ConvertAttempt CUInt CInt
ConvertAttempt CUInt CInt
ConvertAttempt CUInt CLong
ConvertAttempt CUInt CLong
ConvertAttempt CUInt CULong
ConvertAttempt CUInt CULong
ConvertAttempt CUInt CLLong
ConvertAttempt CUInt CLLong
ConvertAttempt CUInt CULLong
ConvertAttempt CUInt CULLong
ConvertAttempt CUInt CSize
ConvertAttempt CUInt CSize
ConvertAttempt CUInt CWchar
ConvertAttempt CUInt CWchar
ConvertAttempt CLong Char
ConvertAttempt CLong Char
ConvertAttempt CLong Int
ConvertAttempt CLong Int
ConvertAttempt CLong Int8
ConvertAttempt CLong Int8
ConvertAttempt CLong Int16
ConvertAttempt CLong Int16
ConvertAttempt CLong Int32
ConvertAttempt CLong Int32
ConvertAttempt CLong Int64
ConvertAttempt CLong Int64
ConvertAttempt CLong Word
ConvertAttempt CLong Word
ConvertAttempt CLong Word8
ConvertAttempt CLong Word8
ConvertAttempt CLong Word16
ConvertAttempt CLong Word16
ConvertAttempt CLong Word32
ConvertAttempt CLong Word32
ConvertAttempt CLong Word64
ConvertAttempt CLong Word64
ConvertAttempt CLong CChar
ConvertAttempt CLong CChar
ConvertAttempt CLong CSChar
ConvertAttempt CLong CSChar
ConvertAttempt CLong CUChar
ConvertAttempt CLong CUChar
ConvertAttempt CLong CShort
ConvertAttempt CLong CShort
ConvertAttempt CLong CUShort
ConvertAttempt CLong CUShort
ConvertAttempt CLong CInt
ConvertAttempt CLong CInt
ConvertAttempt CLong CUInt
ConvertAttempt CLong CUInt
ConvertAttempt CLong CULong
ConvertAttempt CLong CULong
ConvertAttempt CLong CLLong
ConvertAttempt CLong CLLong
ConvertAttempt CLong CULLong
ConvertAttempt CLong CULLong
ConvertAttempt CLong CSize
ConvertAttempt CLong CSize
ConvertAttempt CLong CWchar
ConvertAttempt CLong CWchar
ConvertAttempt CULong Char
ConvertAttempt CULong Char
ConvertAttempt CULong Int
ConvertAttempt CULong Int
ConvertAttempt CULong Int8
ConvertAttempt CULong Int8
ConvertAttempt CULong Int16
ConvertAttempt CULong Int16
ConvertAttempt CULong Int32
ConvertAttempt CULong Int32
ConvertAttempt CULong Int64
ConvertAttempt CULong Int64
ConvertAttempt CULong Word
ConvertAttempt CULong Word
ConvertAttempt CULong Word8
ConvertAttempt CULong Word8
ConvertAttempt CULong Word16
ConvertAttempt CULong Word16
ConvertAttempt CULong Word32
ConvertAttempt CULong Word32
ConvertAttempt CULong Word64
ConvertAttempt CULong Word64
ConvertAttempt CULong CChar
ConvertAttempt CULong CChar
ConvertAttempt CULong CSChar
ConvertAttempt CULong CSChar
ConvertAttempt CULong CUChar
ConvertAttempt CULong CUChar
ConvertAttempt CULong CShort
ConvertAttempt CULong CShort
ConvertAttempt CULong CUShort
ConvertAttempt CULong CUShort
ConvertAttempt CULong CInt
ConvertAttempt CULong CInt
ConvertAttempt CULong CUInt
ConvertAttempt CULong CUInt
ConvertAttempt CULong CLong
ConvertAttempt CULong CLong
ConvertAttempt CULong CLLong
ConvertAttempt CULong CLLong
ConvertAttempt CULong CULLong
ConvertAttempt CULong CULLong
ConvertAttempt CULong CSize
ConvertAttempt CULong CSize
ConvertAttempt CULong CWchar
ConvertAttempt CULong CWchar
ConvertAttempt CLLong Char
ConvertAttempt CLLong Char
ConvertAttempt CLLong Int
ConvertAttempt CLLong Int
ConvertAttempt CLLong Int8
ConvertAttempt CLLong Int8
ConvertAttempt CLLong Int16
ConvertAttempt CLLong Int16
ConvertAttempt CLLong Int32
ConvertAttempt CLLong Int32
ConvertAttempt CLLong Int64
ConvertAttempt CLLong Int64
ConvertAttempt CLLong Word
ConvertAttempt CLLong Word
ConvertAttempt CLLong Word8
ConvertAttempt CLLong Word8
ConvertAttempt CLLong Word16
ConvertAttempt CLLong Word16
ConvertAttempt CLLong Word32
ConvertAttempt CLLong Word32
ConvertAttempt CLLong Word64
ConvertAttempt CLLong Word64
ConvertAttempt CLLong CChar
ConvertAttempt CLLong CChar
ConvertAttempt CLLong CSChar
ConvertAttempt CLLong CSChar
ConvertAttempt CLLong CUChar
ConvertAttempt CLLong CUChar
ConvertAttempt CLLong CShort
ConvertAttempt CLLong CShort
ConvertAttempt CLLong CUShort
ConvertAttempt CLLong CUShort
ConvertAttempt CLLong CInt
ConvertAttempt CLLong CInt
ConvertAttempt CLLong CUInt
ConvertAttempt CLLong CUInt
ConvertAttempt CLLong CLong
ConvertAttempt CLLong CLong
ConvertAttempt CLLong CULong
ConvertAttempt CLLong CULong
ConvertAttempt CLLong CULLong
ConvertAttempt CLLong CULLong
ConvertAttempt CLLong CSize
ConvertAttempt CLLong CSize
ConvertAttempt CLLong CWchar
ConvertAttempt CLLong CWchar
ConvertAttempt CULLong Char
ConvertAttempt CULLong Char
ConvertAttempt CULLong Int
ConvertAttempt CULLong Int
ConvertAttempt CULLong Int8
ConvertAttempt CULLong Int8
ConvertAttempt CULLong Int16
ConvertAttempt CULLong Int16
ConvertAttempt CULLong Int32
ConvertAttempt CULLong Int32
ConvertAttempt CULLong Int64
ConvertAttempt CULLong Int64
ConvertAttempt CULLong Word
ConvertAttempt CULLong Word
ConvertAttempt CULLong Word8
ConvertAttempt CULLong Word8
ConvertAttempt CULLong Word16
ConvertAttempt CULLong Word16
ConvertAttempt CULLong Word32
ConvertAttempt CULLong Word32
ConvertAttempt CULLong Word64
ConvertAttempt CULLong Word64
ConvertAttempt CULLong CChar
ConvertAttempt CULLong CChar
ConvertAttempt CULLong CSChar
ConvertAttempt CULLong CSChar
ConvertAttempt CULLong CUChar
ConvertAttempt CULLong CUChar
ConvertAttempt CULLong CShort
ConvertAttempt CULLong CShort
ConvertAttempt CULLong CUShort
ConvertAttempt CULLong CUShort
ConvertAttempt CULLong CInt
ConvertAttempt CULLong CInt
ConvertAttempt CULLong CUInt
ConvertAttempt CULLong CUInt
ConvertAttempt CULLong CLong
ConvertAttempt CULLong CLong
ConvertAttempt CULLong CULong
ConvertAttempt CULLong CULong
ConvertAttempt CULLong CLLong
ConvertAttempt CULLong CLLong
ConvertAttempt CULLong CSize
ConvertAttempt CULLong CSize
ConvertAttempt CULLong CWchar
ConvertAttempt CULLong CWchar
ConvertAttempt CFloat Int
ConvertAttempt CFloat Int
ConvertAttempt CFloat Int8
ConvertAttempt CFloat Int8
ConvertAttempt CFloat Int16
ConvertAttempt CFloat Int16
ConvertAttempt CFloat Int32
ConvertAttempt CFloat Int32
ConvertAttempt CFloat Int64
ConvertAttempt CFloat Int64
ConvertAttempt CFloat Word
ConvertAttempt CFloat Word
ConvertAttempt CFloat Word8
ConvertAttempt CFloat Word8
ConvertAttempt CFloat Word16
ConvertAttempt CFloat Word16
ConvertAttempt CFloat Word32
ConvertAttempt CFloat Word32
ConvertAttempt CFloat Word64
ConvertAttempt CFloat Word64
ConvertAttempt CDouble Int
ConvertAttempt CDouble Int
ConvertAttempt CDouble Int8
ConvertAttempt CDouble Int8
ConvertAttempt CDouble Int16
ConvertAttempt CDouble Int16
ConvertAttempt CDouble Int32
ConvertAttempt CDouble Int32
ConvertAttempt CDouble Int64
ConvertAttempt CDouble Int64
ConvertAttempt CDouble Word
ConvertAttempt CDouble Word
ConvertAttempt CDouble Word8
ConvertAttempt CDouble Word8
ConvertAttempt CDouble Word16
ConvertAttempt CDouble Word16
ConvertAttempt CDouble Word32
ConvertAttempt CDouble Word32
ConvertAttempt CDouble Word64
ConvertAttempt CDouble Word64
ConvertAttempt CLDouble Int
ConvertAttempt CLDouble Int
ConvertAttempt CLDouble Int8
ConvertAttempt CLDouble Int8
ConvertAttempt CLDouble Int16
ConvertAttempt CLDouble Int16
ConvertAttempt CLDouble Int32
ConvertAttempt CLDouble Int32
ConvertAttempt CLDouble Int64
ConvertAttempt CLDouble Int64
ConvertAttempt CLDouble Word
ConvertAttempt CLDouble Word
ConvertAttempt CLDouble Word8
ConvertAttempt CLDouble Word8
ConvertAttempt CLDouble Word16
ConvertAttempt CLDouble Word16
ConvertAttempt CLDouble Word32
ConvertAttempt CLDouble Word32
ConvertAttempt CLDouble Word64
ConvertAttempt CLDouble Word64
ConvertAttempt CSize Char
ConvertAttempt CSize Char
ConvertAttempt CSize Int
ConvertAttempt CSize Int
ConvertAttempt CSize Int8
ConvertAttempt CSize Int8
ConvertAttempt CSize Int16
ConvertAttempt CSize Int16
ConvertAttempt CSize Int32
ConvertAttempt CSize Int32
ConvertAttempt CSize Int64
ConvertAttempt CSize Int64
ConvertAttempt CSize Word
ConvertAttempt CSize Word
ConvertAttempt CSize Word8
ConvertAttempt CSize Word8
ConvertAttempt CSize Word16
ConvertAttempt CSize Word16
ConvertAttempt CSize Word32
ConvertAttempt CSize Word32
ConvertAttempt CSize Word64
ConvertAttempt CSize Word64
ConvertAttempt CSize CChar
ConvertAttempt CSize CChar
ConvertAttempt CSize CSChar
ConvertAttempt CSize CSChar
ConvertAttempt CSize CUChar
ConvertAttempt CSize CUChar
ConvertAttempt CSize CShort
ConvertAttempt CSize CShort
ConvertAttempt CSize CUShort
ConvertAttempt CSize CUShort
ConvertAttempt CSize CInt
ConvertAttempt CSize CInt
ConvertAttempt CSize CUInt
ConvertAttempt CSize CUInt
ConvertAttempt CSize CLong
ConvertAttempt CSize CLong
ConvertAttempt CSize CULong
ConvertAttempt CSize CULong
ConvertAttempt CSize CLLong
ConvertAttempt CSize CLLong
ConvertAttempt CSize CULLong
ConvertAttempt CSize CULLong
ConvertAttempt CSize CWchar
ConvertAttempt CSize CWchar
ConvertAttempt CWchar Char
ConvertAttempt CWchar Char
ConvertAttempt CWchar Int
ConvertAttempt CWchar Int
ConvertAttempt CWchar Int8
ConvertAttempt CWchar Int8
ConvertAttempt CWchar Int16
ConvertAttempt CWchar Int16
ConvertAttempt CWchar Int32
ConvertAttempt CWchar Int32
ConvertAttempt CWchar Int64
ConvertAttempt CWchar Int64
ConvertAttempt CWchar Word
ConvertAttempt CWchar Word
ConvertAttempt CWchar Word8
ConvertAttempt CWchar Word8
ConvertAttempt CWchar Word16
ConvertAttempt CWchar Word16
ConvertAttempt CWchar Word32
ConvertAttempt CWchar Word32
ConvertAttempt CWchar Word64
ConvertAttempt CWchar Word64
ConvertAttempt CWchar CChar
ConvertAttempt CWchar CChar
ConvertAttempt CWchar CSChar
ConvertAttempt CWchar CSChar
ConvertAttempt CWchar CUChar
ConvertAttempt CWchar CUChar
ConvertAttempt CWchar CShort
ConvertAttempt CWchar CShort
ConvertAttempt CWchar CUShort
ConvertAttempt CWchar CUShort
ConvertAttempt CWchar CInt
ConvertAttempt CWchar CInt
ConvertAttempt CWchar CUInt
ConvertAttempt CWchar CUInt
ConvertAttempt CWchar CLong
ConvertAttempt CWchar CLong
ConvertAttempt CWchar CULong
ConvertAttempt CWchar CULong
ConvertAttempt CWchar CLLong
ConvertAttempt CWchar CLLong
ConvertAttempt CWchar CULLong
ConvertAttempt CWchar CULLong
ConvertAttempt CWchar CSize
ConvertAttempt CWchar CSize
ConvertAttempt CTime Double
ConvertAttempt CTime Double
ConvertAttempt CTime Int
ConvertAttempt CTime Int
ConvertAttempt CTime Integer
ConvertAttempt CTime Integer
ConvertAttempt CTime ClockTime
ConvertAttempt CTime ClockTime
ConvertAttempt CTime CalendarTime
ConvertAttempt CTime CalendarTime
ConvertAttempt CTime ZonedTime
ConvertAttempt CTime ZonedTime
ConvertAttempt CTime POSIXTime
ConvertAttempt CTime POSIXTime
ConvertAttempt CTime UTCTime
ConvertAttempt CTime UTCTime
ConvertAttempt ByteString Bool
ConvertAttempt ByteString Bool
ConvertAttempt ByteString Int
ConvertAttempt ByteString Int
ConvertAttempt ByteString Day
ConvertAttempt ByteString Day
ConvertAttempt ByteString Bool
ConvertAttempt ByteString Bool
ConvertAttempt ByteString Int
ConvertAttempt ByteString Int
ConvertAttempt ByteString Day
ConvertAttempt ByteString Day
ConvertAttempt ClockTime Integer
ConvertAttempt ClockTime Integer
ConvertAttempt ClockTime CTime
ConvertAttempt ClockTime CTime
ConvertAttempt ClockTime CalendarTime
ConvertAttempt ClockTime CalendarTime
ConvertAttempt ClockTime ZonedTime
ConvertAttempt ClockTime ZonedTime
ConvertAttempt ClockTime UTCTime
ConvertAttempt ClockTime UTCTime
ConvertAttempt CalendarTime CTime
ConvertAttempt CalendarTime CTime
ConvertAttempt CalendarTime ClockTime
ConvertAttempt CalendarTime ClockTime
ConvertAttempt CalendarTime POSIXTime
ConvertAttempt CalendarTime POSIXTime
ConvertAttempt CalendarTime UTCTime
ConvertAttempt CalendarTime UTCTime
ConvertAttempt TimeDiff Double
ConvertAttempt TimeDiff Double
ConvertAttempt TimeDiff Integer
ConvertAttempt TimeDiff Integer
ConvertAttempt TimeDiff Rational
ConvertAttempt TimeDiff Rational
ConvertAttempt Text Bool
ConvertAttempt Text Bool
ConvertAttempt Text Int
ConvertAttempt Text Int
ConvertAttempt Text Day
ConvertAttempt Text Day
ConvertAttempt Text Bool
ConvertAttempt Text Bool
ConvertAttempt Text Int
ConvertAttempt Text Int
ConvertAttempt Text Day
ConvertAttempt Text Day
ConvertAttempt ZonedTime CTime
ConvertAttempt ZonedTime CTime
ConvertAttempt ZonedTime ClockTime
ConvertAttempt ZonedTime ClockTime
ConvertAttempt ZonedTime POSIXTime
ConvertAttempt ZonedTime POSIXTime
ConvertAttempt ZonedTime UTCTime
ConvertAttempt ZonedTime UTCTime
ConvertAttempt POSIXTime Double
ConvertAttempt POSIXTime Double
ConvertAttempt POSIXTime Int
ConvertAttempt POSIXTime Int
ConvertAttempt POSIXTime Integer
ConvertAttempt POSIXTime Integer
ConvertAttempt POSIXTime Rational
ConvertAttempt POSIXTime Rational
ConvertAttempt POSIXTime CTime
ConvertAttempt POSIXTime CTime
ConvertAttempt POSIXTime CalendarTime
ConvertAttempt POSIXTime CalendarTime
ConvertAttempt POSIXTime ZonedTime
ConvertAttempt POSIXTime ZonedTime
ConvertAttempt POSIXTime UTCTime
ConvertAttempt POSIXTime UTCTime
ConvertAttempt UTCTime Double
ConvertAttempt UTCTime Double
ConvertAttempt UTCTime Int
ConvertAttempt UTCTime Int
ConvertAttempt UTCTime Integer
ConvertAttempt UTCTime Integer
ConvertAttempt UTCTime Rational
ConvertAttempt UTCTime Rational
ConvertAttempt UTCTime CTime
ConvertAttempt UTCTime CTime
ConvertAttempt UTCTime ClockTime
ConvertAttempt UTCTime ClockTime
ConvertAttempt UTCTime CalendarTime
ConvertAttempt UTCTime CalendarTime
ConvertAttempt UTCTime ZonedTime
ConvertAttempt UTCTime ZonedTime
ConvertAttempt UTCTime POSIXTime
ConvertAttempt UTCTime POSIXTime
ConvertAttempt ByteString (Ratio Integer)
ConvertAttempt ByteString (Ratio Integer)
ConvertAttempt ByteString (Ratio Integer)
ConvertAttempt ByteString (Ratio Integer)
ConvertAttempt Text (Ratio Integer)
ConvertAttempt Text (Ratio Integer)
ConvertAttempt Text (Ratio Integer)
ConvertAttempt Text (Ratio Integer)
ConvertAttempt ([] Char) Bool
ConvertAttempt ([] Char) Bool
ConvertAttempt ([] Char) Int
ConvertAttempt ([] Char) Int
ConvertAttempt ([] Char) Day
ConvertAttempt ([] Char) Day
ConvertAttempt ([] Char) (Ratio Integer)
ConvertAttempt ([] Char) (Ratio Integer)
class ConvertAttempt a b => ConvertSuccess a b whereSource
A typeclass that represents something that guarantees a successful conversion. A ConvertSuccess a b instance represents an a that can be converted to a b.
Methods
convertSuccess :: a -> bSource
Convert a to b.
show/hide Instances
ConvertSuccess Bool ByteString
ConvertSuccess Bool ByteString
ConvertSuccess Bool ByteString
ConvertSuccess Bool ByteString
ConvertSuccess Bool Text
ConvertSuccess Bool Text
ConvertSuccess Bool Text
ConvertSuccess Bool Text
ConvertSuccess Char Integer
ConvertSuccess Char Integer
ConvertSuccess Double Float
ConvertSuccess Double Float
ConvertSuccess Double Integer
ConvertSuccess Double Integer
ConvertSuccess Double Rational
ConvertSuccess Double Rational
ConvertSuccess Double CFloat
ConvertSuccess Double CFloat
ConvertSuccess Double CDouble
ConvertSuccess Double CDouble
ConvertSuccess Double CLDouble
ConvertSuccess Double CLDouble
ConvertSuccess Double CTime
ConvertSuccess Double CTime
ConvertSuccess Double TimeDiff
ConvertSuccess Double TimeDiff
ConvertSuccess Double POSIXTime
ConvertSuccess Double POSIXTime
ConvertSuccess Double UTCTime
ConvertSuccess Double UTCTime
ConvertSuccess Float Double
ConvertSuccess Float Double
ConvertSuccess Float Integer
ConvertSuccess Float Integer
ConvertSuccess Float Rational
ConvertSuccess Float Rational
ConvertSuccess Float CFloat
ConvertSuccess Float CFloat
ConvertSuccess Float CDouble
ConvertSuccess Float CDouble
ConvertSuccess Float CLDouble
ConvertSuccess Float CLDouble
ConvertSuccess Int Double
ConvertSuccess Int Double
ConvertSuccess Int Float
ConvertSuccess Int Float
ConvertSuccess Int Integer
ConvertSuccess Int Integer
ConvertSuccess Int Rational
ConvertSuccess Int Rational
ConvertSuccess Int CFloat
ConvertSuccess Int CFloat
ConvertSuccess Int CDouble
ConvertSuccess Int CDouble
ConvertSuccess Int CLDouble
ConvertSuccess Int CLDouble
ConvertSuccess Int CTime
ConvertSuccess Int CTime
ConvertSuccess Int ByteString
ConvertSuccess Int ByteString
ConvertSuccess Int ByteString
ConvertSuccess Int ByteString
ConvertSuccess Int Text
ConvertSuccess Int Text
ConvertSuccess Int Text
ConvertSuccess Int Text
ConvertSuccess Int POSIXTime
ConvertSuccess Int POSIXTime
ConvertSuccess Int UTCTime
ConvertSuccess Int UTCTime
ConvertSuccess Int8 Double
ConvertSuccess Int8 Double
ConvertSuccess Int8 Float
ConvertSuccess Int8 Float
ConvertSuccess Int8 Integer
ConvertSuccess Int8 Integer
ConvertSuccess Int8 Rational
ConvertSuccess Int8 Rational
ConvertSuccess Int8 CFloat
ConvertSuccess Int8 CFloat
ConvertSuccess Int8 CDouble
ConvertSuccess Int8 CDouble
ConvertSuccess Int8 CLDouble
ConvertSuccess Int8 CLDouble
ConvertSuccess Int16 Double
ConvertSuccess Int16 Double
ConvertSuccess Int16 Float
ConvertSuccess Int16 Float
ConvertSuccess Int16 Integer
ConvertSuccess Int16 Integer
ConvertSuccess Int16 Rational
ConvertSuccess Int16 Rational
ConvertSuccess Int16 CFloat
ConvertSuccess Int16 CFloat
ConvertSuccess Int16 CDouble
ConvertSuccess Int16 CDouble
ConvertSuccess Int16 CLDouble
ConvertSuccess Int16 CLDouble
ConvertSuccess Int32 Double
ConvertSuccess Int32 Double
ConvertSuccess Int32 Float
ConvertSuccess Int32 Float
ConvertSuccess Int32 Integer
ConvertSuccess Int32 Integer
ConvertSuccess Int32 Rational
ConvertSuccess Int32 Rational
ConvertSuccess Int32 CFloat
ConvertSuccess Int32 CFloat
ConvertSuccess Int32 CDouble
ConvertSuccess Int32 CDouble
ConvertSuccess Int32 CLDouble
ConvertSuccess Int32 CLDouble
ConvertSuccess Int64 Double
ConvertSuccess Int64 Double
ConvertSuccess Int64 Float
ConvertSuccess Int64 Float
ConvertSuccess Int64 Integer
ConvertSuccess Int64 Integer
ConvertSuccess Int64 Rational
ConvertSuccess Int64 Rational
ConvertSuccess Int64 CFloat
ConvertSuccess Int64 CFloat
ConvertSuccess Int64 CDouble
ConvertSuccess Int64 CDouble
ConvertSuccess Int64 CLDouble
ConvertSuccess Int64 CLDouble
ConvertSuccess Integer Double
ConvertSuccess Integer Double
ConvertSuccess Integer Float
ConvertSuccess Integer Float
ConvertSuccess Integer Integer
ConvertSuccess Integer Rational
ConvertSuccess Integer Rational
ConvertSuccess Integer CFloat
ConvertSuccess Integer CFloat
ConvertSuccess Integer CDouble
ConvertSuccess Integer CDouble
ConvertSuccess Integer CLDouble
ConvertSuccess Integer CLDouble
ConvertSuccess Integer CTime
ConvertSuccess Integer CTime
ConvertSuccess Integer ClockTime
ConvertSuccess Integer ClockTime
ConvertSuccess Integer TimeDiff
ConvertSuccess Integer TimeDiff
ConvertSuccess Integer POSIXTime
ConvertSuccess Integer POSIXTime
ConvertSuccess Integer UTCTime
ConvertSuccess Integer UTCTime
ConvertSuccess Rational Double
ConvertSuccess Rational Double
ConvertSuccess Rational Float
ConvertSuccess Rational Float
ConvertSuccess Rational Integer
ConvertSuccess Rational Integer
ConvertSuccess Rational CFloat
ConvertSuccess Rational CFloat
ConvertSuccess Rational CDouble
ConvertSuccess Rational CDouble
ConvertSuccess Rational CLDouble
ConvertSuccess Rational CLDouble
ConvertSuccess Rational POSIXTime
ConvertSuccess Rational POSIXTime
ConvertSuccess Rational UTCTime
ConvertSuccess Rational UTCTime
ConvertSuccess Word Double
ConvertSuccess Word Double
ConvertSuccess Word Float
ConvertSuccess Word Float
ConvertSuccess Word Integer
ConvertSuccess Word Integer
ConvertSuccess Word Rational
ConvertSuccess Word Rational
ConvertSuccess Word CFloat
ConvertSuccess Word CFloat
ConvertSuccess Word CDouble
ConvertSuccess Word CDouble
ConvertSuccess Word CLDouble
ConvertSuccess Word CLDouble
ConvertSuccess Word8 Double
ConvertSuccess Word8 Double
ConvertSuccess Word8 Float
ConvertSuccess Word8 Float
ConvertSuccess Word8 Integer
ConvertSuccess Word8 Integer
ConvertSuccess Word8 Rational
ConvertSuccess Word8 Rational
ConvertSuccess Word8 CFloat
ConvertSuccess Word8 CFloat
ConvertSuccess Word8 CDouble
ConvertSuccess Word8 CDouble
ConvertSuccess Word8 CLDouble
ConvertSuccess Word8 CLDouble
ConvertSuccess Word16 Double
ConvertSuccess Word16 Double
ConvertSuccess Word16 Float
ConvertSuccess Word16 Float
ConvertSuccess Word16 Integer
ConvertSuccess Word16 Integer
ConvertSuccess Word16 Rational
ConvertSuccess Word16 Rational
ConvertSuccess Word16 CFloat
ConvertSuccess Word16 CFloat
ConvertSuccess Word16 CDouble
ConvertSuccess Word16 CDouble
ConvertSuccess Word16 CLDouble
ConvertSuccess Word16 CLDouble
ConvertSuccess Word32 Double
ConvertSuccess Word32 Double
ConvertSuccess Word32 Float
ConvertSuccess Word32 Float
ConvertSuccess Word32 Integer
ConvertSuccess Word32 Integer
ConvertSuccess Word32 Rational
ConvertSuccess Word32 Rational
ConvertSuccess Word32 CFloat
ConvertSuccess Word32 CFloat
ConvertSuccess Word32 CDouble
ConvertSuccess Word32 CDouble
ConvertSuccess Word32 CLDouble
ConvertSuccess Word32 CLDouble
ConvertSuccess Word64 Double
ConvertSuccess Word64 Double
ConvertSuccess Word64 Float
ConvertSuccess Word64 Float
ConvertSuccess Word64 Integer
ConvertSuccess Word64 Integer
ConvertSuccess Word64 Rational
ConvertSuccess Word64 Rational
ConvertSuccess Word64 CFloat
ConvertSuccess Word64 CFloat
ConvertSuccess Word64 CDouble
ConvertSuccess Word64 CDouble
ConvertSuccess Word64 CLDouble
ConvertSuccess Word64 CLDouble
ConvertSuccess CChar Integer
ConvertSuccess CChar Integer
ConvertSuccess CSChar Integer
ConvertSuccess CSChar Integer
ConvertSuccess CUChar Integer
ConvertSuccess CUChar Integer
ConvertSuccess CShort Integer
ConvertSuccess CShort Integer
ConvertSuccess CUShort Integer
ConvertSuccess CUShort Integer
ConvertSuccess CInt Integer
ConvertSuccess CInt Integer
ConvertSuccess CUInt Integer
ConvertSuccess CUInt Integer
ConvertSuccess CLong Integer
ConvertSuccess CLong Integer
ConvertSuccess CULong Integer
ConvertSuccess CULong Integer
ConvertSuccess CLLong Integer
ConvertSuccess CLLong Integer
ConvertSuccess CULLong Integer
ConvertSuccess CULLong Integer
ConvertSuccess CFloat Double
ConvertSuccess CFloat Double
ConvertSuccess CFloat Float
ConvertSuccess CFloat Float
ConvertSuccess CFloat Integer
ConvertSuccess CFloat Integer
ConvertSuccess CFloat Rational
ConvertSuccess CFloat Rational
ConvertSuccess CFloat CDouble
ConvertSuccess CFloat CDouble
ConvertSuccess CFloat CLDouble
ConvertSuccess CFloat CLDouble
ConvertSuccess CDouble Double
ConvertSuccess CDouble Double
ConvertSuccess CDouble Float
ConvertSuccess CDouble Float
ConvertSuccess CDouble Integer
ConvertSuccess CDouble Integer
ConvertSuccess CDouble Rational
ConvertSuccess CDouble Rational
ConvertSuccess CDouble CFloat
ConvertSuccess CDouble CFloat
ConvertSuccess CDouble CLDouble
ConvertSuccess CDouble CLDouble
ConvertSuccess CLDouble Double
ConvertSuccess CLDouble Double
ConvertSuccess CLDouble Float
ConvertSuccess CLDouble Float
ConvertSuccess CLDouble Integer
ConvertSuccess CLDouble Integer
ConvertSuccess CLDouble Rational
ConvertSuccess CLDouble Rational
ConvertSuccess CLDouble CFloat
ConvertSuccess CLDouble CFloat
ConvertSuccess CLDouble CDouble
ConvertSuccess CLDouble CDouble
ConvertSuccess CSize Integer
ConvertSuccess CSize Integer
ConvertSuccess CWchar Integer
ConvertSuccess CWchar Integer
ConvertSuccess CTime Double
ConvertSuccess CTime Double
ConvertSuccess CTime Integer
ConvertSuccess CTime Integer
ConvertSuccess CTime ClockTime
ConvertSuccess CTime ClockTime
ConvertSuccess CTime CalendarTime
ConvertSuccess CTime CalendarTime
ConvertSuccess CTime ZonedTime
ConvertSuccess CTime ZonedTime
ConvertSuccess CTime POSIXTime
ConvertSuccess CTime POSIXTime
ConvertSuccess CTime UTCTime
ConvertSuccess CTime UTCTime
ConvertSuccess ByteString ByteString
ConvertSuccess ByteString ByteString
ConvertSuccess ByteString ByteString
ConvertSuccess ByteString Text
ConvertSuccess ByteString Text
ConvertSuccess ByteString Text
ConvertSuccess ByteString Text
ConvertSuccess ByteString ByteString
ConvertSuccess ByteString ByteString
ConvertSuccess ByteString ByteString
ConvertSuccess ByteString Text
ConvertSuccess ByteString Text
ConvertSuccess ByteString Text
ConvertSuccess ByteString Text
ConvertSuccess ClockTime Integer
ConvertSuccess ClockTime Integer
ConvertSuccess ClockTime CTime
ConvertSuccess ClockTime CTime
ConvertSuccess ClockTime CalendarTime
ConvertSuccess ClockTime CalendarTime
ConvertSuccess ClockTime ZonedTime
ConvertSuccess ClockTime ZonedTime
ConvertSuccess ClockTime POSIXTime
ConvertSuccess ClockTime POSIXTime
ConvertSuccess ClockTime UTCTime
ConvertSuccess ClockTime UTCTime
ConvertSuccess CalendarTime CTime
ConvertSuccess CalendarTime CTime
ConvertSuccess CalendarTime ClockTime
ConvertSuccess CalendarTime ClockTime
ConvertSuccess CalendarTime ZonedTime
ConvertSuccess CalendarTime ZonedTime
ConvertSuccess CalendarTime POSIXTime
ConvertSuccess CalendarTime POSIXTime
ConvertSuccess CalendarTime UTCTime
ConvertSuccess CalendarTime UTCTime
ConvertSuccess TimeDiff Double
ConvertSuccess TimeDiff Double
ConvertSuccess TimeDiff Integer
ConvertSuccess TimeDiff Integer
ConvertSuccess TimeDiff Rational
ConvertSuccess TimeDiff Rational
ConvertSuccess TimeDiff NominalDiffTime
ConvertSuccess TimeDiff NominalDiffTime
ConvertSuccess Text ByteString
ConvertSuccess Text ByteString
ConvertSuccess Text ByteString
ConvertSuccess Text ByteString
ConvertSuccess Text Text
ConvertSuccess Text Text
ConvertSuccess Text Text
ConvertSuccess Text ByteString
ConvertSuccess Text ByteString
ConvertSuccess Text ByteString
ConvertSuccess Text ByteString
ConvertSuccess Text Text
ConvertSuccess Text Text
ConvertSuccess Text Text
ConvertSuccess ZonedTime CTime
ConvertSuccess ZonedTime CTime
ConvertSuccess ZonedTime ClockTime
ConvertSuccess ZonedTime ClockTime
ConvertSuccess ZonedTime CalendarTime
ConvertSuccess ZonedTime CalendarTime
ConvertSuccess ZonedTime POSIXTime
ConvertSuccess ZonedTime POSIXTime
ConvertSuccess ZonedTime UTCTime
ConvertSuccess ZonedTime UTCTime
ConvertSuccess POSIXTime Double
ConvertSuccess POSIXTime Double
ConvertSuccess POSIXTime Integer
ConvertSuccess POSIXTime Integer
ConvertSuccess POSIXTime Rational
ConvertSuccess POSIXTime Rational
ConvertSuccess POSIXTime CTime
ConvertSuccess POSIXTime CTime
ConvertSuccess POSIXTime ClockTime
ConvertSuccess POSIXTime ClockTime
ConvertSuccess POSIXTime CalendarTime
ConvertSuccess POSIXTime CalendarTime
ConvertSuccess POSIXTime ZonedTime
ConvertSuccess POSIXTime ZonedTime
ConvertSuccess POSIXTime UTCTime
ConvertSuccess POSIXTime UTCTime
ConvertSuccess UTCTime Double
ConvertSuccess UTCTime Double
ConvertSuccess UTCTime Integer
ConvertSuccess UTCTime Integer
ConvertSuccess UTCTime Rational
ConvertSuccess UTCTime Rational
ConvertSuccess UTCTime CTime
ConvertSuccess UTCTime CTime
ConvertSuccess UTCTime ClockTime
ConvertSuccess UTCTime ClockTime
ConvertSuccess UTCTime CalendarTime
ConvertSuccess UTCTime CalendarTime
ConvertSuccess UTCTime ZonedTime
ConvertSuccess UTCTime ZonedTime
ConvertSuccess UTCTime POSIXTime
ConvertSuccess UTCTime POSIXTime
ConvertSuccess NominalDiffTime TimeDiff
ConvertSuccess NominalDiffTime TimeDiff
ConvertSuccess Day ByteString
ConvertSuccess Day ByteString
ConvertSuccess Day ByteString
ConvertSuccess Day ByteString
ConvertSuccess Day Text
ConvertSuccess Day Text
ConvertSuccess Day Text
ConvertSuccess Day Text
ConvertSuccess Bool ([] Char)
ConvertSuccess Bool ([] Char)
ConvertSuccess Int ([] Char)
ConvertSuccess Int ([] Char)
ConvertSuccess ByteString ([] Char)
ConvertSuccess ByteString ([] Char)
ConvertSuccess ByteString ([] Char)
ConvertSuccess ByteString ([] Char)
ConvertSuccess Text ([] Char)
ConvertSuccess Text ([] Char)
ConvertSuccess Text ([] Char)
ConvertSuccess Text ([] Char)
ConvertSuccess Day ([] Char)
ConvertSuccess Day ([] Char)
ConvertSuccess ([] Char) ByteString
ConvertSuccess ([] Char) ByteString
ConvertSuccess ([] Char) ByteString
ConvertSuccess ([] Char) ByteString
ConvertSuccess ([] Char) Text
ConvertSuccess ([] Char) Text
ConvertSuccess ([] Char) Text
ConvertSuccess ([] Char) Text
ConvertSuccess (Ratio Integer) ByteString
ConvertSuccess (Ratio Integer) ByteString
ConvertSuccess (Ratio Integer) ByteString
ConvertSuccess (Ratio Integer) ByteString
ConvertSuccess (Ratio Integer) Text
ConvertSuccess (Ratio Integer) Text
ConvertSuccess (Ratio Integer) Text
ConvertSuccess (Ratio Integer) Text
ConvertSuccess ([] Char) ([] Char)
ConvertSuccess (Ratio Integer) ([] Char)
ConvertSuccess (Ratio Integer) ([] Char)
Ord k => ConvertSuccess ([] ((,) k a)) (Map k a)
Ord k => ConvertSuccess ([] ((,) k a)) (Map k a)
ConvertSuccess (Map k a) ([] ((,) k a))
ConvertSuccess (Map k a) ([] ((,) k a))
data ConversionException Source
Wraps any Exception which could occur during a convertAttempt.
Constructors
forall e . Exception e => ConversionException e
show/hide Instances
convertUnsafe :: ConvertAttempt a b => a -> bSource
Convert from one type of data to another. Raises an exception if there is an error with the conversion. For a function that does not raise an exception in that case, see convertAttempt.
convertAttemptWrap :: (ConvertAttempt a b, MonadFailure ConversionException m) => a -> m bSource
Calls convertAttempt, wrapping any Exceptions in a ConversionException
Produced by Haddock version 2.4.2