unexceptionalio-trans-0.4.0: A wrapper around UnexceptionalIO using monad transformers

Safe HaskellSafe
LanguageHaskell98

UnexceptionalIO.Trans

Contents

Description

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

Documentation

data UIO a :: * -> * #

IO without any PseudoException

Instances

Monad UIO 

Methods

(>>=) :: UIO a -> (a -> UIO b) -> UIO b #

(>>) :: UIO a -> UIO b -> UIO b #

return :: a -> UIO a #

fail :: String -> UIO a #

Functor UIO 

Methods

fmap :: (a -> b) -> UIO a -> UIO b #

(<$) :: a -> UIO b -> UIO a #

MonadFix UIO 

Methods

mfix :: (a -> UIO a) -> UIO a #

Applicative UIO 

Methods

pure :: a -> UIO a #

(<*>) :: UIO (a -> b) -> UIO a -> UIO b #

liftA2 :: (a -> b -> c) -> UIO a -> UIO b -> UIO c #

(*>) :: UIO a -> UIO b -> UIO b #

(<*) :: UIO a -> UIO b -> UIO a #

Unexceptional UIO 

Methods

lift :: UIO a -> UIO a #

class Monad m => Unexceptional (m :: * -> *) where #

Polymorphic base without any PseudoException

Minimal complete definition

lift

Methods

lift :: UIO a -> m a #

Instances

Unexceptional IO 

Methods

lift :: UIO a -> IO a #

Unexceptional UIO 

Methods

lift :: UIO a -> UIO a #

fromIO :: Unexceptional m => IO a -> ExceptT SomeNonPseudoException m a Source #

Catch any exception but PseudoException in an IO action

run :: MonadIO m => UIO a -> m a Source #

Re-embed UIO into MonadIO

runExceptIO :: (Exception e, MonadIO m) => ExceptT e UIO a -> m a Source #

Re-embed UIO and possible exception back into IO

Unsafe entry points

fromIO' :: (Exception e, Unexceptional m) => IO a -> ExceptT e m a Source #

You promise that e covers all exceptions but PseudoException thrown by this IO action

This function is partial if you lie

unsafeFromIO :: Unexceptional m => IO a -> m a #

You promise there are no exceptions but PseudoException thrown by this IO action

Pseudo exceptions

data PseudoException :: * #

Not everything handled by the exception system is a run-time error you can handle. This is the class of pseudo-exceptions you usually can do nothing about, just log or exit.

Additionally, except for ExitCode any of these psuedo-exceptions you could never guarentee to have caught, since they can come from anywhere at any time, we could never guarentee that UIO does not contain them.

Constructors

ProgrammerError ProgrammerError

Mistakes programmers make

ExternalError ExternalError

Errors thrown by the runtime

Exit ExitCode

Process exit requests

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 any PseudoException to the parent thread

Orphan instances

Unexceptional m => Unexceptional (MaybeT m) Source # 

Methods

lift :: UIO a -> MaybeT m a #

Unexceptional m => Unexceptional (ListT m) Source # 

Methods

lift :: UIO a -> ListT m a #

(Unexceptional m, Monoid w) => Unexceptional (WriterT w m) Source # 

Methods

lift :: UIO a -> WriterT w m a #

(Unexceptional m, Monoid w) => Unexceptional (WriterT w m) Source # 

Methods

lift :: UIO a -> WriterT w m a #

Unexceptional m => Unexceptional (StateT s m) Source # 

Methods

lift :: UIO a -> StateT s m a #

Unexceptional m => Unexceptional (StateT s m) Source # 

Methods

lift :: UIO a -> StateT s m a #

Unexceptional m => Unexceptional (IdentityT * m) Source # 

Methods

lift :: UIO a -> IdentityT * m a #

Unexceptional m => Unexceptional (ExceptT e m) Source # 

Methods

lift :: UIO a -> ExceptT e m a #

(Unexceptional m, Error e) => Unexceptional (ErrorT e m) Source # 

Methods

lift :: UIO a -> ErrorT e m a #

Unexceptional m => Unexceptional (ReaderT * r m) Source # 

Methods

lift :: UIO a -> ReaderT * r m a #

Unexceptional m => Unexceptional (ContT * r m) Source # 

Methods

lift :: UIO a -> ContT * r m a #

(Unexceptional m, Monoid w) => Unexceptional (RWST r w s m) Source # 

Methods

lift :: UIO a -> RWST r w s m a #

(Unexceptional m, Monoid w) => Unexceptional (RWST r w s m) Source # 

Methods

lift :: UIO a -> RWST r w s m a #