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