{-# LANGUAGE Trustworthy #-}{-# LANGUAGE NoImplicitPrelude, MagicHash #-}{-# LANGUAGE StandaloneDeriving #-}------------------------------------------------------------------------------- |-- Module : Control.Exception.Base-- 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)---- Extensible exceptions, except for multiple handlers.-------------------------------------------------------------------------------moduleControl.Exception.Base(-- * The Exception typeSomeException (..),Exception (..),IOException ,ArithException (..),ArrayException (..),AssertionFailed (..),SomeAsyncException (..),AsyncException (..),asyncExceptionToException ,asyncExceptionFromException ,NonTermination (..),NestedAtomically (..),BlockedIndefinitelyOnMVar (..),BlockedIndefinitelyOnSTM (..),AllocationLimitExceeded (..),CompactionFailed (..),Deadlock (..),NoMethodError (..),PatternMatchFail (..),RecConError (..),RecSelError (..),RecUpdError (..),ErrorCall (..),TypeError (..),-- #10284, custom error type for deferred type errors-- * Throwing exceptionsthrowIO ,throw ,ioError ,throwTo ,-- * Catching Exceptions-- ** The @catch@ functionscatch ,catchJust ,-- ** The @handle@ functionshandle ,handleJust ,-- ** The @try@ functionstry ,tryJust ,onException ,-- ** The @evaluate@ functionevaluate ,-- ** The @mapException@ functionmapException ,-- * Asynchronous Exceptions-- ** Asynchronous exception controlmask ,mask_ ,uninterruptibleMask ,uninterruptibleMask_ ,MaskingState (..),getMaskingState ,-- * Assertionsassert ,-- * Utilitiesbracket ,bracket_ ,bracketOnError ,finally ,-- * Calls for GHC runtimerecSelError ,recConError ,irrefutPatError ,runtimeError ,nonExhaustiveGuardsError ,patError ,noMethodBindingError ,absentError ,typeError ,nonTermination ,nestedAtomically ,)whereimportGHC.Base importGHC.IO hiding(bracket ,finally ,onException )importGHC.IO.Exception importGHC.Exception importGHC.Show -- import GHC.Exception hiding ( Exception )importGHC.Conc.Sync importData.Either ------------------------------------------------------------------------------- Catching exceptions-- | The function 'catchJust' is like 'catch', but it takes an extra-- argument which is an /exception 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 enclosing-- 'catch', 'catchJust', etc.catchJust::Exception e =>(e ->Maybe b )-- ^ Predicate to select exceptions->IOa -- ^ Computation to run->(b ->IOa )-- ^ Handler->IOa catchJust p a handler =catch a handler' wherehandler' e =casep e ofNothing ->throwIO e Just b ->handler b -- | A version of 'catch' with the arguments swapped around; useful in-- situations where the code for the handler is shorter. For example:---- > do handle (\NonTermination -> exitWith (ExitFailure 1)) $-- > ...handle::Exception e =>(e ->IOa )->IOa ->IOa handle =flip catch -- | A version of 'catchJust' with the arguments swapped around (see-- 'handle').handleJust::Exception e =>(e ->Maybe b )->(b ->IOa )->IOa ->IOa handleJust p =flip (catchJust p )------------------------------------------------------------------------------- 'mapException'-- | This function maps one exception into another as proposed in the-- paper \"A semantics for imprecise exceptions\".-- Notice that the usage of 'unsafePerformIO' is safe here.mapException::(Exception e1 ,Exception e2 )=>(e1 ->e2 )->a ->a mapException f v =unsafePerformIO (catch (evaluate v )(\x ->throwIO (f x )))------------------------------------------------------------------------------- 'try' and variations.-- | Similar to 'catch', but returns an 'Either' result which is-- @('Right' a)@ if no exception of type @e@ was raised, or @('Left' ex)@-- if an exception of type @e@ was raised and its value is @ex@.-- 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)try::Exception e =>IOa ->IO(Either e a )try a =catch (a >>= \v ->return (Right v ))(\e ->return (Left e ))-- | A variant of 'try' that takes an exception predicate to select-- which exceptions are caught (c.f. 'catchJust'). If the exception-- does not match the predicate, it is re-thrown.tryJust::Exception e =>(e ->Maybe b )->IOa ->IO(Either b a )tryJust p a =dor <-try a caser ofRight v ->return (Right v )Left e ->casep e ofNothing ->throwIO e Just b ->return (Left b )-- | Like 'finally', but only performs the final action if there was an-- exception raised by the computation.onException::IOa ->IOb ->IOa onException io what =io `catch `\e ->do_<-what throwIO (e ::SomeException )------------------------------------------------------------------------------- Some Useful Functions-- | When you want to acquire a resource, do some work with it, and-- then release the resource, it is a good idea to use 'bracket',-- because 'bracket' 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, then 'bracket' 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 to 'bracket' are in this order so that we can partially apply-- it, e.g.:---- > withFile name mode = bracket (openFile name mode) hClose--bracket::IOa -- ^ computation to run first (\"acquire resource\")->(a ->IOb )-- ^ computation to run last (\"release resource\")->(a ->IOc )-- ^ computation to run in-between->IOc -- returns the value from the in-between computationbracket before after thing =mask $ \restore ->doa <-before r <-restore (thing a )`onException `after a _<-after a return r -- | A specialised variant of 'bracket' with just a computation to run-- afterward.--finally::IOa -- ^ computation to run first->IOb -- ^ computation to run afterward (even if an exception-- was raised)->IOa -- returns the value from the first computationa `finally `sequel =mask $ \restore ->dor <-restore a `onException `sequel _<-sequel return r -- | A variant of 'bracket' where the return value from the first computation-- is not required.bracket_::IOa ->IOb ->IOc ->IOc bracket_ before after thing =bracket before (const after )(const thing )-- | Like 'bracket', but only performs the final action if there was an-- exception raised by the in-between computation.bracketOnError::IOa -- ^ computation to run first (\"acquire resource\")->(a ->IOb )-- ^ computation to run last (\"release resource\")->(a ->IOc )-- ^ computation to run in-between->IOc -- returns the value from the in-between computationbracketOnError before after thing =mask $ \restore ->doa <-before restore (thing a )`onException `after a ------- |A pattern match failed. The @String@ gives information about the-- source location of the pattern.newtypePatternMatchFail =PatternMatchFail String -- | @since 4.0instanceShow PatternMatchFail whereshowsPrec _(PatternMatchFail err )=showString err -- | @since 4.0instanceException PatternMatchFail ------- |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. The @String@ gives information about the source-- location of the record selector.newtypeRecSelError =RecSelError String -- | @since 4.0instanceShow RecSelError whereshowsPrec _(RecSelError err )=showString err -- | @since 4.0instanceException RecSelError ------- |An uninitialised record field was used. The @String@ gives-- information about the source location where the record was-- constructed.newtypeRecConError =RecConError String -- | @since 4.0instanceShow RecConError whereshowsPrec _(RecConError err )=showString err -- | @since 4.0instanceException RecConError ------- |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. The @String@ gives information about the source-- location of the record update.newtypeRecUpdError =RecUpdError String -- | @since 4.0instanceShow RecUpdError whereshowsPrec _(RecUpdError err )=showString err -- | @since 4.0instanceException RecUpdError ------- |A class method without a definition (neither a default definition,-- nor a definition in the appropriate instance) was called. The-- @String@ gives information about which method it was.newtypeNoMethodError =NoMethodError String -- | @since 4.0instanceShow NoMethodError whereshowsPrec _(NoMethodError err )=showString err -- | @since 4.0instanceException NoMethodError ------- |An expression that didn't typecheck during compile time was called.-- This is only possible with -fdefer-type-errors. The @String@ gives-- details about the failed type check.---- @since 4.9.0.0newtypeTypeError =TypeError String -- | @since 4.9.0.0instanceShow TypeError whereshowsPrec _(TypeError err )=showString err -- | @since 4.9.0.0instanceException TypeError ------- |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.dataNonTermination =NonTermination -- | @since 4.0instanceShow NonTermination whereshowsPrec _NonTermination =showString "<<loop>>"-- | @since 4.0instanceException NonTermination ------- |Thrown when the program attempts to call @atomically@, from the @stm@-- package, inside another call to @atomically@.dataNestedAtomically =NestedAtomically -- | @since 4.0instanceShow NestedAtomically whereshowsPrec _NestedAtomically =showString "Control.Concurrent.STM.atomically was nested"-- | @since 4.0instanceException NestedAtomically -----recSelError,recConError,irrefutPatError,runtimeError,nonExhaustiveGuardsError,patError,noMethodBindingError,absentError,typeError::Addr#->a -- All take a UTF8-encoded C stringrecSelError s =throw (RecSelError ("No match in record selector "++ unpackCStringUtf8#s ))-- No location info unfortunatelyruntimeError s =errorWithoutStackTrace (unpackCStringUtf8#s )-- No location info unfortunatelyabsentError s =errorWithoutStackTrace ("Oops! Entered absent arg "++ unpackCStringUtf8#s )nonExhaustiveGuardsError s =throw (PatternMatchFail (untangle s "Non-exhaustive guards in"))irrefutPatError s =throw (PatternMatchFail (untangle s "Irrefutable pattern failed for pattern"))recConError s =throw (RecConError (untangle s "Missing field in record construction"))noMethodBindingError s =throw (NoMethodError (untangle s "No instance nor default method for class operation"))patError s =throw (PatternMatchFail (untangle s "Non-exhaustive patterns in"))typeError s =throw (TypeError (unpackCStringUtf8#s ))-- GHC's RTS calls thisnonTermination::SomeException nonTermination =toException NonTermination -- GHC's RTS calls thisnestedAtomically::SomeException nestedAtomically =toException NestedAtomically 

AltStyle によって変換されたページ (->オリジナル) /