diff options
author | Ian Lynagh <igloo@earth.li> | 2008-10-03 14:02:16 +0000 |
---|---|---|
committer | Ian Lynagh <igloo@earth.li> | 2008-10-03 14:02:16 +0000 |
commit | 1f3a7730cd7f831344d2a3b74a0ce700c382e858 (patch) | |
tree | fc77a60a3cde863e0beb8810f48330200f455e22 /compiler/utils | |
parent | 08a9d7341402232672fcff9062454e6ba1ae8bd1 (diff) | |
download | haskell-1f3a7730cd7f831344d2a3b74a0ce700c382e858.tar.gz |
Use an extensible-exceptions package when bootstrapping
Ifdefs for whether we had extensible exceptions or not were spreading
through GHC's source, and things would only have got worse for the next
2-3 years, so instead we now use an implementation of extensible
exceptions built on top of the old exception type.
Diffstat (limited to 'compiler/utils')
-rw-r--r-- | compiler/utils/Exception.hs | 46 | ||||
-rw-r--r-- | compiler/utils/IOEnv.hs | 4 | ||||
-rw-r--r-- | compiler/utils/Panic.lhs | 61 |
3 files changed, 10 insertions, 101 deletions
diff --git a/compiler/utils/Exception.hs b/compiler/utils/Exception.hs index 8d5d4389b6..32422920ac 100644 --- a/compiler/utils/Exception.hs +++ b/compiler/utils/Exception.hs @@ -7,40 +7,21 @@ module Exception where import Prelude hiding (catch) -import Control.Exception #if __GLASGOW_HASKELL__ < 609 -import Data.Typeable ( Typeable ) - -type SomeException = Exception - -onException :: IO a -> IO () -> IO a -onException io what = io `catch` \e -> do what - throw e +import Control.Exception.Extensible as Control.Exception +#else +import Control.Exception #endif catchIO :: IO a -> (IOException -> IO a) -> IO a -#if __GLASGOW_HASKELL__ >= 609 catchIO = catch -#else -catchIO io handler = io `catch` handler' - where handler' (IOException ioe) = handler ioe - handler' e = throw e -#endif handleIO :: (IOException -> IO a) -> IO a -> IO a handleIO = flip catchIO tryIO :: IO a -> IO (Either IOException a) -#if __GLASGOW_HASKELL__ >= 609 tryIO = try -#else -tryIO io = do ei <- try io - case ei of - Right v -> return (Right v) - Left (IOException ioe) -> return (Left ioe) - Left e -> throwIO e -#endif -- | A monad that can catch exceptions. A minimal definition -- requires a definition of 'gcatch'. @@ -51,12 +32,7 @@ tryIO io = do ei <- try io class Monad m => ExceptionMonad m where -- | Generalised version of 'Control.Exception.catch', allowing an arbitrary -- exception handling monad instead of just 'IO'. -#if __GLASGOW_HASKELL__ >= 609 gcatch :: Exception e => m a -> (e -> m a) -> m a -#else - gcatch :: m a -> (Exception -> m a) -> m a - gcatchDyn :: Typeable e => m a -> (e -> m a) -> m a -#endif -- | Generalised version of 'Control.Exception.bracket', allowing an arbitrary -- exception handling monad instead of just 'IO'. @@ -79,28 +55,17 @@ class Monad m => ExceptionMonad m where instance ExceptionMonad IO where gcatch = catch -#if __GLASGOW_HASKELL__ < 609 - gcatchDyn = catchDyn -#endif gbracket = bracket gfinally = finally -#if __GLASGOW_HASKELL__ >= 609 gtry :: (ExceptionMonad m, Exception e) => m a -> m (Either e a) -#else -gtry :: (ExceptionMonad m) => m a -> m (Either Exception a) -#endif gtry act = gcatch (act >>= \a -> return (Right a)) (\e -> return (Left e)) -- | Generalised version of 'Control.Exception.handle', allowing an arbitrary -- exception handling monad instead of just 'IO'. -#if __GLASGOW_HASKELL__ >= 609 ghandle :: (ExceptionMonad m, Exception e) => (e -> m a) -> m a -> m a -#else -ghandle :: (ExceptionMonad m) => (Exception -> m a) -> m a -> m a -#endif ghandle = flip gcatch -- | Always executes the first argument. If this throws an exception the @@ -108,8 +73,5 @@ ghandle = flip gcatch gonException :: (ExceptionMonad m) => m a -> m b -> m a gonException ioA cleanup = ioA `gcatch` \e -> do cleanup -#if __GLASGOW_HASKELL__ >= 609 throw (e :: SomeException) -#else - throw e -#endif + diff --git a/compiler/utils/IOEnv.hs b/compiler/utils/IOEnv.hs index 394a1c8f45..9332a8b363 100644 --- a/compiler/utils/IOEnv.hs +++ b/compiler/utils/IOEnv.hs @@ -95,11 +95,7 @@ fixM f = IOEnv (\ env -> fixIO (\ r -> unIOEnv (f r) env)) --------------------------- -#if __GLASGOW_HASKELL__ < 609 -tryM :: IOEnv env r -> IOEnv env (Either Exception r) -#else tryM :: IOEnv env r -> IOEnv env (Either IOException r) -#endif -- Reflect UserError exceptions (only) into IOEnv monad -- Other exceptions are not caught; they are simply propagated as exns -- diff --git a/compiler/utils/Panic.lhs b/compiler/utils/Panic.lhs index 0e049b0cfb..e6c385c7d2 100644 --- a/compiler/utils/Panic.lhs +++ b/compiler/utils/Panic.lhs @@ -17,8 +17,7 @@ module Panic panic, panicFastInt, assertPanic, trace, - Exception.Exception(..), showException, try, tryJust, tryMost, tryUser, - catchJust, throwTo, + Exception.Exception(..), showException, try, tryMost, tryUser, throwTo, installSignalHandlers, interruptTargetThread ) where @@ -50,11 +49,7 @@ GHC's own exception type. \begin{code} ghcError :: GhcException -> a -#if __GLASGOW_HASKELL__ >= 609 ghcError e = Exception.throw e -#else -ghcError e = Exception.throwDyn e -#endif -- error messages all take the form -- @@ -76,9 +71,7 @@ data GhcException | ProgramError String -- error in the user's code, probably deriving Eq -#if __GLASGOW_HASKELL__ >= 609 instance Exception GhcException -#endif progName :: String progName = unsafePerformIO (getProgName) @@ -87,16 +80,8 @@ progName = unsafePerformIO (getProgName) short_usage :: String short_usage = "Usage: For basic information, try the `--help' option." -#if __GLASGOW_HASKELL__ < 609 -showException :: Exception.Exception -> String --- Show expected dynamic exceptions specially -showException (Exception.DynException d) | Just e <- fromDynamic d - = show (e::GhcException) -showException other_exn = show other_exn -#else showException :: Exception e => e -> String showException = show -#endif instance Show GhcException where showsPrec _ e@(ProgramError _) = showGhcException e @@ -130,18 +115,10 @@ showGhcException (Panic s) ++ "Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug\n") throwGhcException :: GhcException -> a -#if __GLASGOW_HASKELL__ < 609 -throwGhcException = Exception.throwDyn -#else throwGhcException = Exception.throw -#endif handleGhcException :: ExceptionMonad m => (GhcException -> m a) -> m a -> m a -#if __GLASGOW_HASKELL__ < 609 -handleGhcException = flip gcatchDyn -#else handleGhcException = ghandle -#endif ghcExceptionTc :: TyCon ghcExceptionTc = mkTyCon "GhcException" @@ -175,62 +152,40 @@ assertPanic file line = -- exceptions. Used when we want soft failures when reading interface -- files, for example. -#if __GLASGOW_HASKELL__ < 609 -tryMost :: IO a -> IO (Either Exception.Exception a) -tryMost action = do r <- try action; filter r - where - filter (Left e@(Exception.DynException d)) - | Just ghc_ex <- fromDynamic d - = case ghc_ex of - Interrupted -> Exception.throw e - Panic _ -> Exception.throw e - _other -> return (Left e) - filter other - = return other -#else -- XXX I'm not entirely sure if this is catching what we really want to catch tryMost :: IO a -> IO (Either SomeException a) tryMost action = do r <- try action case r of - Left se@(SomeException e) -> - case cast e of + Left se -> + case fromException se of -- Some GhcException's we rethrow, Just Interrupted -> throwIO se Just (Panic _) -> throwIO se -- others we return Just _ -> return (Left se) Nothing -> - case cast e of + case fromException se of -- All IOExceptions are returned Just (_ :: IOException) -> return (Left se) -- Anything else is rethrown Nothing -> throwIO se Right v -> return (Right v) -#endif -- | tryUser is like try, but catches only UserErrors. -- These are the ones that are thrown by the TcRn monad -- to signal an error in the program being compiled -#if __GLASGOW_HASKELL__ < 609 -tryUser :: IO a -> IO (Either Exception.Exception a) -tryUser action = tryJust tc_errors action - where - tc_errors e@(Exception.IOException ioe) | isUserError ioe = Just e - tc_errors _other = Nothing -#else tryUser :: IO a -> IO (Either IOException a) tryUser io = do ei <- try io case ei of Right v -> return (Right v) - Left se@(SomeException ex) -> - case cast ex of + Left se -> + case fromException se of Just ioe | isUserError ioe -> return (Left ioe) _ -> throw se -#endif \end{code} Standard signal handlers for catching ^C, which just throw an @@ -242,11 +197,7 @@ installSignalHandlers. installSignalHandlers :: IO () installSignalHandlers = do let -#if __GLASGOW_HASKELL__ < 609 - interrupt_exn = Exception.DynException (toDyn Interrupted) -#else interrupt_exn = (toException Interrupted) -#endif interrupt = do withMVar interruptTargetThread $ \targets -> |