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