Don't capture error calls in tryUser
[ghc-hetmet.git] / compiler / utils / Panic.lhs
index 1a74d5d..0e049b0 100644 (file)
@@ -1,7 +1,7 @@
 %
+% (c) The University of Glasgow 2006
 % (c) The GRASP Project, Glasgow University, 1992-2000
 %
-\section{Panic error messages}
 
 Defines basic funtions for printing error messages.
 
@@ -11,13 +11,14 @@ some unnecessary loops in the module dependency graph.
 \begin{code}
 module Panic  
    ( 
-     GhcException(..), showGhcException, ghcError, progName, 
+     GhcException(..), showGhcException, throwGhcException, handleGhcException,
+     ghcError, progName,
      pgmError,
 
-     panic, panic#, assertPanic, trace,
+     panic, panicFastInt, assertPanic, trace,
      
      Exception.Exception(..), showException, try, tryJust, tryMost, tryUser,
-     catchJust, ioErrors, throwTo,
+     catchJust, throwTo,
 
      installSignalHandlers, interruptTargetThread
    ) where
@@ -28,42 +29,32 @@ import Config
 import FastTypes
 
 #ifndef mingw32_HOST_OS
-# if __GLASGOW_HASKELL__ > 504
 import System.Posix.Signals
-# else
-import Posix           ( Handler(Catch), installHandler, sigINT, sigQUIT )
-# endif /* GHC > 504 */
 #endif /* mingw32_HOST_OS */
 
-#if defined(mingw32_HOST_OS) && __GLASGOW_HASKELL__ >= 603
+#if defined(mingw32_HOST_OS)
 import GHC.ConsoleHandler
 #endif
 
-# if __GLASGOW_HASKELL__ < 500
-import EXCEPTION        ( raiseInThread )
-# else
-import EXCEPTION       ( throwTo )
-# endif /* GHC < 500 */
-
-#if __GLASGOW_HASKELL__ > 408
-import EXCEPTION       ( catchJust, tryJust, ioErrors )
-#endif
-
-import CONCURRENT      ( myThreadId, MVar, ThreadId, withMVar, newEmptyMVar )
-import DYNAMIC
-import qualified EXCEPTION as Exception
-import TRACE           ( trace )
-import UNSAFE_IO       ( unsafePerformIO )
-import IO              ( isUserError )
-
-import System
+import Exception
+import Control.Concurrent ( MVar, ThreadId, withMVar, newMVar )
+import Data.Dynamic
+import Debug.Trace     ( trace )
+import System.IO.Unsafe        ( unsafePerformIO )
+import System.IO.Error hiding ( try )
+import System.Exit
+import System.Environment
 \end{code}
 
 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
 --
@@ -85,21 +76,34 @@ 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)
 {-# NOINLINE progName #-}
 
+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
+  showsPrec _ e@(CmdLineError _) = showString "<command line>: " . showGhcException e
   showsPrec _ e = showString progName . showString ": " . showGhcException e
 
+showGhcException :: GhcException -> String -> String
 showGhcException (UsageError str)
    = showString str . showChar '\n' . showString short_usage
 showGhcException (PhaseFailed phase code)
@@ -125,31 +129,40 @@ showGhcException (Panic s)
                 ++ s ++ "\n\n"
                 ++ "Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug\n")
 
-#if __GLASGOW_HASKELL__ < 603
-myMkTyConApp = mkAppTy
-#else 
-myMkTyConApp = mkTyConApp
+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"
 {-# NOINLINE ghcExceptionTc #-}
 instance Typeable GhcException where
-  typeOf _ = myMkTyConApp ghcExceptionTc []
+  typeOf _ = mkTyConApp ghcExceptionTc []
 \end{code}
 
 Panics and asserts.
 
 \begin{code}
 panic, pgmError :: String -> a
-panic    x = Exception.throwDyn (Panic x)
-pgmError x = Exception.throwDyn (ProgramError x)
+panic    x = throwGhcException (Panic x)
+pgmError x = throwGhcException (ProgramError x)
 
 --  #-versions because panic can't return an unboxed int, and that's
 -- what TAG_ is with GHC at the moment.  Ugh. (Simon)
 -- No, man -- Too Beautiful! (Will)
 
-panic# :: String -> FastInt
-panic# s = case (panic s) of () -> _ILIT 0
+panicFastInt :: String -> FastInt
+panicFastInt s = case (panic s) of () -> _ILIT(0)
 
 assertPanic :: String -> Int -> a
 assertPanic file line = 
@@ -162,6 +175,7 @@ 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
@@ -173,37 +187,49 @@ tryMost action = do r <- try action; filter r
                    _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
+                                -- 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
+                                        -- 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 
-#if __GLASGOW_HASKELL__ > 504 || __GLASGOW_HASKELL__ < 500
        tc_errors e@(Exception.IOException ioe) | isUserError ioe = Just e
-#elif __GLASGOW_HASKELL__ == 502
-       tc_errors e@(UserError _) = Just e
-#else 
-       tc_errors e@(Exception.IOException ioe) | isUserError e = Just e
-#endif
        tc_errors _other = Nothing
-\end{code}     
-
-Compatibility stuff:
-
-\begin{code}
-#if __GLASGOW_HASKELL__ <= 408
-try = Exception.tryAllIO
 #else
-try = Exception.try
-#endif
-
-#if __GLASGOW_HASKELL__ <= 408
-catchJust = Exception.catchIO
-tryJust   = Exception.tryIO
-ioErrors  = Exception.justIoErrors
-throwTo   = Exception.raiseInThread
+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
+                   Just ioe
+                    | isUserError ioe ->
+                       return (Left ioe)
+                   _ -> throw se
 #endif
 \end{code}
 
@@ -216,7 +242,11 @@ 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 ->
@@ -228,7 +258,7 @@ installSignalHandlers = do
   installHandler sigQUIT (Catch interrupt) Nothing 
   installHandler sigINT  (Catch interrupt) Nothing
   return ()
-#elif __GLASGOW_HASKELL__ >= 603
+#else
   -- GHC 6.3+ has support for console events on Windows
   -- NOTE: running GHCi under a bash shell for some reason requires
   -- you to press Ctrl-Break rather than Ctrl-C to provoke
@@ -240,11 +270,9 @@ installSignalHandlers = do
 
   installHandler (Catch sig_handler)
   return ()
-#else
-  return () -- nothing
 #endif
 
 {-# NOINLINE interruptTargetThread #-}
 interruptTargetThread :: MVar [ThreadId]
-interruptTargetThread = unsafePerformIO newEmptyMVar
+interruptTargetThread = unsafePerformIO (newMVar [])
 \end{code}