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