| Copyright | (c) The University of Glasgow 2001 |
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) |
| Maintainer | libraries@haskell.org |
| Stability | experimental |
| Portability | non-portable (extended exceptions) |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Control.Exception.Base
Contents
Description
Extensible exceptions, except for multiple handlers.
TheSomeException type is the root of the exception type hierarchy.When an exception of typee is thrown, behind the scenes it isencapsulated in aSomeException.
Constructors
| Exception e =>SomeException e |
| ShowSomeExceptionSource# | Since: 3.0 |
Instance detailsDefined inGHC.Exception.Type | |
| ExceptionSomeExceptionSource# | Since: 3.0 |
Instance detailsDefined inGHC.Exception.Type | |
class (Typeable e,Show e) =>Exception ewhereSource#
Any type that you wish to throw or catch as an exception must be aninstance of theException class. The simplest case is a new exceptiontype directly below the root:
data MyException = ThisException | ThatException deriving Showinstance Exception MyException
The default method definitions in theException class do what we needin this case. You can now throw and catchThisException andThatException as exceptions:
*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))Caught ThisExceptionIn more complicated examples, you may wish to define a whole hierarchyof exceptions:
----------------------------------------------------------------------- Make the root exception type for all the exceptions in a compilerdata SomeCompilerException = forall e . Exception e => SomeCompilerException einstance Show SomeCompilerException where show (SomeCompilerException e) = show einstance Exception SomeCompilerExceptioncompilerExceptionToException :: Exception e => e -> SomeExceptioncompilerExceptionToException = toException . SomeCompilerExceptioncompilerExceptionFromException :: Exception e => SomeException -> Maybe ecompilerExceptionFromException x = do SomeCompilerException a <- fromException x cast a----------------------------------------------------------------------- Make a subhierarchy for exceptions in the frontend of the compilerdata SomeFrontendException = forall e . Exception e => SomeFrontendException einstance Show SomeFrontendException where show (SomeFrontendException e) = show einstance Exception SomeFrontendException where toException = compilerExceptionToException fromException = compilerExceptionFromExceptionfrontendExceptionToException :: Exception e => e -> SomeExceptionfrontendExceptionToException = toException . SomeFrontendExceptionfrontendExceptionFromException :: Exception e => SomeException -> Maybe efrontendExceptionFromException x = do SomeFrontendException a <- fromException x cast a----------------------------------------------------------------------- Make an exception type for a particular frontend compiler exceptiondata MismatchedParentheses = MismatchedParentheses deriving Showinstance Exception MismatchedParentheses where toException = frontendExceptionToException fromException = frontendExceptionFromException
We can now catch aMismatchedParentheses exception asMismatchedParentheses,SomeFrontendException orSomeCompilerException, but not other types, e.g.IOException:
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))Caught MismatchedParentheses*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))Caught MismatchedParentheses*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))Caught MismatchedParentheses*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException))*** Exception: MismatchedParenthesesMinimal complete definition
Nothing
Methods
toException :: e ->SomeExceptionSource#
fromException ::SomeException ->Maybe eSource#
displayException :: e ->StringSource#
Exceptions that occur in theIO monad. AnIOException records a more specific error type, a descriptive string and maybe the handle that was used when the error was flagged.
| EqIOExceptionSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| ShowIOExceptionSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| ExceptionIOExceptionSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
Arithmetic exceptions.
Constructors
| Overflow | |
| Underflow | |
| LossOfPrecision | |
| DivideByZero | |
| Denormal | |
| RatioZeroDenominator | Since: 4.6.0.0 |
| EqArithExceptionSource# | Since: 3.0 |
Instance detailsDefined inGHC.Exception.Type | |
| OrdArithExceptionSource# | Since: 3.0 |
Instance detailsDefined inGHC.Exception.Type Methods compare ::ArithException ->ArithException ->Ordering# (<) ::ArithException ->ArithException ->Bool# (<=) ::ArithException ->ArithException ->Bool# (>) ::ArithException ->ArithException ->Bool# (>=) ::ArithException ->ArithException ->Bool# | |
| ShowArithExceptionSource# | Since: 4.0.0.0 |
Instance detailsDefined inGHC.Exception.Type | |
| ExceptionArithExceptionSource# | Since: 4.0.0.0 |
Instance detailsDefined inGHC.Exception.Type | |
Exceptions generated by array operations
Constructors
| IndexOutOfBoundsString | An attempt was made to index an array outside its declared bounds. |
| UndefinedElementString | An attempt was made to evaluate an element of an array that had not been initialized. |
| EqArrayExceptionSource# | Since: 4.2.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| OrdArrayExceptionSource# | Since: 4.2.0.0 |
Instance detailsDefined inGHC.IO.Exception Methods compare ::ArrayException ->ArrayException ->Ordering# (<) ::ArrayException ->ArrayException ->Bool# (<=) ::ArrayException ->ArrayException ->Bool# (>) ::ArrayException ->ArrayException ->Bool# (>=) ::ArrayException ->ArrayException ->Bool# | |
| ShowArrayExceptionSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| ExceptionArrayExceptionSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
newtypeAssertionFailedSource#
Constructors
| AssertionFailedString |
| ShowAssertionFailedSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| ExceptionAssertionFailedSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
Superclass for asynchronous exceptions.
Since: 4.7.0.0
Constructors
| Exception e =>SomeAsyncException e |
| ShowSomeAsyncExceptionSource# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| ExceptionSomeAsyncExceptionSource# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
Asynchronous exceptions.
Constructors
| StackOverflow | The current thread's stack exceeded its limit. Since an exception has been raised, the thread's stack will certainly be below its limit again, but the programmer should take remedial action immediately. |
| HeapOverflow | The program's heap is reaching its limit, and the program should take action to reduce the amount of live data it has. Notes:
|
| ThreadKilled | This exception is raised by another thread calling |
| UserInterrupt | This exception is raised by default in the main thread of the program when the user requests to terminate the program via the usual mechanism(s) (e.g. Control-C in the console). |
| EqAsyncExceptionSource# | Since: 4.2.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| OrdAsyncExceptionSource# | Since: 4.2.0.0 |
Instance detailsDefined inGHC.IO.Exception Methods compare ::AsyncException ->AsyncException ->Ordering# (<) ::AsyncException ->AsyncException ->Bool# (<=) ::AsyncException ->AsyncException ->Bool# (>) ::AsyncException ->AsyncException ->Bool# (>=) ::AsyncException ->AsyncException ->Bool# | |
| ShowAsyncExceptionSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| ExceptionAsyncExceptionSource# | Since: 4.7.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
asyncExceptionToException ::Exception e => e ->SomeExceptionSource#
Since: 4.7.0.0
asyncExceptionFromException ::Exception e =>SomeException ->Maybe eSource#
Since: 4.7.0.0
Thrown when the runtime system detects that the computation is guaranteed not to terminate. Note that there is no guarantee that the runtime system will notice whether any given computation is guaranteed to terminate or not.
Constructors
| NonTermination |
| ShowNonTerminationSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
| ExceptionNonTerminationSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
Thrown when the program attempts to callatomically, from thestm package, inside another call toatomically.
Constructors
| NestedAtomically |
| ShowNestedAtomicallySource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
| ExceptionNestedAtomicallySource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
dataBlockedIndefinitelyOnMVarSource#
The thread is blocked on anMVar, but there are no other references to theMVar so it can't ever continue.
Constructors
| BlockedIndefinitelyOnMVar |
| ShowBlockedIndefinitelyOnMVarSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| ExceptionBlockedIndefinitelyOnMVarSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
The exception thrown when an infinite cycle is detected infixIO.
Since: 4.11.0.0
Constructors
| FixIOException |
| ShowFixIOExceptionSource# | Since: 4.11.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| ExceptionFixIOExceptionSource# | Since: 4.11.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
dataBlockedIndefinitelyOnSTMSource#
The thread is waiting to retry an STM transaction, but there are no other references to anyTVars involved, so it can't ever continue.
Constructors
| BlockedIndefinitelyOnSTM |
| ShowBlockedIndefinitelyOnSTMSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| ExceptionBlockedIndefinitelyOnSTMSource# | Since: 4.1.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
dataAllocationLimitExceededSource#
This thread has exceeded its allocation limit. SeesetAllocationCounter andenableAllocationLimit.
Since: 4.8.0.0
Constructors
| AllocationLimitExceeded |
| ShowAllocationLimitExceededSource# | Since: 4.7.1.0 |
Instance detailsDefined inGHC.IO.Exception | |
| ExceptionAllocationLimitExceededSource# | Since: 4.8.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
newtypeCompactionFailedSource#
Compaction found an object that cannot be compacted. Functions cannot be compacted, nor can mutable objects or pinned objects. Seecompact.
Since: 4.10.0.0
Constructors
| CompactionFailedString |
| ShowCompactionFailedSource# | Since: 4.10.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
| ExceptionCompactionFailedSource# | Since: 4.10.0.0 |
Instance detailsDefined inGHC.IO.Exception | |
There are no runnable threads, so the program is deadlocked. TheDeadlock exception is raised in the main thread only.
Constructors
| Deadlock |
newtypeNoMethodErrorSource#
A class method without a definition (neither a default definition, nor a definition in the appropriate instance) was called. TheString gives information about which method it was.
Constructors
| NoMethodErrorString |
| ShowNoMethodErrorSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
| ExceptionNoMethodErrorSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
newtypePatternMatchFailSource#
A pattern match failed. TheString gives information about the source location of the pattern.
Constructors
| PatternMatchFailString |
| ShowPatternMatchFailSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
| ExceptionPatternMatchFailSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
newtypeRecConErrorSource#
An uninitialised record field was used. TheString gives information about the source location where the record was constructed.
Constructors
| RecConErrorString |
| ShowRecConErrorSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
| ExceptionRecConErrorSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
newtypeRecSelErrorSource#
A record selector was applied to a constructor without the appropriate field. This can only happen with a datatype with multiple constructors, where some fields are in one constructor but not another. TheString gives information about the source location of the record selector.
Constructors
| RecSelErrorString |
| ShowRecSelErrorSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
| ExceptionRecSelErrorSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
newtypeRecUpdErrorSource#
A record update was performed on a constructor without the appropriate field. This can only happen with a datatype with multiple constructors, where some fields are in one constructor but not another. TheString gives information about the source location of the record update.
Constructors
| RecUpdErrorString |
| ShowRecUpdErrorSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
| ExceptionRecUpdErrorSource# | Since: 4.0 |
Instance detailsDefined inControl.Exception.Base | |
This is thrown when the user callserror. The firstString is the argument given toerror, secondString is the location.
Constructors
| ErrorCallWithLocationStringString |
An expression that didn't typecheck during compile time was called. This is only possible with -fdefer-type-errors. TheString gives details about the failed type check.
Since: 4.9.0.0
throwIO ::Exception e => e ->IO aSource#
A variant ofthrow that can only be used within theIO monad.
AlthoughthrowIO has a type that is an instance of the type ofthrow, the two functions are subtly different:
throw e `seq` x ===> throw ethrowIO e `seq` x ===> x
The first example will cause the exceptione to be raised, whereas the second one won't. In fact,throwIO will only cause an exception to be raised when it is used within theIO monad. ThethrowIO variant should be used in preference tothrow to raise an exception within theIO monad because it guarantees ordering with respect to otherIO operations, whereasthrow does not.
throw ::forall (r ::RuntimeRep).forall (a ::TYPE r).forall e.Exception e => e -> aSource#
Throw an exception. Exceptions may be thrown from purely functional code, but may only be caught within theIO monad.
throwTo ::Exception e =>ThreadId -> e ->IO ()Source#
throwTo raises an arbitrary exception in the target thread (GHC only).
Exception delivery synchronizes between the source and target thread:throwTo does not return until the exception has been raised in thetarget thread. The calling thread can thus be certain that the targetthread has received the exception. Exception delivery is also atomicwith respect to other exceptions. Atomicity is a useful property to havewhen dealing with race conditions: e.g. if there are two threads thatcan kill each other, it is guaranteed that only one of the threadswill get to kill the other.
Whatever work the target thread was doing when the exception wasraised is not lost: the computation is suspended until required byanother thread.
If the target thread is currently making a foreign call, then theexception will not be raised (and hencethrowTo will not return)until the call has completed. This is the case regardless of whetherthe call is inside amask or not. However, in GHC a foreign callcan be annotated asinterruptible, in which case athrowTo willcause the RTS to attempt to cause the call to return; see the GHCdocumentation for more details.
Important note: the behaviour ofthrowTo differs from that described inthe paper "Asynchronous exceptions in Haskell"(http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm).In the paper,throwTo is non-blocking; but the library implementation adoptsa more synchronous design in whichthrowTo does not return until the exceptionis received by the target thread. The trade-off is discussed in Section 9 of the paper.Like any blocking operation,throwTo is therefore interruptible (see Section 5.3 ofthe paper). Unlike other interruptible operations, however,throwToisalways interruptible, even if it does not actually block.
There is no guarantee that the exception will be delivered promptly,although the runtime will endeavour to ensure that arbitrarydelays don't occur. In GHC, an exception can only be raised when athread reaches asafe point, where a safe point is where memoryallocation occurs. Some loops do not perform any memory allocationinside the loop and therefore cannot be interrupted by athrowTo.
If the target ofthrowTo is the calling thread, then the behaviouris the same asthrowIO, except that the exceptionis thrown as an asynchronous exception. This means that if there isan enclosing pure computation, which would be the case if the currentIO operation is insideunsafePerformIO orunsafeInterleaveIO, thatcomputation is not permanently replaced by the exception, but issuspended as if it had received an asynchronous exception.
Note that ifthrowTo is called with the current thread as thetarget, the exception will be thrown even if the thread is currentlyinsidemask oruninterruptibleMask.
catch functionsArguments
| ::Exception e | |
| =>IO a | The computation to run |
| -> (e ->IO a) | Handler to invoke if an exception is raised |
| ->IO a |
This is the simplest of the exception-catching functions. It takes a single argument, runs it, and if an exception is raised the "handler" is executed, with the value of the exception passed as an argument. Otherwise, the result is returned as normal. For example:
catch (readFile f) (\e -> do let err = show (e :: IOException) hPutStr stderr ("Warning: Couldn't open " ++ f ++ ": " ++ err) return "")Note that we have to give a type signature toe, or the program will not typecheck as the type is ambiguous. While it is possible to catch exceptions of any type, see the section "Catching all exceptions" (inControl.Exception) for an explanation of the problems with doing so.
For catching exceptions in pure (non-IO) expressions, see the functionevaluate.
Note that due to Haskell's unspecified evaluation order, an expression may throw one of several possible exceptions: consider the expression(error "urk") + (1 `div` 0). Does the expression throwErrorCall "urk", orDivideByZero?
The answer is "it might throw either"; the choice is non-deterministic. If you are catching any type of exception then you might catch either. If you are callingcatch with typeIO Int -> (ArithException -> IO Int) -> IO Int then the handler may get run withDivideByZero as an argument, or anErrorCall "urk" exception may be propogated further up. If you call it again, you might get a the opposite behaviour. This is ok, becausecatch is anIO computation.
Arguments
| ::Exception e | |
| => (e ->Maybe b) | Predicate to select exceptions |
| ->IO a | Computation to run |
| -> (b ->IO a) | Handler |
| ->IO a |
The functioncatchJust is likecatch, but it takes an extra argument which is anexception predicate, a function which selects which type of exceptions we're interested in.
catchJust (\e -> if isDoesNotExistErrorType (ioeGetErrorType e) then Just () else Nothing) (readFile f) (\_ -> do hPutStrLn stderr ("No such file: " ++ show f) return "")Any other exceptions which are not matched by the predicate are re-raised, and may be caught by an enclosingcatch,catchJust, etc.
handle functionshandle ::Exception e => (e ->IO a) ->IO a ->IO aSource#
A version ofcatch with the arguments swapped around; useful in situations where the code for the handler is shorter. For example:
do handle (\NonTermination -> exitWith (ExitFailure 1)) $ ...
try functionstry ::Exception e =>IO a ->IO (Either e a)Source#
Similar tocatch, but returns anEither result which is( if no exception of typeRight a)e was raised, or( if an exception of typeLeft ex)e was raised and its value isex. If any other type of exception is raised than it will be propogated up to the next enclosing exception handler.
try a = catch (Right `liftM` a) (return . Left)
onException ::IO a ->IO b ->IO aSource#
Likefinally, but only performs the final action if there was an exception raised by the computation.
evaluate functionEvaluate the argument to weak head normal form.
evaluate is typically used to uncover any exceptions that a lazy value may contain, and possibly handle them.
evaluate only evaluates toweak head normal form. If deeper evaluation is needed, theforce function fromControl.DeepSeq may be handy:
evaluate $ force x
There is a subtle difference between andevaluate x, analogous to the difference betweenreturn$! xthrowIO andthrow. If the lazy valuex throws an exception, will fail to return anreturn$! xIO action and will throw an exception instead., on the other hand, always produces anevaluate xIO action; that action will throw an exception uponexecution iffx throws an exception uponevaluation.
The practical implication of this difference is that due to theimprecise exceptions semantics,
(return $! error "foo") >> error "bar"
may throw either"foo" or"bar", depending on the optimizations performed by the compiler. On the other hand,
evaluate (error "foo") >> error "bar"
is guaranteed to throw"foo".
The rule of thumb is to useevaluate to force or handle exceptions in lazy values. If, on the other hand, you are forcing a lazy value for efficiency reasons only and do not care about exceptions, you may use.return$! x
mapException functionmapException :: (Exception e1,Exception e2) => (e1 -> e2) -> a -> aSource#
This function maps one exception into another as proposed in the paper "A semantics for imprecise exceptions".
mask :: ((forall a.IO a ->IO a) ->IO b) ->IO bSource#
Executes an IO computation with asynchronous exceptionsmasked. That is, any thread which attempts to raise an exception in the current thread withthrowTo will be blocked until asynchronous exceptions are unmasked again.
The argument passed tomask is a function that takes as its argument another function, which can be used to restore the prevailing masking state within the context of the masked computation. For example, a common way to usemask is to protect the acquisition of a resource:
mask $ \restore -> do x <- acquire restore (do_something_with x) `onException` release release
This code guarantees thatacquire is paired withrelease, by masking asynchronous exceptions for the critical parts. (Rather than write this code yourself, it would be better to usebracket which abstracts the general pattern).
Note that therestore action passed to the argument tomask does not necessarily unmask asynchronous exceptions, it just restores the masking state to that of the enclosing context. Thus if asynchronous exceptions are already masked,mask cannot be used to unmask exceptions again. This is so that if you call a library function with exceptions masked, you can be sure that the library call will not be able to unmask exceptions again. If you are writing library code and need to use asynchronous exceptions, the only way is to create a new thread; seeforkIOWithUnmask.
Asynchronous exceptions may still be received while in the masked state if the masked threadblocks in certain ways; seeControl.Exception.
Threads created byforkIO inherit theMaskingState from the parent; that is, to start a thread in theMaskedInterruptible state, usemask_ $ forkIO .... This is particularly useful if you need to establish an exception handler in the forked thread before any asynchronous exceptions are received. To create a new thread in an unmasked state useforkIOWithUnmask.
uninterruptibleMask :: ((forall a.IO a ->IO a) ->IO b) ->IO bSource#
Likemask, but the masked computation is not interruptible (seeControl.Exception). THIS SHOULD BE USED WITH GREAT CARE, because if a thread executing inuninterruptibleMask blocks for any reason, then the thread (and possibly the program, if this is the main thread) will be unresponsive and unkillable. This function should only be necessary if you need to mask exceptions around an interruptible operation, and you can guarantee that the interruptible operation will only block for a short period of time.
uninterruptibleMask_ ::IO a ->IO aSource#
LikeuninterruptibleMask, but does not pass arestore action to the argument.
Describes the behaviour of a thread when an asynchronous exception is received.
Constructors
| Unmasked | asynchronous exceptions are unmasked (the normal state) |
| MaskedInterruptible | the state during |
| MaskedUninterruptible | the state during |
| EqMaskingStateSource# | Since: 4.3.0.0 |
Instance detailsDefined inGHC.IO | |
| ShowMaskingStateSource# | Since: 4.3.0.0 |
getMaskingState ::IOMaskingStateSource#
Returns theMaskingState for the current thread.
assert ::Bool -> a -> aSource#
If the first argument evaluates toTrue, then the result is the second argument. Otherwise anAssertionFailed exception is raised, containing aString with the source file and line number of the call toassert.
Assertions can normally be turned on or off with a compiler flag (for GHC, assertions are normally on unless optimisation is turned on with-O or the-fignore-asserts option is given). When assertions are turned off, the first argument toassert is ignored, and the second argument is returned as the result.
Arguments
| ::IO a | computation to run first ("acquire resource") |
| -> (a ->IO b) | computation to run last ("release resource") |
| -> (a ->IO c) | computation to run in-between |
| ->IO c |
When you want to acquire a resource, do some work with it, and then release the resource, it is a good idea to usebracket, becausebracket will install the necessary exception handler to release the resource in the event that an exception is raised during the computation. If an exception is raised, thenbracket will re-raise the exception (after performing the release).
A common example is opening a file:
bracket (openFile "filename" ReadMode) (hClose) (\fileHandle -> do { ... })The arguments tobracket are in this order so that we can partially apply it, e.g.:
withFile name mode = bracket (openFile name mode) hClose
bracket_ ::IO a ->IO b ->IO c ->IO cSource#
A variant ofbracket where the return value from the first computation is not required.
Arguments
| ::IO a | computation to run first ("acquire resource") |
| -> (a ->IO b) | computation to run last ("release resource") |
| -> (a ->IO c) | computation to run in-between |
| ->IO c |
Likebracket, but only performs the final action if there was an exception raised by the in-between computation.
Arguments
| ::IO a | computation to run first |
| ->IO b | computation to run afterward (even if an exception was raised) |
| ->IO a |
A specialised variant ofbracket with just a computation to run afterward.
recSelError ::Addr# -> aSource#
recConError ::Addr# -> aSource#
runtimeError ::Addr# -> aSource#
noMethodBindingError ::Addr# -> aSource#
absentError ::Addr# -> aSource#
Produced byHaddock version 2.20.0