Safe Haskell | Safe |
---|---|
Language | Haskell98 |
When you've caught all the exceptions that can be handled safely, this is what you're left with.
runExceptIO . fromIO ≡ id
It is intended that you use qualified imports with this library.
import UnexceptionalIO.Trans (UIO) import qualified UnexceptionalIO.Trans as UIO
Synopsis
- data UIO a
- class Monad m => Unexceptional (m :: Type -> Type) where
- fromIO :: Unexceptional m => IO a -> ExceptT SomeNonPseudoException m a
- fromIO' :: (Exception e, Unexceptional m) => (SomeNonPseudoException -> e) -> IO a -> ExceptT e m a
- run :: MonadIO m => UIO a -> m a
- runExceptIO :: (Exception e, MonadIO m) => ExceptT e UIO a -> m a
- unsafeFromIO :: Unexceptional m => IO a -> m a
- data SomeNonPseudoException
- data PseudoException
- data ProgrammerError
- = TypeError TypeError
- | ArithException ArithException
- | ArrayException ArrayException
- | AssertionFailed AssertionFailed
- | ErrorCall ErrorCall
- | NestedAtomically NestedAtomically
- | NoMethodError NoMethodError
- | PatternMatchFail PatternMatchFail
- | RecConError RecConError
- | RecSelError RecSelError
- | RecUpdError RecSelError
- data ExternalError
- bracket :: Unexceptional m => UIO a -> (a -> UIO ()) -> (a -> UIO c) -> m c
- forkFinally :: Unexceptional m => UIO a -> (Either PseudoException a -> UIO ()) -> m ThreadId
- fork :: Unexceptional m => UIO () -> m ThreadId
- newtype ChildThreadError = ChildThreadError PseudoException
Documentation
Like IO, but throws only PseudoException
Instances
Monad UIO | |
Functor UIO | |
MonadFix UIO | |
Defined in UnexceptionalIO | |
Applicative UIO | |
Unexceptional UIO | |
Defined in UnexceptionalIO |
class Monad m => Unexceptional (m :: Type -> Type) where #
Monads in which UIO
computations may be embedded
Instances
fromIO :: Unexceptional m => IO a -> ExceptT SomeNonPseudoException m a Source #
Catch any exception but PseudoException
in an IO
action
:: (Exception e, Unexceptional m) | |
=> (SomeNonPseudoException -> e) | Default if an unexpected exception occurs |
-> IO a | |
-> ExceptT e m a |
Catch any e
in an IO
action, with a default mapping for
unexpected cases
runExceptIO :: (Exception e, MonadIO m) => ExceptT e UIO a -> m a Source #
Re-embed UIO
and possible exception back into IO
Unsafe entry points
unsafeFromIO :: Unexceptional m => IO a -> m a #
You promise there are no exceptions but PseudoException
thrown by this IO
action
Pseudo exceptions
data SomeNonPseudoException #
Every SomeException
but PseudoException
Instances
Show SomeNonPseudoException | |
Defined in UnexceptionalIO showsPrec :: Int -> SomeNonPseudoException -> ShowS # show :: SomeNonPseudoException -> String # showList :: [SomeNonPseudoException] -> ShowS # | |
Exception SomeNonPseudoException | |
data PseudoException #
Not everything handled by the exception system is a run-time error you can handle. This is the class of unrecoverable pseudo-exceptions.
Additionally, except for ExitCode
any of these pseudo-exceptions
you could never guarantee to have caught. Since they can come
from anywhere at any time, we could never guarentee that UIO
does
not contain them.
ProgrammerError ProgrammerError | Mistakes programmers make |
ExternalError ExternalError | Errors thrown by the runtime |
Exit ExitCode | Process exit requests |
Instances
Show PseudoException | |
Defined in UnexceptionalIO showsPrec :: Int -> PseudoException -> ShowS # show :: PseudoException -> String # showList :: [PseudoException] -> ShowS # | |
Exception PseudoException | |
Defined in UnexceptionalIO |
data ProgrammerError #
Instances
Show ProgrammerError | |
Defined in UnexceptionalIO showsPrec :: Int -> ProgrammerError -> ShowS # show :: ProgrammerError -> String # showList :: [ProgrammerError] -> ShowS # | |
Exception ProgrammerError | |
Defined in UnexceptionalIO |
data ExternalError #
Pseudo-exceptions thrown by the runtime environment
Instances
Show ExternalError | |
Defined in UnexceptionalIO showsPrec :: Int -> ExternalError -> ShowS # show :: ExternalError -> String # showList :: [ExternalError] -> ShowS # | |
Exception ExternalError | |
Defined in UnexceptionalIO |
Pseudo exception helpers
bracket :: Unexceptional m => UIO a -> (a -> UIO ()) -> (a -> UIO c) -> m c #
When you're doing resource handling, PseudoException
matters.
You still need to use the bracket
pattern to handle cleanup.
forkFinally :: Unexceptional m => UIO a -> (Either PseudoException a -> UIO ()) -> m ThreadId #
Mirrors forkFinally
, but since the body is UIO
,
the thread must terminate successfully or because of PseudoException
fork :: Unexceptional m => UIO () -> m ThreadId #
Mirrors forkIO
, but re-throws errors to the parent thread
- Ignores manual thread kills, since those are on purpose.
- Re-throws async exceptions (
SomeAsyncException
) as is. - Re-throws
ExitCode
as is in an attempt to exit with the requested code. - Wraps synchronous
PseudoException
in asyncChildThreadError
.
newtype ChildThreadError #
Async signal that a child thread ended due to non-async PseudoException
Instances
Show ChildThreadError | |
Defined in UnexceptionalIO showsPrec :: Int -> ChildThreadError -> ShowS # show :: ChildThreadError -> String # showList :: [ChildThreadError] -> ShowS # | |
Exception ChildThreadError | |
Defined in UnexceptionalIO |
Orphan instances
Unexceptional m => Unexceptional (MaybeT m) Source # | |
Unexceptional m => Unexceptional (ListT m) Source # | |
(Unexceptional m, Monoid w) => Unexceptional (WriterT w m) Source # | |
(Unexceptional m, Monoid w) => Unexceptional (AccumT w m) Source # | |
(Unexceptional m, Monoid w) => Unexceptional (WriterT w m) Source # | |
Unexceptional m => Unexceptional (StateT s m) Source # | |
Unexceptional m => Unexceptional (StateT s m) Source # | |
Unexceptional m => Unexceptional (SelectT r m) Source # | |
Unexceptional m => Unexceptional (IdentityT m) Source # | |
Unexceptional m => Unexceptional (ExceptT e m) Source # | |
(Unexceptional m, Error e) => Unexceptional (ErrorT e m) Source # | |
Unexceptional m => Unexceptional (ReaderT r m) Source # | |
Unexceptional m => Unexceptional (ContT r m) Source # | |
(Unexceptional m, Monoid w) => Unexceptional (RWST r w s m) Source # | |
(Unexceptional m, Monoid w) => Unexceptional (RWST r w s m) Source # | |