module TextShow.Control.Exception (
showbSomeExceptionPrec
, showbIOException
, showbArithException
, showbArrayException
, showbAssertionFailed
#if MIN_VERSION_base(4,7,0)
, showbSomeAsyncException
#endif
, showbAsyncException
, showbNonTermination
, showbNestedAtomically
, showbBlockedIndefinitelyOnMVar
, showbBlockedIndefinitelyOnSTM
#if MIN_VERSION_base(4,8,0)
, showbAllocationLimitExceeded
#endif
#if MIN_VERSION_base(4,9,0)
, showbTypeError
#endif
, showbDeadlock
, showbNoMethodError
, showbPatternMatchFail
, showbRecConError
, showbRecSelError
, showbRecUpdError
, showbErrorCall
, showbMaskingState
) where
import Control.Exception.Base
import Data.Monoid.Compat ((<>))
import Data.Text.Lazy.Builder (Builder, fromString)
#if MIN_VERSION_base(4,9,0)
import Data.Text.Lazy.Builder (singleton)
#endif
import Prelude ()
import Prelude.Compat
import TextShow.Classes (TextShow(..))
import TextShow.FromStringTextShow (FromStringShow(..))
import TextShow.TH.Internal (deriveTextShow)
#include "inline.h"
showbSomeExceptionPrec :: Int -> SomeException -> Builder
showbSomeExceptionPrec p (SomeException e) = showbPrec p $ FromStringShow e
showbIOException :: IOException -> Builder
showbIOException = showb . FromStringShow
showbArithException :: ArithException -> Builder
showbArithException Overflow = "arithmetic overflow"
showbArithException Underflow = "arithmetic underflow"
showbArithException LossOfPrecision = "loss of precision"
showbArithException DivideByZero = "divide by zero"
showbArithException Denormal = "denormal"
#if MIN_VERSION_base(4,6,0)
showbArithException RatioZeroDenominator = "Ratio has zero denominator"
#endif
showbArrayException :: ArrayException -> Builder
showbArrayException (IndexOutOfBounds s)
= "array index out of range"
<> (if not $ null s then ": " <> fromString s
else mempty)
showbArrayException (UndefinedElement s)
= "undefined array element"
<> (if not $ null s then ": " <> fromString s
else mempty)
showbAssertionFailed :: AssertionFailed -> Builder
showbAssertionFailed (AssertionFailed err) = fromString err
#if MIN_VERSION_base(4,7,0)
showbSomeAsyncException :: SomeAsyncException -> Builder
showbSomeAsyncException (SomeAsyncException e) = showb $ FromStringShow e
#endif
showbAsyncException :: AsyncException -> Builder
showbAsyncException StackOverflow = "stack overflow"
showbAsyncException HeapOverflow = "heap overflow"
showbAsyncException ThreadKilled = "thread killed"
showbAsyncException UserInterrupt = "user interrupt"
showbNonTermination :: NonTermination -> Builder
showbNonTermination NonTermination = "<<loop>>"
showbNestedAtomically :: NestedAtomically -> Builder
showbNestedAtomically NestedAtomically = "Control.Concurrent.STM.atomically was nested"
showbBlockedIndefinitelyOnMVar :: BlockedIndefinitelyOnMVar -> Builder
showbBlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar = "thread blocked indefinitely in an MVar operation"
showbBlockedIndefinitelyOnSTM :: BlockedIndefinitelyOnSTM -> Builder
showbBlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM = "thread blocked indefinitely in an STM transaction"
#if MIN_VERSION_base(4,8,0)
showbAllocationLimitExceeded :: AllocationLimitExceeded -> Builder
showbAllocationLimitExceeded AllocationLimitExceeded = "allocation limit exceeded"
#endif
#if MIN_VERSION_base(4,9,0)
showbTypeError :: TypeError -> Builder
showbTypeError (TypeError err) = fromString err
#endif
showbDeadlock :: Deadlock -> Builder
showbDeadlock Deadlock = "<<deadlock>>"
showbNoMethodError :: NoMethodError -> Builder
showbNoMethodError (NoMethodError err) = fromString err
showbPatternMatchFail :: PatternMatchFail -> Builder
showbPatternMatchFail (PatternMatchFail err) = fromString err
showbRecConError :: RecConError -> Builder
showbRecConError (RecConError err) = fromString err
showbRecSelError :: RecSelError -> Builder
showbRecSelError (RecSelError err) = fromString err
showbRecUpdError :: RecUpdError -> Builder
showbRecUpdError (RecUpdError err) = fromString err
showbErrorCall :: ErrorCall -> Builder
#if MIN_VERSION_base(4,9,0)
showbErrorCall (ErrorCallWithLocation err "") = fromString err
showbErrorCall (ErrorCallWithLocation err loc) =
fromString err <> singleton '\n' <> fromString loc
#else
showbErrorCall (ErrorCall err) = fromString err
#endif
showbMaskingState :: MaskingState -> Builder
showbMaskingState = showb
instance TextShow SomeException where
showbPrec = showbSomeExceptionPrec
INLINE_INST_FUN(showbPrec)
instance TextShow IOException where
showb = showbIOException
INLINE_INST_FUN(showb)
instance TextShow ArithException where
showb = showbArithException
INLINE_INST_FUN(showb)
instance TextShow ArrayException where
showb = showbArrayException
INLINE_INST_FUN(showb)
instance TextShow AssertionFailed where
showb = showbAssertionFailed
INLINE_INST_FUN(showb)
#if MIN_VERSION_base(4,7,0)
instance TextShow SomeAsyncException where
showb = showbSomeAsyncException
#endif
instance TextShow AsyncException where
showb = showbAsyncException
INLINE_INST_FUN(showb)
instance TextShow NonTermination where
showb = showbNonTermination
INLINE_INST_FUN(showb)
instance TextShow NestedAtomically where
showb = showbNestedAtomically
INLINE_INST_FUN(showb)
instance TextShow BlockedIndefinitelyOnMVar where
showb = showbBlockedIndefinitelyOnMVar
INLINE_INST_FUN(showb)
instance TextShow BlockedIndefinitelyOnSTM where
showb = showbBlockedIndefinitelyOnSTM
INLINE_INST_FUN(showb)
#if MIN_VERSION_base(4,8,0)
instance TextShow AllocationLimitExceeded where
showb = showbAllocationLimitExceeded
#endif
#if MIN_VERSION_base(4,9,0)
instance TextShow TypeError where
showb = showbTypeError
#endif
instance TextShow Deadlock where
showb = showbDeadlock
INLINE_INST_FUN(showb)
instance TextShow NoMethodError where
showb = showbNoMethodError
INLINE_INST_FUN(showb)
instance TextShow PatternMatchFail where
showb = showbPatternMatchFail
INLINE_INST_FUN(showb)
instance TextShow RecConError where
showb = showbRecConError
INLINE_INST_FUN(showb)
instance TextShow RecSelError where
showb = showbRecSelError
INLINE_INST_FUN(showb)
instance TextShow RecUpdError where
showb = showbRecUpdError
INLINE_INST_FUN(showb)
instance TextShow ErrorCall where
showb = showbErrorCall
INLINE_INST_FUN(showb)
$(deriveTextShow ''MaskingState)