checked-io-0.1.0.0: Checked IO exceptions
Safe HaskellSafe-Inferred
LanguageHaskell2010

CheckedIO.Core

Synopsis

IOE: Checked IO with exceptions

newtype IOE e a Source #

A checked IO action that can only throw synchronous exceptions of the given type.

Morally equivalent to UIO (Either e a), but implemented without the Either for performance.

Constructors

UnsafeIOE (UnsafeIO a) 

Instances

Instances details
Exception e => MonadCatchIO e (IOE e) Source # 
Instance details

Defined in CheckedIO.Core

Methods

catchM :: MonadRunAsIOE e' m' => IOE e a -> (e -> m' a) -> m' a Source #

catchAnyM :: MonadRunAsIOE e' m' => IOE e a -> (AnyException e -> m' a) -> m' a Source #

Exception e => MonadRunAsIOE e (IOE e) Source # 
Instance details

Defined in CheckedIO.Core

Methods

withRunAsIOE :: ((forall a. IOE e a -> IOE e a) -> IOE e b) -> IOE e b Source #

Exception e => MonadRunIOE e (IOE e) Source # 
Instance details

Defined in CheckedIO.Core

Methods

runIOE :: IOE e a -> IOE e a Source #

Applicative (IOE e) Source # 
Instance details

Defined in CheckedIO.Core

Methods

pure :: a -> IOE e a #

(<*>) :: IOE e (a -> b) -> IOE e a -> IOE e b #

liftA2 :: (a -> b -> c) -> IOE e a -> IOE e b -> IOE e c #

(*>) :: IOE e a -> IOE e b -> IOE e b #

(<*) :: IOE e a -> IOE e b -> IOE e a #

Functor (IOE e) Source # 
Instance details

Defined in CheckedIO.Core

Methods

fmap :: (a -> b) -> IOE e a -> IOE e b #

(<$) :: a -> IOE e b -> IOE e a #

Monad (IOE e) Source # 
Instance details

Defined in CheckedIO.Core

Methods

(>>=) :: IOE e a -> (a -> IOE e b) -> IOE e b #

(>>) :: IOE e a -> IOE e b -> IOE e b #

return :: a -> IOE e a #

class (Monad m, Exception e) => MonadRunIOE e m | m -> e where Source #

Run an IOE action in the given monad.

e.g. to convert an IOE action to an ExceptT stack on top of UIO:

newtype ExceptT e m a = ExceptT { unExceptT :: m (Either e a) }
  deriving (Functor, Applicative, Monad)

instance MonadRunUIO m => MonadRunIOE e (ExceptT e m) where
  runIOE = ExceptT . try

Methods

runIOE :: IOE e a -> m a Source #

Instances

Instances details
Exception e => MonadRunIOE e (IOE e) Source # 
Instance details

Defined in CheckedIO.Core

Methods

runIOE :: IOE e a -> IOE e a Source #

class MonadRunIOE e m => MonadRunAsIOE e m | m -> e where Source #

Provide a function for running an action in the given monad in IOE.

Instances must satisfy the following laws:

Identity
withRunAsIOE (\run -> run m) === m
Inverse
withRunAsIOE (\_ -> m) === runIOE m

Methods

withRunAsIOE :: ((forall a. m a -> IOE e a) -> IOE e b) -> m b Source #

Instances

Instances details
Exception e => MonadRunAsIOE e (IOE e) Source # 
Instance details

Defined in CheckedIO.Core

Methods

withRunAsIOE :: ((forall a. IOE e a -> IOE e a) -> IOE e b) -> IOE e b Source #

IO convenience type

type IO = IOE SomeSyncException Source #

A helper containing any synchronous exception.

runIO :: MonadRunIO m => IO a -> m a Source #

runIOE specialized to IO

withRunAsIO :: MonadRunAsIO m => ((forall a. m a -> IO a) -> IO b) -> m b Source #

withRunAsIOE specialized to IO

UIO convenience type

type UIO = IOE Void Source #

A checked IO action that cannot throw any (synchronous) exceptions.

runUIO :: MonadRunIOE e m => UIO a -> m a Source #

withRunAsUIO :: MonadRunAsUIO m => ((forall a. m a -> UIO a) -> UIO b) -> m b Source #

fromUIO :: forall e m a. MonadRunIOE e m => UIO (Either e a) -> m a Source #

Convert UIO (Either e a) to IOE e a (or any other monad with a MonadRunIOE instance).

fromUIO m = runUIO m >>= either throw pure

fromUIOWith :: forall e1 e2 m a. MonadRunIOE e2 m => (e1 -> e2) -> UIO (Either e1 a) -> m a Source #

Convert UIO (Either e1 a) to IOE e2 a (or any other monad with a MonadRunIOE instance) with the given transformation function.

Same as mapExceptionM f . fromUIO, but more performant.

uioToIO :: (Exception e, MonadRunIO m) => UIO (Either e a) -> m a Source #

Convert UIO (Either e a) action to IO a (or any other monad with a MonadRunIO instance).

Same as liftE . fromUIO, but more performant.

Exception handling

throw :: MonadRunIOE e m => e -> m a Source #

Throw the given exception.

throwTo :: (Exception e, MonadRunIOE e' m) => ThreadId -> e -> m () Source #

Throw the given exception as an asynchronous exception to the given thread.

throwImprecise :: Exception e => e -> a Source #

Throw an imprecise exception in a pure context.

Warning: Because the exception isn't tracked at the type level, this should be reserved for unrecoverable errors that aren't expected to be handled. Also, if this value is not evaluated before uncheckIOE is called, it'll remain wrapped in AnyException.

catch :: forall e1 e2 a. (Exception e1, Exception e2) => IOE e1 a -> (e1 -> IOE e2 a) -> IOE e2 a Source #

Handle the exception tracked in IOE if one is thrown.

catchAny :: forall e1 e2 a. (Exception e1, Exception e2) => IOE e1 a -> (AnyException e1 -> IOE e2 a) -> IOE e2 a Source #

Handle all exceptions in the given IOE action, including non-synchronous exceptions.

Warning: You probably want catch instead; if you catch an async exception, you must be careful to rethrow it after.

More information:

try :: forall e1 e2 a. (Exception e1, Exception e2) => IOE e1 a -> IOE e2 (Either e1 a) Source #

Get an Either containing either the result or the exception thrown.

mapExceptionM :: forall e1 e2 m1 m2 a. (MonadCatchIO e1 m1, MonadRunAsIOE e2 m2) => (e1 -> e2) -> m1 a -> m2 a Source #

liftE :: forall e m1 m2 a. (MonadCatchIO e m1, MonadRunAsIO m2) => m1 a -> m2 a Source #

Lift an exception to SomeSyncException, useful for converting to IO.

liftE = mapExceptionM SomeSyncException

Example

Expand
foo :: String -> IOE MyException Int

bar :: IO Int
bar = liftE $ foo "hello world"

evaluate :: MonadRunIOE e m => a -> m a Source #

Cleanup (no recovery)

bracket :: Exception e => IOE e a -> (a -> IOE e b) -> (a -> IOE e c) -> IOE e c Source #

bracket_ :: Exception e => IOE e a -> IOE e b -> IOE e c -> IOE e c Source #

Same as bracket, except without passing the result of the acquire action to the release or run actions.

bracketOnError :: (Exception e, Exception e') => IOE e a -> (a -> IOE e' b) -> (a -> IOE e c) -> IOE e c Source #

Same as bracket, but only perform the cleanup if an exception is thrown.

bracketOnError_ :: (Exception e, Exception e') => IOE e a -> IOE e' b -> IOE e c -> IOE e c Source #

Same as bracket_, but only perform the cleanup if an exception is thrown.

finally :: Exception e => IOE e a -> IOE e b -> IOE e a Source #

A specialized variant of bracket that just runs a computation afterward.

onException :: (Exception e, Exception e') => IOE e a -> IOE e' b -> IOE e a Source #

Like finally, except only runs the cleanup if an exception occurs.

withException :: (Exception e, Exception e') => IOE e a -> (AnyException e -> IOE e' b) -> IOE e a Source #

Like onException, except passing the exception to the cleanup function.

Unlike catchAny, you don't need to worry about rethrowing async exceptions because withException always rethrows the exception after running the cleanup.

Masking

mask :: Exception e => ((forall e' a. Exception e' => IOE e' a -> IOE e' a) -> IOE e b) -> IOE e b Source #

Execute an IO action with asynchronous exceptions masked.

https://hackage.haskell.org/package/base-4.17.0.0/docs/GHC-IO.html#v:mask

uninterruptibleMask :: Exception e => ((forall e' a. Exception e' => IOE e' a -> IOE e' a) -> IOE e b) -> IOE e b Source #

Like mask, but the masked computation is not interruptible.

Warning: Use with great care, as a thread running with uninterruptibleMask will be unresponsive and unkillable if it blocks at all.

https://hackage.haskell.org/package/base-4.17.0.0/docs/GHC-IO.html#v:uninterruptibleMask

mask_ :: Exception e => IOE e a -> IOE e a Source #

Like mask, but does not pass a restore action to the argument.

uninterruptibleMask_ :: Exception e => IOE e a -> IOE e a Source #

Like uninterruptibleMask, but does not pass a restore action to the argument.

Lifted exception handling

class (MonadRunAsIOE e m, Exception e) => MonadCatchIO e m | m -> e where Source #

Minimal complete definition

catchAnyM

Methods

catchM :: MonadRunAsIOE e' m' => m a -> (e -> m' a) -> m' a Source #

catch generalized to any MonadCatchIO + MonadRunAsIOE

catchAnyM :: MonadRunAsIOE e' m' => m a -> (AnyException e -> m' a) -> m' a Source #

catchAny generalized to any MonadCatchIO + MonadRunAsIOE

Instances

Instances details
Exception e => MonadCatchIO e (IOE e) Source # 
Instance details

Defined in CheckedIO.Core

Methods

catchM :: MonadRunAsIOE e' m' => IOE e a -> (e -> m' a) -> m' a Source #

catchAnyM :: MonadRunAsIOE e' m' => IOE e a -> (AnyException e -> m' a) -> m' a Source #

tryM :: (MonadCatchIO e m1, MonadRunIOE e' m2) => m1 a -> m2 (Either e a) Source #

try generalized to any MonadCatchIO + MonadRunIOE

bracketM :: MonadCatchIO e m => m a -> (a -> m b) -> (a -> m c) -> m c Source #

bracket generalized to any MonadCatchIO

bracketM_ :: MonadCatchIO e m => m a -> m b -> m c -> m c Source #

bracket_ generalized to any MonadCatchIO

bracketOnErrorM :: (MonadCatchIO e m, MonadCatchIO e' m') => m a -> (a -> m' b) -> (a -> m c) -> m c Source #

bracketOnError generalized to any MonadCatchIO

bracketOnErrorM_ :: (MonadCatchIO e m, MonadCatchIO e' m') => m a -> m' b -> m c -> m c Source #

bracketOnError_ generalized to any MonadCatchIO

finallyM :: MonadCatchIO e m => m a -> m b -> m a Source #

finally generalized to any MonadCatchIO

onExceptionM :: (MonadCatchIO e m, MonadCatchIO e' m') => m a -> m' b -> m a Source #

onException generalized to any MonadCatchIO

withExceptionM :: (MonadCatchIO e m, MonadCatchIO e' m') => m a -> (AnyException e -> m' b) -> m a Source #

withException generalized to any MonadCatchIO

maskM :: MonadCatchIO e m => ((forall m' e' a. MonadCatchIO e' m' => m' a -> m' a) -> m b) -> m b Source #

mask generalized to any MonadCatchIO

uninterruptibleMaskM :: MonadCatchIO e m => ((forall m' e' a. MonadCatchIO e' m' => m' a -> m' a) -> m b) -> m b Source #

maskM_ :: MonadCatchIO e m => m a -> m a Source #

mask_ generalized to any MonadCatchIO

Interop with unchecked IO

type Main = UnsafeIO () Source #

A convenient alias for main functions

type UnsafeIO = IO Source #

An alias for the normal unsafe IO type.

checkIO :: MonadRunIO m => UnsafeIO a -> m a Source #

Convert an unchecked IO action into a checked IO action.

checkIOWith :: MonadRunIOE e m => (SomeException -> e) -> UnsafeIO a -> m a Source #

Same as checkIO except converting a synchronous exception with the given function.

Equivalent to mapExceptionM f . checkIO, except more performant.

checkUIOWith :: MonadRunIOE e' m => (SomeException -> e) -> UnsafeIO a -> m (Either e a) Source #

Same as checkIOWith except returning the exception as an Either instead of throwing it.

unsafeCheckIO :: (HasCallStack, MonadRunIOE e m) => UnsafeIO a -> m a Source #

Convert an unchecked IO action into a checked IO action that can throw the given exception type.

Warning: If the IO action threw a different synchronous exception, this function will error. Prefer using checkIOWith and calling error yourself with a better error message.

unsafeCheckUIO :: (HasCallStack, MonadRunIOE e m) => UnsafeIO a -> m a Source #

Same as unsafeCheckIO, except expects no exceptions to be thrown.

uncheckIOE :: forall e a. Exception e => IOE e a -> UnsafeIO a Source #

Unchecks an IOE action back into the normal IO monad.

Warning: Imprecise exceptions might be wrapped in AnyException after converting to UnsafeIO. See throwImprecise for more details.

uncheckUIO :: UIO a -> UnsafeIO a Source #

uncheckIOE specialized to UIO.

Exceptions in checked IO actions

data AnyException e Source #

All exceptions floating around IOE (synchronous or otherwise) will be an AnyException SomeException.