Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Extra functions for Control.Exception.
These functions provide retrying, showing in the presence of exceptions,
and functions to catch/ignore exceptions, including monomorphic (no Exception
context) versions.
If you want to use a safer set of exceptions see the safe-exceptions package.
Synopsis
- module Control.Exception
- type Partial = HasCallStack
- retry :: Int -> IO a -> IO a
- retryBool :: Exception e => (e -> Bool) -> Int -> IO a -> IO a
- errorWithoutStackTrace :: [Char] -> a
- showException :: Show e => e -> IO String
- stringException :: String -> IO String
- errorIO :: Partial => String -> IO a
- ignore :: IO () -> IO ()
- catch_ :: IO a -> (SomeException -> IO a) -> IO a
- handle_ :: (SomeException -> IO a) -> IO a -> IO a
- try_ :: IO a -> IO (Either SomeException a)
- catchJust_ :: (SomeException -> Maybe b) -> IO a -> (b -> IO a) -> IO a
- handleJust_ :: (SomeException -> Maybe b) -> (b -> IO a) -> IO a -> IO a
- tryJust_ :: (SomeException -> Maybe b) -> IO a -> IO (Either b a)
- catchBool :: Exception e => (e -> Bool) -> IO a -> (e -> IO a) -> IO a
- handleBool :: Exception e => (e -> Bool) -> (e -> IO a) -> IO a -> IO a
- tryBool :: Exception e => (e -> Bool) -> IO a -> IO (Either e a)
Documentation
module Control.Exception
type Partial = HasCallStack Source #
A constraint which documents that a function is partial, and on GHC 8.0 and above produces a stack trace on failure. For example:
myHead :: Partial
=> [a] -> a
myHead [] = error "bad"
myHead (x:xs) = x
When using Partial
with GHC 7.8 or below you need to enable the
language feature ConstraintKinds
, e.g. {-# LANGUAGE ConstraintKinds #-}
at the top of the file.
retry :: Int -> IO a -> IO a Source #
Retry an operation at most n times (n must be positive). If the operation fails the nth time it will throw that final exception.
retry 1 (print "x") == print "x" retry 3 (fail "die") == fail "die"
retryBool :: Exception e => (e -> Bool) -> Int -> IO a -> IO a Source #
Retry an operation at most n times (n must be positive), while the exception value and type match a predicate. If the operation fails the nth time it will throw that final exception.
errorWithoutStackTrace :: [Char] -> a #
A variant of error
that does not produce a stack trace.
Since: base-4.9.0.0
showException :: Show e => e -> IO String Source #
Show a value, but if the result contains exceptions, produce
<Exception>
. Defined as
.
Particularly useful for printing exceptions to users, remembering that exceptions
can themselves contain undefined values.stringException
. show
stringException :: String -> IO String Source #
Fully evaluate an input String. If the String contains embedded exceptions it will produce <Exception>
.
stringException "test" == pure "test" stringException ("test" ++ undefined) == pure "test<Exception>" stringException ("test" ++ undefined ++ "hello") == pure "test<Exception>" stringException ['t','e','s','t',undefined] == pure "test<Exception>"
Exception catching/ignoring
ignore :: IO () -> IO () Source #
Ignore any exceptions thrown by the action.
ignore (print 1) == print 1 ignore (fail "die") == pure ()
catch_ :: IO a -> (SomeException -> IO a) -> IO a Source #
A version of catch
without the Exception
context, restricted to SomeException
,
so catches all exceptions.
catchJust_ :: (SomeException -> Maybe b) -> IO a -> (b -> IO a) -> IO a Source #
handleJust_ :: (SomeException -> Maybe b) -> (b -> IO a) -> IO a -> IO a Source #
Like catch_
but for handleJust
catchBool :: Exception e => (e -> Bool) -> IO a -> (e -> IO a) -> IO a Source #
Catch an exception if the predicate passes, then call the handler with the original exception. As an example:
readFileExists x == catchBool isDoesNotExistError (readFile "myfile") (const $ pure "")