| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
CheckedIO.Core
Synopsis
- newtype IOE e a = UnsafeIOE (UnsafeIO a)
- class (Monad m, Exception e) => MonadRunIOE e m | m -> e where
- class MonadRunIOE e m => MonadRunAsIOE e m | m -> e where
- withRunAsIOE :: ((forall a. m a -> IOE e a) -> IOE e b) -> m b
- type IO = IOE SomeSyncException
- type MonadRunIO = MonadRunIOE SomeSyncException
- type MonadRunAsIO = MonadRunAsIOE SomeSyncException
- runIO :: MonadRunIO m => IO a -> m a
- withRunAsIO :: MonadRunAsIO m => ((forall a. m a -> IO a) -> IO b) -> m b
- type UIO = IOE Void
- type MonadRunUIO = MonadRunIOE Void
- type MonadRunAsUIO = MonadRunAsIOE Void
- runUIO :: MonadRunIOE e m => UIO a -> m a
- withRunAsUIO :: MonadRunAsUIO m => ((forall a. m a -> UIO a) -> UIO b) -> m b
- fromUIO :: forall e m a. MonadRunIOE e m => UIO (Either e a) -> m a
- fromUIOWith :: forall e1 e2 m a. MonadRunIOE e2 m => (e1 -> e2) -> UIO (Either e1 a) -> m a
- uioToIO :: (Exception e, MonadRunIO m) => UIO (Either e a) -> m a
- throw :: MonadRunIOE e m => e -> m a
- throwTo :: (Exception e, MonadRunIOE e' m) => ThreadId -> e -> m ()
- throwImprecise :: Exception e => e -> a
- catch :: forall e1 e2 a. (Exception e1, Exception e2) => IOE e1 a -> (e1 -> IOE e2 a) -> IOE e2 a
- catchAny :: forall e1 e2 a. (Exception e1, Exception e2) => IOE e1 a -> (AnyException e1 -> IOE e2 a) -> IOE e2 a
- try :: forall e1 e2 a. (Exception e1, Exception e2) => IOE e1 a -> IOE e2 (Either e1 a)
- mapExceptionM :: forall e1 e2 m1 m2 a. (MonadCatchIO e1 m1, MonadRunAsIOE e2 m2) => (e1 -> e2) -> m1 a -> m2 a
- liftE :: forall e m1 m2 a. (MonadCatchIO e m1, MonadRunAsIO m2) => m1 a -> m2 a
- evaluate :: MonadRunIOE e m => a -> m a
- bracket :: Exception e => IOE e a -> (a -> IOE e b) -> (a -> IOE e c) -> IOE e c
- bracket_ :: Exception e => IOE e a -> IOE e b -> IOE e c -> IOE e c
- bracketOnError :: (Exception e, Exception e') => IOE e a -> (a -> IOE e' b) -> (a -> IOE e c) -> IOE e c
- bracketOnError_ :: (Exception e, Exception e') => IOE e a -> IOE e' b -> IOE e c -> IOE e c
- finally :: Exception e => IOE e a -> IOE e b -> IOE e a
- onException :: (Exception e, Exception e') => IOE e a -> IOE e' b -> IOE e a
- withException :: (Exception e, Exception e') => IOE e a -> (AnyException e -> IOE e' b) -> IOE e a
- mask :: Exception e => ((forall e' a. Exception e' => IOE e' a -> IOE e' a) -> IOE e b) -> IOE e b
- uninterruptibleMask :: Exception e => ((forall e' a. Exception e' => IOE e' a -> IOE e' a) -> IOE e b) -> IOE e b
- mask_ :: Exception e => IOE e a -> IOE e a
- uninterruptibleMask_ :: Exception e => IOE e a -> IOE e a
- class (MonadRunAsIOE e m, Exception e) => MonadCatchIO e m | m -> e where
- catchM :: MonadRunAsIOE e' m' => m a -> (e -> m' a) -> m' a
- catchAnyM :: MonadRunAsIOE e' m' => m a -> (AnyException e -> m' a) -> m' a
- tryM :: (MonadCatchIO e m1, MonadRunIOE e' m2) => m1 a -> m2 (Either e a)
- bracketM :: MonadCatchIO e m => m a -> (a -> m b) -> (a -> m c) -> m c
- bracketM_ :: MonadCatchIO e m => m a -> m b -> m c -> m c
- bracketOnErrorM :: (MonadCatchIO e m, MonadCatchIO e' m') => m a -> (a -> m' b) -> (a -> m c) -> m c
- bracketOnErrorM_ :: (MonadCatchIO e m, MonadCatchIO e' m') => m a -> m' b -> m c -> m c
- finallyM :: MonadCatchIO e m => m a -> m b -> m a
- onExceptionM :: (MonadCatchIO e m, MonadCatchIO e' m') => m a -> m' b -> m a
- withExceptionM :: (MonadCatchIO e m, MonadCatchIO e' m') => m a -> (AnyException e -> m' b) -> m a
- maskM :: MonadCatchIO e m => ((forall m' e' a. MonadCatchIO e' m' => m' a -> m' a) -> m b) -> m b
- uninterruptibleMaskM :: MonadCatchIO e m => ((forall m' e' a. MonadCatchIO e' m' => m' a -> m' a) -> m b) -> m b
- maskM_ :: MonadCatchIO e m => m a -> m a
- uninterruptibleMaskM_ :: MonadCatchIO e m => m a -> m a
- type Main = UnsafeIO ()
- type UnsafeIO = IO
- checkIO :: MonadRunIO m => UnsafeIO a -> m a
- checkIOWith :: MonadRunIOE e m => (SomeException -> e) -> UnsafeIO a -> m a
- checkUIOWith :: MonadRunIOE e' m => (SomeException -> e) -> UnsafeIO a -> m (Either e a)
- unsafeCheckIO :: (HasCallStack, MonadRunIOE e m) => UnsafeIO a -> m a
- unsafeCheckUIO :: (HasCallStack, MonadRunIOE e m) => UnsafeIO a -> m a
- uncheckIOE :: forall e a. Exception e => IOE e a -> UnsafeIO a
- uncheckUIO :: UIO a -> UnsafeIO a
- data AnyException e
- data SomeSyncException = forall e.Exception e => SomeSyncException e
IOE: Checked IO with exceptions
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.
Instances
| Exception e => MonadCatchIO e (IOE e) Source # | |
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 # | |
Defined in CheckedIO.Core | |
| Exception e => MonadRunIOE e (IOE e) Source # | |
| Applicative (IOE e) Source # | |
| Functor (IOE e) Source # | |
| Monad (IOE e) Source # | |
class (Monad m, Exception e) => MonadRunIOE e m | m -> e where 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
| Exception e => MonadRunAsIOE e (IOE e) Source # | |
Defined in CheckedIO.Core | |
IO convenience type
type IO = IOE SomeSyncException Source #
A helper containing any synchronous exception.
type MonadRunIO = MonadRunIOE SomeSyncException Source #
MonadRunIOE specialized to IO
type MonadRunAsIO = MonadRunAsIOE SomeSyncException Source #
MonadRunAsIOE 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 MonadRunUIO = MonadRunIOE Void Source #
type MonadRunAsUIO = MonadRunAsIOE Void Source #
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 #
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
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 #
Allocate and clean up a resource safely.
Runs the clean up in an uninterruptible mask. For more information:
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
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
| Exception e => MonadCatchIO e (IOE e) Source # | |
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 #
uninterruptibleMask generalized to any MonadCatchIO
maskM_ :: MonadCatchIO e m => m a -> m a Source #
mask_ generalized to any MonadCatchIO
uninterruptibleMaskM_ :: MonadCatchIO e m => m a -> m a Source #
uninterruptibleMask_ generalized to any MonadCatchIO
Interop with unchecked IO
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.
Instances
| Functor AnyException Source # | |
Defined in CheckedIO.Core Methods fmap :: (a -> b) -> AnyException a -> AnyException b # (<$) :: a -> AnyException b -> AnyException a # | |
| Exception (AnyException SomeException) Source # | |
Defined in CheckedIO.Core Methods toException :: AnyException SomeException -> SomeException # fromException :: SomeException -> Maybe (AnyException SomeException) # | |
| Show e => Show (AnyException e) Source # | |
Defined in CheckedIO.Core Methods showsPrec :: Int -> AnyException e -> ShowS # show :: AnyException e -> String # showList :: [AnyException e] -> ShowS # | |
data SomeSyncException Source #
Constructors
| forall e.Exception e => SomeSyncException e |
Instances
| Exception SomeSyncException Source # | |
Defined in CheckedIO.Core Methods toException :: SomeSyncException -> SomeException # | |
| Show SomeSyncException Source # | |
Defined in CheckedIO.Core Methods showsPrec :: Int -> SomeSyncException -> ShowS # show :: SomeSyncException -> String # showList :: [SomeSyncException] -> ShowS # | |