Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Fx env err res
- provideAndUse :: Provider err env -> Fx env err res -> Fx env' err res
- handleEnv :: (env -> Fx env err res) -> Fx env err res
- start :: Fx env err res -> Fx env err' (Future err res)
- wait :: Future err res -> Fx env err res
- concurrently :: Conc env err res -> Fx env err res
- runTotalIO :: IO res -> Fx env err res
- runPartialIO :: IO (Either err res) -> Fx env err res
- runExceptionalIO :: Exception exc => IO res -> Fx env exc res
- runSTM :: STM res -> Fx env err res
- data Provider err env
- acquireAndRelease :: Fx () err env -> (env -> Fx () err ()) -> Provider err env
- pool :: Int -> Provider err env -> Provider err (Provider err' env)
- data Future err res
- data Conc env err res
- class FxRunning env err m | m -> env, m -> err where
- class ErrHandling m where
- exposeErr :: (ErrHandling m, Functor (m a), Applicative (m b)) => m a res -> m b (Either a res)
- absorbErr :: (ErrHandling m, Applicative (m b)) => (a -> res) -> m a res -> m b res
- class EnvMapping m where
- mapEnv :: (b -> a) -> m a err res -> m b err res
- data FxException = FxException [ThreadId] FxExceptionReason
- data FxExceptionReason
Fx
Effectful computation with explicit errors in the context of provided environment.
Calling fail
causes the whole app to interrupt outputting a message to console.
fail
is intended to be used in events which you expect never to happen,
and hence which should be considered bugs.
It is similar to calling fail
on IO,
with a major difference of the error never getting lost in a concurrent environment.
Calling fail
results in ErrorCallFxExceptionReason
in the triggerred FxException
.
Thus in effect it is the same as calling the error
function.
Instances
EnvMapping Fx Source # | |
FxRunning () Void (Fx env err) Source # | Executes an effect with no environment and all errors handled in |
Bifunctor (Fx env) Source # | |
ErrHandling (Fx env) Source # | |
Monad (Fx env err) Source # | |
Functor (Fx env err) Source # | |
MonadFail (Fx env err) Source # | |
Applicative (Fx env err) Source # | |
MonadIO (Fx env SomeException) Source # | |
Monoid err => Alternative (Fx env err) Source # | |
Monoid err => MonadPlus (Fx env err) Source # | |
Selective (Fx env err) Source # | |
Environment handling
provideAndUse :: Provider err env -> Fx env err res -> Fx env' err res Source #
Execute Fx in the scope of a provided environment.
handleEnv :: (env -> Fx env err res) -> Fx env err res Source #
Collapse an env handler into an environmental effect.
Warning: This function leaks the abstraction over the environment. It is your responsibility to ensure that you don't use it to return the environment and use it outside of the handler's scope.
Concurrency
start :: Fx env err res -> Fx env err' (Future err res) Source #
Spawn a thread and start running an effect on it, returning the associated future.
Fatal errors on the spawned thread are guaranteed to get propagated to the top.
By fatal errors we mean calls to error
, fail
and uncaught exceptions.
Normal errors (the explicit err
parameter) will only propagate
if you use wait
at some point.
Warning:
It is your responsibility to ensure that the whole future executes
before the running Fx
finishes.
Otherwise you will lose the environment in scope of which the future executes.
To achieve that use wait
.
wait :: Future err res -> Fx env err res Source #
Block until the future completes either with a result or an error.
concurrently :: Conc env err res -> Fx env err res Source #
Execute concurrent effects.
IO execution
These functions leak abstraction in one way or the other,
requiring you to ensure that your code doesn't throw unexpected exceptions.
try
are catch
are your tools for that.
Besides these functions Fx
also has an instance of MonadIO
,
which provides the only non-leaky way of running IO, catching all possible exceptions.
runTotalIO :: IO res -> Fx env err res Source #
Turn a non-failing IO action into an effect.
Warning: It is your responsibility to ensure that it does not throw exceptions!
runPartialIO :: IO (Either err res) -> Fx env err res Source #
Run IO which produces either an error or result.
Warning: It is your responsibility to ensure that it does not throw exceptions!
runExceptionalIO :: Exception exc => IO res -> Fx env exc res Source #
Run IO which only throws a specific type of exception.
Warning: It is your responsibility to ensure that it doesn't throw any other exceptions!
runSTM :: STM res -> Fx env err res Source #
Run STM, crashing in case of STM exceptions.
Same as
.runTotalIO
. atomically
Provider
data Provider err env Source #
Effectful computation with explicit errors, which encompasses environment acquisition and releasing.
Composes well, allowing you to merge multiple providers into one.
Builds up on ideas expressed in http://www.haskellforall.com/2013/06/the-resource-applicative.html and later released as the "managed" package.
acquireAndRelease :: Fx () err env -> (env -> Fx () err ()) -> Provider err env Source #
Create a resource provider from acquiring and releasing effects.
pool :: Int -> Provider err env -> Provider err (Provider err' env) Source #
Convert a single resource provider into a pool provider.
The wrapper provider acquires the specified amount of resources using the original provider, and returns a modified version of the original provider, whose acquisition and releasing merely takes one resource out of the pool and puts it back when done. No actual acquisition or releasing happens in the wrapped provider. No errors get raised in it either.
Use this when you need to access a resource concurrently.
Future
Handle to a result of an action which may still be being executed on another thread.
The way you deal with it is thru the start
and wait
functions.
Conc
data Conc env err res Source #
Wrapper over Fx
,
whose instances compose by running computations on separate threads.
Instances
EnvMapping Conc Source # | |
FxRunning env err (Conc env err) Source # | |
Bifunctor (Conc env) Source # | |
ErrHandling (Conc env) Source # | |
Functor (Conc env err) Source # | |
Applicative (Conc env err) Source # | |
Defined in Fx | |
Selective (Conc env err) Source # | Spawns a computation, deciding whether to wait for it. |
Classes
FxRunning
class FxRunning env err m | m -> env, m -> err where Source #
Support for running of Fx
.
Apart from other things this is your interface to turn Fx
into IO
or Conc
.
Instances
FxRunning () Void IO Source # | Executes an effect with no environment and all errors handled. |
FxRunning () err (Provider err) Source # | |
FxRunning () err (ExceptT err IO) Source # | |
FxRunning () Void (Fx env err) Source # | Executes an effect with no environment and all errors handled in |
FxRunning env err (Conc env err) Source # | |
FxRunning env err (ReaderT env (ExceptT err IO)) Source # | |
ErrHandling
class ErrHandling m where Source #
Support for error handling.
Functions provided by this class are particularly helpful,
when you need to map into error of type Void
.
throwErr :: err -> m err res Source #
Interrupt the current computation raising an error.
handleErr :: (a -> m b res) -> m a res -> m b res Source #
Handle error in another failing action. Sort of like a bind operation over the error type parameter.
Instances
ErrHandling Future Source # | |
ErrHandling (Conc env) Source # | |
ErrHandling (Fx env) Source # | |
exposeErr :: (ErrHandling m, Functor (m a), Applicative (m b)) => m a res -> m b (Either a res) Source #
Expose the error in result, producing an action, which is compatible with any error type.
absorbErr :: (ErrHandling m, Applicative (m b)) => (a -> res) -> m a res -> m b res Source #
Map from error to result, leaving the error be anything.
EnvMapping
class EnvMapping m where Source #
Support for mapping of the environment.
Exceptions
data FxException Source #
Fatal failure of an Fx
application.
Informs of an unrecoverable condition that the application has reached.
It is not meant to be caught,
because it implies that there is either a bug in your code or
a bug in the "fx" library itself, which needs reporting.
Consists of a list of thread identifiers specifying the nesting path of the faulty thread and the reason of failure.
Instances
Show FxException Source # | |
Defined in Fx showsPrec :: Int -> FxException -> ShowS # show :: FxException -> String # showList :: [FxException] -> ShowS # | |
Exception FxException Source # | |
Defined in Fx |
data FxExceptionReason Source #
Reason of a fatal failure of an Fx
application.
UncaughtExceptionFxExceptionReason SomeException | |
ErrorCallFxExceptionReason ErrorCall | |
BugFxExceptionReason String |
Instances
Show FxExceptionReason Source # | |
Defined in Fx showsPrec :: Int -> FxExceptionReason -> ShowS # show :: FxExceptionReason -> String # showList :: [FxExceptionReason] -> ShowS # |