94f01d4c344e43905620f67a7cf13b92aadbd925
[ghc-hetmet.git] / compiler / utils / Panic.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP Project, Glasgow University, 1992-2000
4 %
5
6 Defines basic funtions for printing error messages.
7
8 It's hard to put these functions anywhere else without causing
9 some unnecessary loops in the module dependency graph.
10
11 \begin{code}
12 module Panic  
13    ( 
14      GhcException(..), showGhcException, ghcError, progName, 
15      pgmError,
16
17      panic, panic#, assertPanic, trace,
18      
19      Exception.Exception(..), showException, try, tryJust, tryMost, tryUser,
20      catchJust, ioErrors, throwTo,
21
22      installSignalHandlers, interruptTargetThread
23    ) where
24
25 -- XXX This define is a bit of a hack, and should be done more nicely
26 #define FAST_STRING_NOT_NEEDED 1
27 #include "HsVersions.h"
28
29 import Config
30 import FastTypes
31
32 #ifndef mingw32_HOST_OS
33 import System.Posix.Signals
34 #endif /* mingw32_HOST_OS */
35
36 #if defined(mingw32_HOST_OS) && __GLASGOW_HASKELL__ >= 603
37 import GHC.ConsoleHandler
38 #endif
39
40 import Control.Exception
41 import Control.Concurrent ( MVar, ThreadId, withMVar, newMVar )
42 import Data.Dynamic
43 import qualified Control.Exception as Exception
44 import Debug.Trace      ( trace )
45 import System.IO.Unsafe ( unsafePerformIO )
46 import System.IO.Error  ( isUserError )
47 import System.Exit
48 import System.Environment
49 \end{code}
50
51 GHC's own exception type.
52
53 \begin{code}
54 ghcError :: GhcException -> a
55 ghcError e = Exception.throwDyn e
56
57 -- error messages all take the form
58 --
59 --      <location>: <error>
60 --
61 -- If the location is on the command line, or in GHC itself, then 
62 -- <location>="ghc".  All of the error types below correspond to 
63 -- a <location> of "ghc", except for ProgramError (where the string is
64 -- assumed to contain a location already, so we don't print one).
65
66 data GhcException
67   = PhaseFailed String          -- name of phase 
68                 ExitCode        -- an external phase (eg. cpp) failed
69   | Interrupted                 -- someone pressed ^C
70   | UsageError String           -- prints the short usage msg after the error
71   | CmdLineError String         -- cmdline prob, but doesn't print usage
72   | Panic String                -- the `impossible' happened
73   | InstallationError String    -- an installation problem
74   | ProgramError String         -- error in the user's code, probably
75   deriving Eq
76
77 progName :: String
78 progName = unsafePerformIO (getProgName)
79 {-# NOINLINE progName #-}
80
81 short_usage :: String
82 short_usage = "Usage: For basic information, try the `--help' option."
83    
84 showException :: Exception.Exception -> String
85 -- Show expected dynamic exceptions specially
86 showException (Exception.DynException d) | Just e <- fromDynamic d 
87                                          = show (e::GhcException)
88 showException other_exn                  = show other_exn
89
90 instance Show GhcException where
91   showsPrec _ e@(ProgramError _) = showGhcException e
92   showsPrec _ e = showString progName . showString ": " . showGhcException e
93
94 showGhcException :: GhcException -> String -> String
95 showGhcException (UsageError str)
96    = showString str . showChar '\n' . showString short_usage
97 showGhcException (PhaseFailed phase code)
98    = showString "phase `" . showString phase . 
99      showString "' failed (exitcode = " . shows int_code . 
100      showString ")"
101   where
102     int_code = 
103       case code of
104         ExitSuccess   -> (0::Int)
105         ExitFailure x -> x
106 showGhcException (CmdLineError str)
107    = showString str
108 showGhcException (ProgramError str)
109    = showString str
110 showGhcException (InstallationError str)
111    = showString str
112 showGhcException (Interrupted)
113    = showString "interrupted"
114 showGhcException (Panic s)
115    = showString ("panic! (the 'impossible' happened)\n"
116                  ++ "  (GHC version " ++ cProjectVersion ++ " for " ++ TargetPlatform_NAME ++ "):\n\t"
117                  ++ s ++ "\n\n"
118                  ++ "Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug\n")
119
120 myMkTyConApp :: TyCon -> [TypeRep] -> TypeRep
121 #if __GLASGOW_HASKELL__ < 603
122 myMkTyConApp = mkAppTy
123 #else 
124 myMkTyConApp = mkTyConApp
125 #endif
126
127 ghcExceptionTc :: TyCon
128 ghcExceptionTc = mkTyCon "GhcException"
129 {-# NOINLINE ghcExceptionTc #-}
130 instance Typeable GhcException where
131   typeOf _ = myMkTyConApp ghcExceptionTc []
132 \end{code}
133
134 Panics and asserts.
135
136 \begin{code}
137 panic, pgmError :: String -> a
138 panic    x = Exception.throwDyn (Panic x)
139 pgmError x = Exception.throwDyn (ProgramError x)
140
141 --  #-versions because panic can't return an unboxed int, and that's
142 -- what TAG_ is with GHC at the moment.  Ugh. (Simon)
143 -- No, man -- Too Beautiful! (Will)
144
145 panic# :: String -> FastInt
146 panic# s = case (panic s) of () -> _ILIT 0
147
148 assertPanic :: String -> Int -> a
149 assertPanic file line = 
150   Exception.throw (Exception.AssertionFailed 
151            ("ASSERT failed! file " ++ file ++ ", line " ++ show line))
152 \end{code}
153
154 \begin{code}
155 -- | tryMost is like try, but passes through Interrupted and Panic
156 -- exceptions.  Used when we want soft failures when reading interface
157 -- files, for example.
158
159 tryMost :: IO a -> IO (Either Exception.Exception a)
160 tryMost action = do r <- try action; filter r
161   where
162    filter (Left e@(Exception.DynException d))
163             | Just ghc_ex <- fromDynamic d
164                 = case ghc_ex of
165                     Interrupted -> Exception.throw e
166                     Panic _     -> Exception.throw e
167                     _other      -> return (Left e)
168    filter other 
169      = return other
170
171 -- | tryUser is like try, but catches only UserErrors.
172 -- These are the ones that are thrown by the TcRn monad 
173 -- to signal an error in the program being compiled
174 tryUser :: IO a -> IO (Either Exception.Exception a)
175 tryUser action = tryJust tc_errors action
176   where 
177         tc_errors e@(Exception.IOException ioe) | isUserError ioe = Just e
178         tc_errors _other = Nothing
179 \end{code}      
180
181 Standard signal handlers for catching ^C, which just throw an
182 exception in the target thread.  The current target thread is
183 the thread at the head of the list in the MVar passed to
184 installSignalHandlers.
185
186 \begin{code}
187 installSignalHandlers :: IO ()
188 installSignalHandlers = do
189   let
190       interrupt_exn = Exception.DynException (toDyn Interrupted)
191
192       interrupt = do
193         withMVar interruptTargetThread $ \targets ->
194           case targets of
195            [] -> return ()
196            (thread:_) -> throwTo thread interrupt_exn
197   --
198 #if !defined(mingw32_HOST_OS)
199   installHandler sigQUIT (Catch interrupt) Nothing 
200   installHandler sigINT  (Catch interrupt) Nothing
201   return ()
202 #elif __GLASGOW_HASKELL__ >= 603
203   -- GHC 6.3+ has support for console events on Windows
204   -- NOTE: running GHCi under a bash shell for some reason requires
205   -- you to press Ctrl-Break rather than Ctrl-C to provoke
206   -- an interrupt.  Ctrl-C is getting blocked somewhere, I don't know
207   -- why --SDM 17/12/2004
208   let sig_handler ControlC = interrupt
209       sig_handler Break    = interrupt
210       sig_handler _        = return ()
211
212   installHandler (Catch sig_handler)
213   return ()
214 #else
215   return () -- nothing
216 #endif
217
218 {-# NOINLINE interruptTargetThread #-}
219 interruptTargetThread :: MVar [ThreadId]
220 interruptTargetThread = unsafePerformIO (newMVar [])
221 \end{code}