Safe Haskell | None |
---|---|
Language | GHC2021 |
Documentation
data BlockedIndefinitelyOnMVar #
Instances
Instances
Exception TypeError | |
Defined in GHC.Internal.Control.Exception.Base toException :: TypeError -> SomeException # fromException :: SomeException -> Maybe TypeError # displayException :: TypeError -> String # backtraceDesired :: TypeError -> Bool # | |
Show TypeError | |
data SomeException #
(Exception e, HasExceptionContext) => SomeException e |
Instances
Exception SomeException | |
Defined in GHC.Internal.Exception.Type | |
Show SomeException | |
Defined in GHC.Internal.Exception.Type showsPrec :: Int -> SomeException -> ShowS # show :: SomeException -> String # showList :: [SomeException] -> ShowS # |
data ArithException #
Instances
Exception ArithException | |
Defined in GHC.Internal.Exception.Type | |
Show ArithException | |
Defined in GHC.Internal.Exception.Type showsPrec :: Int -> ArithException -> ShowS # show :: ArithException -> String # showList :: [ArithException] -> ShowS # | |
Eq ArithException | |
Defined in GHC.Internal.Exception.Type (==) :: ArithException -> ArithException -> Bool # (/=) :: ArithException -> ArithException -> Bool # | |
Ord ArithException | |
Defined in GHC.Internal.Exception.Type compare :: ArithException -> ArithException -> Ordering # (<) :: ArithException -> ArithException -> Bool # (<=) :: ArithException -> ArithException -> Bool # (>) :: ArithException -> ArithException -> Bool # (>=) :: ArithException -> ArithException -> Bool # max :: ArithException -> ArithException -> ArithException # min :: ArithException -> ArithException -> ArithException # |
data ExceptionWithContext a #
Instances
Exception a => Exception (ExceptionWithContext a) | |
Defined in GHC.Internal.Exception.Type 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 showsPrec :: Int -> ExceptionWithContext a -> ShowS # show :: ExceptionWithContext a -> String # showList :: [ExceptionWithContext a] -> ShowS # |
class (Typeable e, Show e) => Exception e where #
Nothing
toException :: e -> SomeException #
fromException :: SomeException -> Maybe e #
displayException :: e -> String #
backtraceDesired :: e -> Bool #
Instances
addExceptionContext :: ExceptionAnnotation a => a -> SomeException -> SomeException #
Instances
Exception ErrorCall | |
Defined in GHC.Internal.Exception toException :: ErrorCall -> SomeException # fromException :: SomeException -> Maybe ErrorCall # displayException :: ErrorCall -> String # backtraceDesired :: ErrorCall -> Bool # | |
Show ErrorCall | |
Eq ErrorCall | |
Ord ErrorCall | |
Defined in GHC.Internal.Exception |
data IOException #
Instances
Exception IOException | |
Defined in GHC.Internal.IO.Exception toException :: IOException -> SomeException # fromException :: SomeException -> Maybe IOException # displayException :: IOException -> String # backtraceDesired :: IOException -> Bool # | |
Show IOException | |
Defined in GHC.Internal.IO.Exception showsPrec :: Int -> IOException -> ShowS # show :: IOException -> String # showList :: [IOException] -> ShowS # | |
Eq IOException | |
Defined in GHC.Internal.IO.Exception (==) :: IOException -> IOException -> Bool # (/=) :: IOException -> IOException -> Bool # |
data MaskingState #
Instances
NFData MaskingState | Since: deepseq-1.4.4.0 |
Defined in Control.DeepSeq rnf :: MaskingState -> () Source # | |
Show MaskingState | |
Defined in GHC.Internal.IO showsPrec :: Int -> MaskingState -> ShowS # show :: MaskingState -> String # showList :: [MaskingState] -> ShowS # | |
Eq MaskingState | |
Defined in GHC.Internal.IO (==) :: MaskingState -> MaskingState -> Bool # (/=) :: MaskingState -> MaskingState -> Bool # |
annotateIO :: ExceptionAnnotation e => e -> IO a -> IO a #
throwIO :: (HasCallStack, Exception e) => e -> IO a #
interruptible :: IO a -> IO a #
onException :: IO a -> IO b -> IO a #
uninterruptibleMask_ :: IO a -> IO a #
data ArrayException #
Instances
Exception ArrayException | |
Defined in GHC.Internal.IO.Exception | |
Show ArrayException | |
Defined in GHC.Internal.IO.Exception showsPrec :: Int -> ArrayException -> ShowS # show :: ArrayException -> String # showList :: [ArrayException] -> ShowS # | |
Eq ArrayException | |
Defined in GHC.Internal.IO.Exception (==) :: ArrayException -> ArrayException -> Bool # (/=) :: ArrayException -> ArrayException -> Bool # | |
Ord ArrayException | |
Defined in GHC.Internal.IO.Exception compare :: ArrayException -> ArrayException -> Ordering # (<) :: ArrayException -> ArrayException -> Bool # (<=) :: ArrayException -> ArrayException -> Bool # (>) :: ArrayException -> ArrayException -> Bool # (>=) :: ArrayException -> ArrayException -> Bool # max :: ArrayException -> ArrayException -> ArrayException # min :: ArrayException -> ArrayException -> ArrayException # |
data AsyncException #
Instances
Exception AsyncException | |
Defined in GHC.Internal.IO.Exception | |
Show AsyncException | |
Defined in GHC.Internal.IO.Exception showsPrec :: Int -> AsyncException -> ShowS # show :: AsyncException -> String # showList :: [AsyncException] -> ShowS # | |
Eq AsyncException | |
Defined in GHC.Internal.IO.Exception (==) :: AsyncException -> AsyncException -> Bool # (/=) :: AsyncException -> AsyncException -> Bool # | |
Ord AsyncException | |
Defined in GHC.Internal.IO.Exception compare :: AsyncException -> AsyncException -> Ordering # (<) :: AsyncException -> AsyncException -> Bool # (<=) :: AsyncException -> AsyncException -> Bool # (>) :: AsyncException -> AsyncException -> Bool # (>=) :: AsyncException -> AsyncException -> Bool # max :: AsyncException -> AsyncException -> AsyncException # min :: AsyncException -> AsyncException -> AsyncException # |
data SomeAsyncException #
Exception e => SomeAsyncException e |
Instances
Exception SomeAsyncException | |
Show SomeAsyncException | |
Defined in GHC.Internal.IO.Exception showsPrec :: Int -> SomeAsyncException -> ShowS # show :: SomeAsyncException -> String # showList :: [SomeAsyncException] -> ShowS # |
newtype AssertionFailed #
Instances
Exception AssertionFailed | |
Defined in GHC.Internal.IO.Exception | |
Show AssertionFailed | |
Defined in GHC.Internal.IO.Exception showsPrec :: Int -> AssertionFailed -> ShowS # show :: AssertionFailed -> String # showList :: [AssertionFailed] -> ShowS # |
newtype CompactionFailed #
Instances
Exception CompactionFailed | |
Defined in GHC.Internal.IO.Exception | |
Show CompactionFailed | |
Defined in GHC.Internal.IO.Exception showsPrec :: Int -> CompactionFailed -> ShowS # show :: CompactionFailed -> String # showList :: [CompactionFailed] -> ShowS # |
data AllocationLimitExceeded #
Instances
Exception AllocationLimitExceeded | |
Show AllocationLimitExceeded | |
Defined in GHC.Internal.IO.Exception showsPrec :: Int -> AllocationLimitExceeded -> ShowS # show :: AllocationLimitExceeded -> String # showList :: [AllocationLimitExceeded] -> ShowS # |
Instances
Exception Deadlock | |
Defined in GHC.Internal.IO.Exception toException :: Deadlock -> SomeException # fromException :: SomeException -> Maybe Deadlock # displayException :: Deadlock -> String # backtraceDesired :: Deadlock -> Bool # | |
Show Deadlock | |
data BlockedIndefinitelyOnSTM #
Instances
asyncExceptionToException :: Exception e => e -> SomeException #
asyncExceptionFromException :: Exception e => SomeException -> Maybe e #
data NestedAtomically #
Instances
Exception NestedAtomically | |
Show NestedAtomically | |
Defined in GHC.Internal.Control.Exception.Base showsPrec :: Int -> NestedAtomically -> ShowS # show :: NestedAtomically -> String # showList :: [NestedAtomically] -> ShowS # |
data NonTermination #
Instances
Exception NonTermination | |
Defined in GHC.Internal.Control.Exception.Base | |
Show NonTermination | |
Defined in GHC.Internal.Control.Exception.Base showsPrec :: Int -> NonTermination -> ShowS # show :: NonTermination -> String # showList :: [NonTermination] -> ShowS # |
newtype NoMethodError #
Instances
Exception NoMethodError | |
Defined in GHC.Internal.Control.Exception.Base | |
Show NoMethodError | |
Defined in GHC.Internal.Control.Exception.Base showsPrec :: Int -> NoMethodError -> ShowS # show :: NoMethodError -> String # showList :: [NoMethodError] -> ShowS # |
newtype RecUpdError #
Instances
Exception RecUpdError | |
Defined in GHC.Internal.Control.Exception.Base toException :: RecUpdError -> SomeException # fromException :: SomeException -> Maybe RecUpdError # displayException :: RecUpdError -> String # backtraceDesired :: RecUpdError -> Bool # | |
Show RecUpdError | |
Defined in GHC.Internal.Control.Exception.Base showsPrec :: Int -> RecUpdError -> ShowS # show :: RecUpdError -> String # showList :: [RecUpdError] -> ShowS # |
newtype RecConError #
Instances
Exception RecConError | |
Defined in GHC.Internal.Control.Exception.Base toException :: RecConError -> SomeException # fromException :: SomeException -> Maybe RecConError # displayException :: RecConError -> String # backtraceDesired :: RecConError -> Bool # | |
Show RecConError | |
Defined in GHC.Internal.Control.Exception.Base showsPrec :: Int -> RecConError -> ShowS # show :: RecConError -> String # showList :: [RecConError] -> ShowS # |
newtype RecSelError #
Instances
Exception RecSelError | |
Defined in GHC.Internal.Control.Exception.Base toException :: RecSelError -> SomeException # fromException :: SomeException -> Maybe RecSelError # displayException :: RecSelError -> String # backtraceDesired :: RecSelError -> Bool # | |
Show RecSelError | |
Defined in GHC.Internal.Control.Exception.Base showsPrec :: Int -> RecSelError -> ShowS # show :: RecSelError -> String # showList :: [RecSelError] -> ShowS # |
newtype PatternMatchFail #
Instances
Exception PatternMatchFail | |
Show PatternMatchFail | |
Defined in GHC.Internal.Control.Exception.Base showsPrec :: Int -> PatternMatchFail -> ShowS # show :: PatternMatchFail -> String # showList :: [PatternMatchFail] -> ShowS # |
mapException :: (Exception e1, Exception e2) => (e1 -> e2) -> a -> a #
allowInterrupt :: IO () #
type ExceptionMonad (m :: Type -> Type) = (MonadCatch m, MonadThrow m, MonadMask m, MonadIO m) Source #