| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Effectful.Error.Dynamic
Description
The dynamically dispatched variant of the Error effect.
Note: unless you plan to change interpretations at runtime, it's recommended to use the statically dispatched variant, i.e. Effectful.Error.Static.
Synopsis
- data Error e :: Effect where
- ThrowErrorWith :: (e -> String) -> e -> Error e m a
- CatchError :: m a -> (CallStack -> e -> m a) -> Error e m a
- runError :: HasCallStack => Eff (Error e : es) a -> Eff es (Either (CallStack, e) a)
- runErrorWith :: HasCallStack => (CallStack -> e -> Eff es a) -> Eff (Error e : es) a -> Eff es a
- runErrorNoCallStack :: HasCallStack => Eff (Error e : es) a -> Eff es (Either e a)
- runErrorNoCallStackWith :: HasCallStack => (e -> Eff es a) -> Eff (Error e : es) a -> Eff es a
- throwErrorWith :: (HasCallStack, Error e :> es) => (e -> String) -> e -> Eff es a
- throwError :: (HasCallStack, Error e :> es, Show e) => e -> Eff es a
- throwError_ :: (HasCallStack, Error e :> es) => e -> Eff es a
- catchError :: (HasCallStack, Error e :> es) => Eff es a -> (CallStack -> e -> Eff es a) -> Eff es a
- handleError :: (HasCallStack, Error e :> es) => (CallStack -> e -> Eff es a) -> Eff es a -> Eff es a
- tryError :: (HasCallStack, 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 where Source #
Provide the ability to handle errors of type e.
Constructors
| ThrowErrorWith :: (e -> String) -> e -> Error e m a | Since: 2.4.0.0 |
| CatchError :: m a -> (CallStack -> e -> m a) -> Error e m a |
Instances
| type DispatchOf (Error e) Source # | |
Defined in Effectful.Error.Dynamic | |
Handlers
runError :: HasCallStack => Eff (Error e : es) a -> Eff es (Either (CallStack, e) a) Source #
Handle errors of type e (via Effectful.Error.Static).
Arguments
| :: HasCallStack | |
| => (CallStack -> e -> Eff es a) | The error handler. |
| -> Eff (Error e : es) a | |
| -> Eff es a |
Handle errors of type e (via Effectful.Error.Static) with a specific
error handler.
Since: 2.3.0.0
runErrorNoCallStack :: HasCallStack => Eff (Error e : es) a -> Eff es (Either e a) Source #
Handle errors of type e (via Effectful.Error.Static). In case of an
error discard the CallStack.
Since: 2.3.0.0
runErrorNoCallStackWith Source #
Arguments
| :: HasCallStack | |
| => (e -> Eff es a) | The error handler. |
| -> Eff (Error e : es) a | |
| -> Eff es a |
Handle errors of type e (via Effectful.Error.Static) with a specific
error handler. In case of an error discard the CallStack.
Operations
Arguments
| :: (HasCallStack, Error e :> es) | |
| => (e -> String) | The display function. |
| -> e | The error. |
| -> Eff es a |
Throw an error of type e and specify a display function in case a
third-party code catches the internal exception and shows it.
Since: 2.4.0.0
Arguments
| :: (HasCallStack, Error e :> es, Show e) | |
| => e | The error. |
| -> Eff es a |
Throw an error of type e with show as a display function.
Arguments
| :: (HasCallStack, Error e :> es) | |
| => e | The error. |
| -> Eff es a |
Throw an error of type e with no display function.
Since: 2.4.0.0
Arguments
| :: (HasCallStack, 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.
Arguments
| :: (HasCallStack, 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
Arguments
| :: (HasCallStack, 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
CallStacks 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
CallStackin scope -- i.e. the enclosing function has aHasCallStackconstraint -- GHC will append the new call-site to the existingCallStack. - If there is no
CallStackin scope -- e.g. in the GHCi session above -- and the enclosing definition does not have an explicit type signature, GHC will infer aHasCallStackconstraint for the enclosing definition (subject to the monomorphism restriction). - If there is no
CallStackin scope and the enclosing definition has an explicit type signature, GHC will solve theHasCallStackconstraint for the singletonCallStackcontaining just the current call-site.
CallStacks 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