Safe Haskell | None |
---|---|
Language | GHC2021 |
GHC.Utils.Exception
Documentation
allowInterrupt :: IO () #
mapException :: (Exception e1, Exception e2) => (e1 -> e2) -> a -> a #
onException :: IO a -> IO b -> IO a #
tryWithContext :: Exception e => IO a -> IO (Either (ExceptionWithContext e) a) #
throw :: forall a e. (HasCallStack, Exception e) => e -> a #
addExceptionContext :: ExceptionAnnotation a => a -> SomeException -> SomeException #
annotateIO :: ExceptionAnnotation e => e -> IO a -> IO a #
catchNoPropagate :: Exception e => IO a -> (ExceptionWithContext e -> IO a) -> IO a #
interruptible :: IO a -> IO a #
rethrowIO :: Exception e => ExceptionWithContext e -> IO a #
throwIO :: (HasCallStack, Exception e) => e -> IO a #
uninterruptibleMask_ :: IO a -> IO a #
asyncExceptionFromException :: Exception e => SomeException -> Maybe e #
asyncExceptionToException :: Exception e => e -> SomeException #
ioError :: HasCallStack => IOError -> IO a #
data NestedAtomically #
Constructors
NestedAtomically |
Instances
Exception NestedAtomically # | |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: NestedAtomically -> SomeException # fromException :: SomeException -> Maybe NestedAtomically # | |
Show NestedAtomically # | |
Defined in GHC.Internal.Control.Exception.Base Methods showsPrec :: Int -> NestedAtomically -> ShowS # show :: NestedAtomically -> String # showList :: [NestedAtomically] -> ShowS # |
newtype NoMethodError #
Constructors
NoMethodError String |
Instances
Exception NoMethodError # | |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: NoMethodError -> SomeException # fromException :: SomeException -> Maybe NoMethodError # displayException :: NoMethodError -> String # backtraceDesired :: NoMethodError -> Bool # | |
Show NoMethodError # | |
Defined in GHC.Internal.Control.Exception.Base Methods showsPrec :: Int -> NoMethodError -> ShowS # show :: NoMethodError -> String # showList :: [NoMethodError] -> ShowS # |
data NonTermination #
Constructors
NonTermination |
Instances
Exception NonTermination # | |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: NonTermination -> SomeException # fromException :: SomeException -> Maybe NonTermination # displayException :: NonTermination -> String # backtraceDesired :: NonTermination -> Bool # | |
Show NonTermination # | |
Defined in GHC.Internal.Control.Exception.Base Methods showsPrec :: Int -> NonTermination -> ShowS # show :: NonTermination -> String # showList :: [NonTermination] -> ShowS # |
newtype PatternMatchFail #
Constructors
PatternMatchFail String |
Instances
Exception PatternMatchFail # | |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: PatternMatchFail -> SomeException # fromException :: SomeException -> Maybe PatternMatchFail # | |
Show PatternMatchFail # | |
Defined in GHC.Internal.Control.Exception.Base Methods showsPrec :: Int -> PatternMatchFail -> ShowS # show :: PatternMatchFail -> String # showList :: [PatternMatchFail] -> ShowS # |
newtype RecConError #
Constructors
RecConError String |
Instances
Exception RecConError # | |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: RecConError -> SomeException # fromException :: SomeException -> Maybe RecConError # displayException :: RecConError -> String # backtraceDesired :: RecConError -> Bool # | |
Show RecConError # | |
Defined in GHC.Internal.Control.Exception.Base Methods showsPrec :: Int -> RecConError -> ShowS # show :: RecConError -> String # showList :: [RecConError] -> ShowS # |
newtype RecSelError #
Constructors
RecSelError String |
Instances
Exception RecSelError # | |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: RecSelError -> SomeException # fromException :: SomeException -> Maybe RecSelError # displayException :: RecSelError -> String # backtraceDesired :: RecSelError -> Bool # | |
Show RecSelError # | |
Defined in GHC.Internal.Control.Exception.Base Methods showsPrec :: Int -> RecSelError -> ShowS # show :: RecSelError -> String # showList :: [RecSelError] -> ShowS # |
newtype RecUpdError #
Constructors
RecUpdError String |
Instances
Exception RecUpdError # | |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: RecUpdError -> SomeException # fromException :: SomeException -> Maybe RecUpdError # displayException :: RecUpdError -> String # backtraceDesired :: RecUpdError -> Bool # | |
Show RecUpdError # | |
Defined in GHC.Internal.Control.Exception.Base Methods showsPrec :: Int -> RecUpdError -> ShowS # show :: RecUpdError -> String # showList :: [RecUpdError] -> ShowS # |
Instances
Exception TypeError # | |
Defined in GHC.Internal.Control.Exception.Base Methods toException :: TypeError -> SomeException # fromException :: SomeException -> Maybe TypeError # displayException :: TypeError -> String # backtraceDesired :: TypeError -> Bool # | |
Show TypeError # | |
Bundled Patterns
pattern ErrorCallWithLocation :: String -> String -> ErrorCall |
Instances
Eq ErrorCall # | |
Ord ErrorCall # | |
Exception ErrorCall # | |
Defined in GHC.Internal.Exception Methods toException :: ErrorCall -> SomeException # fromException :: SomeException -> Maybe ErrorCall # displayException :: ErrorCall -> String # backtraceDesired :: ErrorCall -> Bool # | |
Show ErrorCall # | |
data ArithException #
Instances
class (Typeable e, Show e) => Exception e where #
Minimal complete definition
Nothing
Methods
toException :: e -> SomeException #
fromException :: SomeException -> Maybe e #
displayException :: e -> String #
backtraceDesired :: e -> Bool #
Instances
data ExceptionWithContext a #
Constructors
ExceptionWithContext ExceptionContext a |
Instances
Exception a => Exception (ExceptionWithContext a) # | |
Defined in GHC.Internal.Exception.Type Methods toException :: ExceptionWithContext a -> SomeException # fromException :: SomeException -> Maybe (ExceptionWithContext a) # displayException :: ExceptionWithContext a -> String # backtraceDesired :: ExceptionWithContext a -> Bool # | |
Show a => Show (ExceptionWithContext a) # | |
Defined in GHC.Internal.Exception.Type Methods showsPrec :: Int -> ExceptionWithContext a -> ShowS # show :: ExceptionWithContext a -> String # showList :: [ExceptionWithContext a] -> ShowS # |
newtype NoBacktrace e #
Constructors
NoBacktrace e |
Instances
Exception e => Exception (NoBacktrace e) # | |
Defined in GHC.Internal.Exception.Type Methods toException :: NoBacktrace e -> SomeException # fromException :: SomeException -> Maybe (NoBacktrace e) # displayException :: NoBacktrace e -> String # backtraceDesired :: NoBacktrace e -> Bool # | |
Show e => Show (NoBacktrace e) # | |
Defined in GHC.Internal.Exception.Type Methods showsPrec :: Int -> NoBacktrace e -> ShowS # show :: NoBacktrace e -> String # showList :: [NoBacktrace e] -> ShowS # |
data SomeException #
Constructors
(Exception e, HasExceptionContext) => SomeException e |
Instances
Exception SomeException # | |
Defined in GHC.Internal.Exception.Type Methods toException :: SomeException -> SomeException # fromException :: SomeException -> Maybe SomeException # displayException :: SomeException -> String # backtraceDesired :: SomeException -> Bool # | |
Show SomeException # | |
Defined in GHC.Internal.Exception.Type Methods showsPrec :: Int -> SomeException -> ShowS # show :: SomeException -> String # showList :: [SomeException] -> ShowS # |
data WhileHandling #
Constructors
WhileHandling SomeException |
Instances
ExceptionAnnotation WhileHandling # | |
Defined in GHC.Internal.Exception.Type Methods | |
Show WhileHandling # | |
Defined in GHC.Internal.Exception.Type Methods showsPrec :: Int -> WhileHandling -> ShowS # show :: WhileHandling -> String # showList :: [WhileHandling] -> ShowS # |
data MaskingState #
Constructors
Unmasked | |
MaskedInterruptible | |
MaskedUninterruptible |
Instances
NFData MaskingState Source # | Since: deepseq-1.4.4.0 |
Defined in Control.DeepSeq Methods rnf :: MaskingState -> () Source # | |
Eq MaskingState # | |
Defined in GHC.Internal.IO | |
Show MaskingState # | |
Defined in GHC.Internal.IO Methods showsPrec :: Int -> MaskingState -> ShowS # show :: MaskingState -> String # showList :: [MaskingState] -> ShowS # |
data AllocationLimitExceeded #
Constructors
AllocationLimitExceeded |
Instances
Exception AllocationLimitExceeded # | |
Defined in GHC.Internal.IO.Exception | |
Show AllocationLimitExceeded # | |
Defined in GHC.Internal.IO.Exception Methods showsPrec :: Int -> AllocationLimitExceeded -> ShowS # show :: AllocationLimitExceeded -> String # showList :: [AllocationLimitExceeded] -> ShowS # |
data ArrayException #
Constructors
IndexOutOfBounds String | |
UndefinedElement String |
Instances
newtype AssertionFailed #
Constructors
AssertionFailed String |
Instances
Exception AssertionFailed # | |
Defined in GHC.Internal.IO.Exception Methods toException :: AssertionFailed -> SomeException # fromException :: SomeException -> Maybe AssertionFailed # displayException :: AssertionFailed -> String # backtraceDesired :: AssertionFailed -> Bool # | |
Show AssertionFailed # | |
Defined in GHC.Internal.IO.Exception Methods showsPrec :: Int -> AssertionFailed -> ShowS # show :: AssertionFailed -> String # showList :: [AssertionFailed] -> ShowS # |
data AsyncException #
Constructors
StackOverflow | |
HeapOverflow | |
ThreadKilled | |
UserInterrupt |
Instances
data BlockedIndefinitelyOnMVar #
Constructors
BlockedIndefinitelyOnMVar |
Instances
Exception BlockedIndefinitelyOnMVar # | |
Show BlockedIndefinitelyOnMVar # | |
Defined in GHC.Internal.IO.Exception Methods showsPrec :: Int -> BlockedIndefinitelyOnMVar -> ShowS # show :: BlockedIndefinitelyOnMVar -> String # showList :: [BlockedIndefinitelyOnMVar] -> ShowS # |
data BlockedIndefinitelyOnSTM #
Constructors
BlockedIndefinitelyOnSTM |
Instances
Exception BlockedIndefinitelyOnSTM # | |
Defined in GHC.Internal.IO.Exception | |
Show BlockedIndefinitelyOnSTM # | |
Defined in GHC.Internal.IO.Exception Methods showsPrec :: Int -> BlockedIndefinitelyOnSTM -> ShowS # show :: BlockedIndefinitelyOnSTM -> String # showList :: [BlockedIndefinitelyOnSTM] -> ShowS # |
newtype CompactionFailed #
Constructors
CompactionFailed String |
Instances
Exception CompactionFailed # | |
Defined in GHC.Internal.IO.Exception Methods toException :: CompactionFailed -> SomeException # fromException :: SomeException -> Maybe CompactionFailed # | |
Show CompactionFailed # | |
Defined in GHC.Internal.IO.Exception Methods showsPrec :: Int -> CompactionFailed -> ShowS # show :: CompactionFailed -> String # showList :: [CompactionFailed] -> ShowS # |
Constructors
Deadlock |
Instances
Exception Deadlock # | |
Defined in GHC.Internal.IO.Exception Methods toException :: Deadlock -> SomeException # fromException :: SomeException -> Maybe Deadlock # displayException :: Deadlock -> String # backtraceDesired :: Deadlock -> Bool # | |
Show Deadlock # | |
data IOException #
Instances
Eq IOException # | |
Defined in GHC.Internal.IO.Exception | |
Exception IOException # | |
Defined in GHC.Internal.IO.Exception Methods toException :: IOException -> SomeException # fromException :: SomeException -> Maybe IOException # displayException :: IOException -> String # backtraceDesired :: IOException -> Bool # | |
Show IOException # | |
Defined in GHC.Internal.IO.Exception Methods showsPrec :: Int -> IOException -> ShowS # show :: IOException -> String # showList :: [IOException] -> ShowS # |
data SomeAsyncException #
Constructors
Exception e => SomeAsyncException e |
Instances
Exception SomeAsyncException # | |
Defined in GHC.Internal.IO.Exception Methods toException :: SomeAsyncException -> SomeException # fromException :: SomeException -> Maybe SomeAsyncException # | |
Show SomeAsyncException # | |
Defined in GHC.Internal.IO.Exception Methods showsPrec :: Int -> SomeAsyncException -> ShowS # show :: SomeAsyncException -> String # showList :: [SomeAsyncException] -> ShowS # |
type ExceptionMonad (m :: Type -> Type) = (MonadCatch m, MonadThrow m, MonadMask m, MonadIO m) Source #