Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Support for handling errors of a particular type, i.e. checked exceptions.
The Error
effect is not a general mechanism for handling regular
exceptions, that's what functions from the exceptions
library are for (see
Control.Monad.Catch for more information).
In particular, regular exceptions of type e
are distinct from errors of
type e
and will not be caught by functions from this module:
>>>
import qualified Control.Monad.Catch as E
>>>
boom = error "BOOM!"
>>>
runEff . runError @ErrorCall $ boom `catchError` \_ (_::ErrorCall) -> pure "caught"
*** Exception: BOOM! ...
If you want to catch regular exceptions, you should use
catch
(or a similar function):
>>>
runEff $ boom `E.catch` \(_::ErrorCall) -> pure "caught"
"caught"
On the other hand, functions for safe finalization and management of
resources such as finally
and
bracket
work as expected:
>>>
msg = liftIO . putStrLn
>>>
:{
runEff . runErrorNoCallStack @String $ do E.bracket_ (msg "Beginning.") (msg "Cleaning up.") (msg "Computing." >> throwError "oops" >> msg "More.") :} Beginning. Computing. Cleaning up. Left "oops"
Note: unlike the ExceptT
monad transformer
from the transformers
library, the order in which you handle the Error
effect with regard to other stateful effects does not matter. Consider the
following:
>>>
import qualified Control.Monad.State.Strict as T
>>>
import qualified Control.Monad.Except as T
>>>
m1 = (T.modify (++ " there!") >> T.throwError "oops") `T.catchError` \_ -> pure ()
>>>
(`T.runStateT` "Hi") . T.runExceptT $ m1
(Right (),"Hi there!")
>>>
T.runExceptT . (`T.runStateT` "Hi") $ m1
Right ((),"Hi")
Here, whether state updates within the catchError
block are discarded or
not depends on the shape of the monad transformer stack, which is surprising
and can be a source of subtle bugs. On the other hand:
>>>
import Effectful.State.Static.Local
>>>
m2 = (modify (++ " there!") >> throwError "oops") `catchError` \_ (_::String) -> pure ()
>>>
runEff . runState "Hi" . runError @String $ m2
(Right (),"Hi there!")
>>>
runEff . runError @String . runState "Hi" $ m2
Right ((),"Hi there!")
Here, no matter the order of effects, state updates made within the
catchError
block before the error happens always persist, giving
predictable behavior.
Hint: if you'd like to reproduce the transactional behavior with the
State
effect, appropriate usage of
bracketOnError
will do the trick.
Synopsis
- data Error e :: Effect
- runError :: forall e es a. Eff (Error e : es) a -> Eff es (Either (CallStack, e) a)
- runErrorWith :: (CallStack -> e -> Eff es a) -> Eff (Error e : es) a -> Eff es a
- runErrorNoCallStack :: forall e es a. Eff (Error e : es) a -> Eff es (Either e a)
- runErrorNoCallStackWith :: (e -> Eff es a) -> Eff (Error e : es) a -> Eff es a
- throwError :: forall e es a. (HasCallStack, Error e :> es) => e -> Eff es a
- catchError :: forall e es a. Error e :> es => Eff es a -> (CallStack -> e -> Eff es a) -> Eff es a
- handleError :: forall e es a. Error e :> es => (CallStack -> e -> Eff es a) -> Eff es a -> Eff es a
- tryError :: forall e es a. Error e :> es => Eff es a -> Eff es (Either (CallStack, e) a)
- type HasCallStack = ?callStack :: CallStack
- data CallStack
- getCallStack :: CallStack -> [([Char], SrcLoc)]
- prettyCallStack :: CallStack -> String
Effect
data Error e :: Effect Source #
Provide the ability to handle errors of type e
.
Instances
type DispatchOf (Error e) Source # | |
Defined in Effectful.Error.Static | |
newtype StaticRep (Error e) Source # | |
Defined in Effectful.Error.Static |
Handlers
runError :: forall e es a. Eff (Error e : es) a -> Eff es (Either (CallStack, e) a) Source #
Handle errors of type e
.
Handle errors of type e
with a specific error handler.
Since: 2.3.0.0
runErrorNoCallStack :: forall e es a. Eff (Error e : es) a -> Eff es (Either e a) Source #
Handle errors of type e
. In case of an error discard the CallStack
.
Since: 2.3.0.0
runErrorNoCallStackWith Source #
Handle errors of type e
with a specific error handler. In case of an
error discard the CallStack
.
Operations
:: forall e es a. (HasCallStack, Error e :> es) | |
=> e | The error. |
-> Eff es a |
Throw an error of type e
.
:: forall e es a. Error e :> es | |
=> Eff es a | The inner computation. |
-> (CallStack -> e -> Eff es a) | A handler for errors in the inner computation. |
-> Eff es a |
Handle an error of type e
.
:: forall e es a. Error e :> es | |
=> (CallStack -> e -> Eff es a) | A handler for errors in the inner computation. |
-> Eff es a | The inner computation. |
-> Eff es a |
The same as
, which is useful in situations where the
code for the handler is shorter.flip
catchError
:: forall e es a. Error e :> es | |
=> Eff es a | The inner computation. |
-> Eff es (Either (CallStack, e) a) |
Similar to catchError
, but returns an Either
result which is a Right
if no error was thrown and a Left
otherwise.
Re-exports
type HasCallStack = ?callStack :: CallStack #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack
is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: base-4.9.0.0
CallStack
s are a lightweight method of obtaining a
partial call-stack at any point in the program.
A function can request its call-site with the HasCallStack
constraint.
For example, we can define
putStrLnWithCallStack :: HasCallStack => String -> IO ()
as a variant of putStrLn
that will get its call-site and print it,
along with the string given as argument. We can access the
call-stack inside putStrLnWithCallStack
with callStack
.
>>>
:{
putStrLnWithCallStack :: HasCallStack => String -> IO () putStrLnWithCallStack msg = do putStrLn msg putStrLn (prettyCallStack callStack) :}
Thus, if we call putStrLnWithCallStack
we will get a formatted call-stack
alongside our string.
>>>
putStrLnWithCallStack "hello"
hello CallStack (from HasCallStack): putStrLnWithCallStack, called at <interactive>:... in interactive:Ghci...
GHC solves HasCallStack
constraints in three steps:
- If there is a
CallStack
in scope -- i.e. the enclosing function has aHasCallStack
constraint -- GHC will append the new call-site to the existingCallStack
. - If there is no
CallStack
in scope -- e.g. in the GHCi session above -- and the enclosing definition does not have an explicit type signature, GHC will infer aHasCallStack
constraint for the enclosing definition (subject to the monomorphism restriction). - If there is no
CallStack
in scope and the enclosing definition has an explicit type signature, GHC will solve theHasCallStack
constraint for the singletonCallStack
containing just the current call-site.
CallStack
s do not interact with the RTS and do not require compilation
with -prof
. On the other hand, as they are built up explicitly via the
HasCallStack
constraints, they will generally not contain as much
information as the simulated call-stacks maintained by the RTS.
A CallStack
is a [(String, SrcLoc)]
. The String
is the name of
function that was called, the SrcLoc
is the call-site. The list is
ordered with the most recently called function at the head.
NOTE: The intrepid user may notice that HasCallStack
is just an
alias for an implicit parameter ?callStack :: CallStack
. This is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: base-4.8.1.0
getCallStack :: CallStack -> [([Char], SrcLoc)] #
Extract a list of call-sites from the CallStack
.
The list is ordered by most recent call.
Since: base-4.8.1.0
prettyCallStack :: CallStack -> String #
Pretty print a CallStack
.
Since: base-4.9.0.0