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