cee03cce3b5b3a4f00981bee822f119a4aad1f55
[ghc-hetmet.git] / compiler / main / ErrUtils.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1998
3 %
4 \section[ErrsUtils]{Utilities for error reporting}
5
6 \begin{code}
7 {-# OPTIONS -w #-}
8 -- The above warning supression flag is a temporary kludge.
9 -- While working on this module you are encouraged to remove it and fix
10 -- any warnings in the module. See
11 --     http://hackage.haskell.org/trac/ghc/wiki/CodingStyle#Warnings
12 -- for details
13
14 module ErrUtils (
15         Message, mkLocMessage, printError,
16         Severity(..),
17
18         ErrMsg, WarnMsg,
19         errMsgSpans, errMsgContext, errMsgShortDoc, errMsgExtraInfo,
20         Messages, errorsFound, emptyMessages,
21         mkErrMsg, mkWarnMsg, mkPlainErrMsg, mkLongErrMsg,
22         printErrorsAndWarnings, printBagOfErrors, printBagOfWarnings,
23
24         ghcExit,
25         doIfSet, doIfSet_dyn, 
26         dumpIfSet, dumpIfSet_core, dumpIfSet_dyn, dumpIfSet_dyn_or, mkDumpDoc, dumpSDoc,
27
28         --  * Messages during compilation
29         putMsg,
30         errorMsg,
31         fatalErrorMsg,
32         compilationProgressMsg,
33         showPass,
34         debugTraceMsg,  
35     ) where
36
37 #include "HsVersions.h"
38
39 import Module           ( ModLocation(..))
40 import Bag              ( Bag, bagToList, isEmptyBag, emptyBag )
41 import SrcLoc           ( SrcSpan )
42 import Util             ( sortLe )
43 import Outputable
44 import SrcLoc           ( srcSpanStart, noSrcSpan )
45 import DynFlags         ( DynFlags(..), DynFlag(..), dopt )
46 import StaticFlags      ( opt_ErrorSpans )
47
48 import System.Exit      ( ExitCode(..), exitWith )
49 import Data.Dynamic
50 import Data.List
51 import System.IO
52
53 -- -----------------------------------------------------------------------------
54 -- Basic error messages: just render a message with a source location.
55
56 type Message = SDoc
57
58 data Severity
59   = SevInfo
60   | SevWarning
61   | SevError
62   | SevFatal
63
64 mkLocMessage :: SrcSpan -> Message -> Message
65 mkLocMessage locn msg
66   | opt_ErrorSpans = hang (ppr locn <> colon) 4 msg
67   | otherwise      = hang (ppr (srcSpanStart locn) <> colon) 4 msg
68   -- always print the location, even if it is unhelpful.  Error messages
69   -- are supposed to be in a standard format, and one without a location
70   -- would look strange.  Better to say explicitly "<no location info>".
71
72 printError :: SrcSpan -> Message -> IO ()
73 printError span msg = printErrs (mkLocMessage span msg $ defaultErrStyle)
74
75
76 -- -----------------------------------------------------------------------------
77 -- Collecting up messages for later ordering and printing.
78
79 data ErrMsg = ErrMsg { 
80         errMsgSpans     :: [SrcSpan],
81         errMsgContext   :: PrintUnqualified,
82         errMsgShortDoc  :: Message,
83         errMsgExtraInfo :: Message
84         }
85         -- The SrcSpan is used for sorting errors into line-number order
86         -- NB  Pretty.Doc not SDoc: we deal with the printing style (in ptic 
87         -- whether to qualify an External Name) at the error occurrence
88
89 -- So we can throw these things as exceptions
90 errMsgTc :: TyCon
91 errMsgTc = mkTyCon "ErrMsg"
92 {-# NOINLINE errMsgTc #-}
93 instance Typeable ErrMsg where
94 #if __GLASGOW_HASKELL__ < 603
95   typeOf _ = mkAppTy errMsgTc []
96 #else
97   typeOf _ = mkTyConApp errMsgTc []
98 #endif
99
100 type WarnMsg = ErrMsg
101
102 -- A short (one-line) error message, with context to tell us whether
103 -- to qualify names in the message or not.
104 mkErrMsg :: SrcSpan -> PrintUnqualified -> Message -> ErrMsg
105 mkErrMsg locn print_unqual msg
106   = ErrMsg [locn] print_unqual msg empty
107
108 -- Variant that doesn't care about qualified/unqualified names
109 mkPlainErrMsg :: SrcSpan -> Message -> ErrMsg
110 mkPlainErrMsg locn msg
111   = ErrMsg [locn] alwaysQualify msg empty
112
113 -- A long (multi-line) error message, with context to tell us whether
114 -- to qualify names in the message or not.
115 mkLongErrMsg :: SrcSpan -> PrintUnqualified -> Message -> Message -> ErrMsg
116 mkLongErrMsg locn print_unqual msg extra 
117  = ErrMsg [locn] print_unqual msg extra
118
119 mkWarnMsg :: SrcSpan -> PrintUnqualified -> Message -> WarnMsg
120 mkWarnMsg = mkErrMsg
121
122 type Messages = (Bag WarnMsg, Bag ErrMsg)
123
124 emptyMessages :: Messages
125 emptyMessages = (emptyBag, emptyBag)
126
127 errorsFound :: DynFlags -> Messages -> Bool
128 -- The dyn-flags are used to see if the user has specified
129 -- -Werorr, which says that warnings should be fatal
130 errorsFound dflags (warns, errs) 
131   | dopt Opt_WarnIsError dflags = not (isEmptyBag errs) || not (isEmptyBag warns)
132   | otherwise                   = not (isEmptyBag errs)
133
134 printErrorsAndWarnings :: DynFlags -> Messages -> IO ()
135 printErrorsAndWarnings dflags (warns, errs)
136   | no_errs && no_warns  = return ()
137   | no_errs              = printBagOfWarnings dflags warns
138                             -- Don't print any warnings if there are errors
139   | otherwise            = printBagOfErrors   dflags errs
140   where
141     no_warns = isEmptyBag warns
142     no_errs  = isEmptyBag errs
143
144 printBagOfErrors :: DynFlags -> Bag ErrMsg -> IO ()
145 printBagOfErrors dflags bag_of_errors
146   = sequence_   [ let style = mkErrStyle unqual
147                   in log_action dflags SevError s style (d $$ e)
148                 | ErrMsg { errMsgSpans = s:ss,
149                            errMsgShortDoc = d,
150                            errMsgExtraInfo = e,
151                            errMsgContext = unqual } <- sorted_errs ]
152     where
153       bag_ls      = bagToList bag_of_errors
154       sorted_errs = sortLe occ'ed_before bag_ls
155
156       occ'ed_before err1 err2 = 
157          case compare (head (errMsgSpans err1)) (head (errMsgSpans err2)) of
158                 LT -> True
159                 EQ -> True
160                 GT -> False
161
162 printBagOfWarnings :: DynFlags -> Bag ErrMsg -> IO ()
163 printBagOfWarnings dflags bag_of_warns
164   = sequence_   [ let style = mkErrStyle unqual
165                   in log_action dflags SevWarning s style (d $$ e)
166                 | ErrMsg { errMsgSpans = s:ss,
167                            errMsgShortDoc = d,
168                            errMsgExtraInfo = e,
169                            errMsgContext = unqual } <- sorted_errs ]
170     where
171       bag_ls      = bagToList bag_of_warns
172       sorted_errs = sortLe occ'ed_before bag_ls
173
174       occ'ed_before err1 err2 = 
175          case compare (head (errMsgSpans err1)) (head (errMsgSpans err2)) of
176                 LT -> True
177                 EQ -> True
178                 GT -> False
179
180
181
182 ghcExit :: DynFlags -> Int -> IO ()
183 ghcExit dflags val
184   | val == 0  = exitWith ExitSuccess
185   | otherwise = do errorMsg dflags (text "\nCompilation had errors\n\n")
186                    exitWith (ExitFailure val)
187
188 doIfSet :: Bool -> IO () -> IO ()
189 doIfSet flag action | flag      = action
190                     | otherwise = return ()
191
192 doIfSet_dyn :: DynFlags -> DynFlag -> IO () -> IO()
193 doIfSet_dyn dflags flag action | dopt flag dflags = action
194                                | otherwise        = return ()
195
196 -- -----------------------------------------------------------------------------
197 -- Dumping
198
199 dumpIfSet :: Bool -> String -> SDoc -> IO ()
200 dumpIfSet flag hdr doc
201   | not flag   = return ()
202   | otherwise  = printDump (mkDumpDoc hdr doc)
203
204 dumpIfSet_core :: DynFlags -> DynFlag -> String -> SDoc -> IO ()
205 dumpIfSet_core dflags flag hdr doc
206   | dopt flag dflags
207         || verbosity dflags >= 4
208         || dopt Opt_D_verbose_core2core dflags
209   = dumpSDoc dflags flag hdr doc
210   | otherwise                                   = return ()
211
212 dumpIfSet_dyn :: DynFlags -> DynFlag -> String -> SDoc -> IO ()
213 dumpIfSet_dyn dflags flag hdr doc
214   | dopt flag dflags || verbosity dflags >= 4 
215   = dumpSDoc dflags flag hdr doc
216   | otherwise
217   = return ()
218
219 dumpIfSet_dyn_or :: DynFlags -> [DynFlag] -> String -> SDoc -> IO ()
220 dumpIfSet_dyn_or dflags flags hdr doc
221   | or [dopt flag dflags | flag <- flags]
222   || verbosity dflags >= 4 
223   = printDump (mkDumpDoc hdr doc)
224   | otherwise = return ()
225
226 mkDumpDoc hdr doc 
227    = vcat [text "", 
228            line <+> text hdr <+> line,
229            doc,
230            text ""]
231      where 
232         line = text (replicate 20 '=')
233
234
235 -- | Write out a dump.
236 --      If --dump-to-file is set then this goes to a file.
237 --      otherwise emit to stdout.
238 dumpSDoc :: DynFlags -> DynFlag -> String -> SDoc -> IO ()
239 dumpSDoc dflags dflag hdr doc
240  = do   let mFile       = chooseDumpFile dflags dflag
241         case mFile of
242                 -- write the dump to a file
243                 --      don't add the header in this case, we can see what kind
244                 --      of dump it is from the filename.
245                 Just fileName
246                  -> do  handle  <- openFile fileName AppendMode
247                         hPrintDump handle doc
248                         hClose handle
249
250                 -- write the dump to stdout
251                 Nothing
252                  -> do  printDump (mkDumpDoc hdr doc)
253
254
255 -- | Choose where to put a dump file based on DynFlags
256 --
257 chooseDumpFile :: DynFlags -> DynFlag -> Maybe String
258 chooseDumpFile dflags dflag
259
260         -- dump file location is being forced
261         --      by the --ddump-file-prefix flag.
262         | dumpToFile
263         , Just prefix   <- dumpPrefixForce dflags
264         = Just $ prefix ++ (beautifyDumpName dflag)
265
266         -- dump file location chosen by DriverPipeline.runPipeline
267         | dumpToFile
268         , Just prefix   <- dumpPrefix dflags
269         = Just $ prefix ++ (beautifyDumpName dflag)
270
271         -- we haven't got a place to put a dump file.
272         | otherwise
273         = Nothing
274
275         where   dumpToFile = dopt Opt_DumpToFile dflags
276
277
278 -- | Build a nice file name from name of a DynFlag constructor
279 beautifyDumpName :: DynFlag -> String
280 beautifyDumpName dflag
281  = let  str     = show dflag
282         cut     = if isPrefixOf "Opt_D_" str
283                          then drop 6 str
284                          else str
285         dash    = map   (\c -> case c of
286                                 '_'     -> '-'
287                                 _       -> c)
288                         cut
289    in   dash
290
291
292 -- -----------------------------------------------------------------------------
293 -- Outputting messages from the compiler
294
295 -- We want all messages to go through one place, so that we can
296 -- redirect them if necessary.  For example, when GHC is used as a
297 -- library we might want to catch all messages that GHC tries to
298 -- output and do something else with them.
299
300 ifVerbose :: DynFlags -> Int -> IO () -> IO ()
301 ifVerbose dflags val act
302   | verbosity dflags >= val = act
303   | otherwise               = return ()
304
305 putMsg :: DynFlags -> Message -> IO ()
306 putMsg dflags msg = log_action dflags SevInfo noSrcSpan defaultUserStyle msg
307
308 errorMsg :: DynFlags -> Message -> IO ()
309 errorMsg dflags msg = log_action dflags SevError noSrcSpan defaultErrStyle msg
310
311 fatalErrorMsg :: DynFlags -> Message -> IO ()
312 fatalErrorMsg dflags msg = log_action dflags SevFatal noSrcSpan defaultErrStyle msg
313
314 compilationProgressMsg :: DynFlags -> String -> IO ()
315 compilationProgressMsg dflags msg
316   = ifVerbose dflags 1 (log_action dflags SevInfo noSrcSpan defaultUserStyle (text msg))
317
318 showPass :: DynFlags -> String -> IO ()
319 showPass dflags what 
320   = ifVerbose dflags 2 (log_action dflags SevInfo noSrcSpan defaultUserStyle (text "***" <+> text what <> colon))
321
322 debugTraceMsg :: DynFlags -> Int -> Message -> IO ()
323 debugTraceMsg dflags val msg
324   = ifVerbose dflags val (log_action dflags SevInfo noSrcSpan defaultDumpStyle msg)
325
326 \end{code}