Warning fix for unused and redundant imports
[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,  
20
21         --  * Messages during compilation
22         putMsg,
23         errorMsg,
24         fatalErrorMsg,
25         compilationProgressMsg,
26         showPass,
27         debugTraceMsg,  
28     ) where
29
30 #include "HsVersions.h"
31
32 import Bag              ( Bag, bagToList, isEmptyBag, emptyBag )
33 import SrcLoc           ( SrcSpan )
34 import Util             ( sortLe )
35 import Outputable
36 import SrcLoc           ( srcSpanStart, noSrcSpan )
37 import DynFlags         ( DynFlags(..), DynFlag(..), dopt )
38 import StaticFlags      ( opt_ErrorSpans )
39
40 import System.Exit      ( ExitCode(..), exitWith )
41 import Data.Dynamic
42
43
44 -- -----------------------------------------------------------------------------
45 -- Basic error messages: just render a message with a source location.
46
47 type Message = SDoc
48
49 data Severity
50   = SevInfo
51   | SevWarning
52   | SevError
53   | SevFatal
54
55 mkLocMessage :: SrcSpan -> Message -> Message
56 mkLocMessage locn msg
57   | opt_ErrorSpans = hang (ppr locn <> colon) 4 msg
58   | otherwise      = hang (ppr (srcSpanStart locn) <> colon) 4 msg
59   -- always print the location, even if it is unhelpful.  Error messages
60   -- are supposed to be in a standard format, and one without a location
61   -- would look strange.  Better to say explicitly "<no location info>".
62
63 printError :: SrcSpan -> Message -> IO ()
64 printError span msg = printErrs (mkLocMessage span msg $ defaultErrStyle)
65
66
67 -- -----------------------------------------------------------------------------
68 -- Collecting up messages for later ordering and printing.
69
70 data ErrMsg = ErrMsg { 
71         errMsgSpans     :: [SrcSpan],
72         errMsgContext   :: PrintUnqualified,
73         errMsgShortDoc  :: Message,
74         errMsgExtraInfo :: Message
75         }
76         -- The SrcSpan is used for sorting errors into line-number order
77         -- NB  Pretty.Doc not SDoc: we deal with the printing style (in ptic 
78         -- whether to qualify an External Name) at the error occurrence
79
80 -- So we can throw these things as exceptions
81 errMsgTc :: TyCon
82 errMsgTc = mkTyCon "ErrMsg"
83 {-# NOINLINE errMsgTc #-}
84 instance Typeable ErrMsg where
85 #if __GLASGOW_HASKELL__ < 603
86   typeOf _ = mkAppTy errMsgTc []
87 #else
88   typeOf _ = mkTyConApp errMsgTc []
89 #endif
90
91 type WarnMsg = ErrMsg
92
93 -- A short (one-line) error message, with context to tell us whether
94 -- to qualify names in the message or not.
95 mkErrMsg :: SrcSpan -> PrintUnqualified -> Message -> ErrMsg
96 mkErrMsg locn print_unqual msg
97   = ErrMsg [locn] print_unqual msg empty
98
99 -- Variant that doesn't care about qualified/unqualified names
100 mkPlainErrMsg :: SrcSpan -> Message -> ErrMsg
101 mkPlainErrMsg locn msg
102   = ErrMsg [locn] alwaysQualify msg empty
103
104 -- A long (multi-line) error message, with context to tell us whether
105 -- to qualify names in the message or not.
106 mkLongErrMsg :: SrcSpan -> PrintUnqualified -> Message -> Message -> ErrMsg
107 mkLongErrMsg locn print_unqual msg extra 
108  = ErrMsg [locn] print_unqual msg extra
109
110 mkWarnMsg :: SrcSpan -> PrintUnqualified -> Message -> WarnMsg
111 mkWarnMsg = mkErrMsg
112
113 type Messages = (Bag WarnMsg, Bag ErrMsg)
114
115 emptyMessages :: Messages
116 emptyMessages = (emptyBag, emptyBag)
117
118 errorsFound :: DynFlags -> Messages -> Bool
119 -- The dyn-flags are used to see if the user has specified
120 -- -Werorr, which says that warnings should be fatal
121 errorsFound dflags (warns, errs) 
122   | dopt Opt_WarnIsError dflags = not (isEmptyBag errs) || not (isEmptyBag warns)
123   | otherwise                   = not (isEmptyBag errs)
124
125 printErrorsAndWarnings :: DynFlags -> Messages -> IO ()
126 printErrorsAndWarnings dflags (warns, errs)
127   | no_errs && no_warns  = return ()
128   | no_errs              = printBagOfWarnings dflags warns
129                             -- Don't print any warnings if there are errors
130   | otherwise            = printBagOfErrors   dflags errs
131   where
132     no_warns = isEmptyBag warns
133     no_errs  = isEmptyBag errs
134
135 printBagOfErrors :: DynFlags -> Bag ErrMsg -> IO ()
136 printBagOfErrors dflags bag_of_errors
137   = sequence_   [ let style = mkErrStyle unqual
138                   in log_action dflags SevError s style (d $$ e)
139                 | ErrMsg { errMsgSpans = s:ss,
140                            errMsgShortDoc = d,
141                            errMsgExtraInfo = e,
142                            errMsgContext = unqual } <- sorted_errs ]
143     where
144       bag_ls      = bagToList bag_of_errors
145       sorted_errs = sortLe occ'ed_before bag_ls
146
147       occ'ed_before err1 err2 = 
148          case compare (head (errMsgSpans err1)) (head (errMsgSpans err2)) of
149                 LT -> True
150                 EQ -> True
151                 GT -> False
152
153 printBagOfWarnings :: DynFlags -> Bag ErrMsg -> IO ()
154 printBagOfWarnings dflags bag_of_warns
155   = sequence_   [ let style = mkErrStyle unqual
156                   in log_action dflags SevWarning s style (d $$ e)
157                 | ErrMsg { errMsgSpans = s:ss,
158                            errMsgShortDoc = d,
159                            errMsgExtraInfo = e,
160                            errMsgContext = unqual } <- sorted_errs ]
161     where
162       bag_ls      = bagToList bag_of_warns
163       sorted_errs = sortLe occ'ed_before bag_ls
164
165       occ'ed_before err1 err2 = 
166          case compare (head (errMsgSpans err1)) (head (errMsgSpans err2)) of
167                 LT -> True
168                 EQ -> True
169                 GT -> False
170 \end{code}
171
172 \begin{code}
173 ghcExit :: DynFlags -> Int -> IO ()
174 ghcExit dflags val
175   | val == 0  = exitWith ExitSuccess
176   | otherwise = do errorMsg dflags (text "\nCompilation had errors\n\n")
177                    exitWith (ExitFailure val)
178 \end{code}
179
180 \begin{code}
181 doIfSet :: Bool -> IO () -> IO ()
182 doIfSet flag action | flag      = action
183                     | otherwise = return ()
184
185 doIfSet_dyn :: DynFlags -> DynFlag -> IO () -> IO()
186 doIfSet_dyn dflags flag action | dopt flag dflags = action
187                                | otherwise        = return ()
188 \end{code}
189
190 \begin{code}
191 dumpIfSet :: Bool -> String -> SDoc -> IO ()
192 dumpIfSet flag hdr doc
193   | not flag   = return ()
194   | otherwise  = printDump (mkDumpDoc hdr doc)
195
196 dumpIfSet_core :: DynFlags -> DynFlag -> String -> SDoc -> IO ()
197 dumpIfSet_core dflags flag hdr doc
198   | dopt flag dflags
199         || verbosity dflags >= 4
200         || dopt Opt_D_verbose_core2core dflags  = printDump (mkDumpDoc hdr doc)
201   | otherwise                                   = return ()
202
203 dumpIfSet_dyn :: DynFlags -> DynFlag -> String -> SDoc -> IO ()
204 dumpIfSet_dyn dflags flag hdr doc
205   | dopt flag dflags || verbosity dflags >= 4 
206   = printDump (mkDumpDoc hdr doc)
207   | otherwise
208   = return ()
209
210 dumpIfSet_dyn_or :: DynFlags -> [DynFlag] -> String -> SDoc -> IO ()
211 dumpIfSet_dyn_or dflags flags hdr doc
212   | or [dopt flag dflags | flag <- flags]
213   || verbosity dflags >= 4 
214   = printDump (mkDumpDoc hdr doc)
215   | otherwise = return ()
216
217 mkDumpDoc hdr doc 
218    = vcat [text "", 
219            line <+> text hdr <+> line,
220            doc,
221            text ""]
222      where 
223         line = text (replicate 20 '=')
224
225 -- -----------------------------------------------------------------------------
226 -- Outputting messages from the compiler
227
228 -- We want all messages to go through one place, so that we can
229 -- redirect them if necessary.  For example, when GHC is used as a
230 -- library we might want to catch all messages that GHC tries to
231 -- output and do something else with them.
232
233 ifVerbose :: DynFlags -> Int -> IO () -> IO ()
234 ifVerbose dflags val act
235   | verbosity dflags >= val = act
236   | otherwise               = return ()
237
238 putMsg :: DynFlags -> Message -> IO ()
239 putMsg dflags msg = log_action dflags SevInfo noSrcSpan defaultUserStyle msg
240
241 errorMsg :: DynFlags -> Message -> IO ()
242 errorMsg dflags msg = log_action dflags SevError noSrcSpan defaultErrStyle msg
243
244 fatalErrorMsg :: DynFlags -> Message -> IO ()
245 fatalErrorMsg dflags msg = log_action dflags SevFatal noSrcSpan defaultErrStyle msg
246
247 compilationProgressMsg :: DynFlags -> String -> IO ()
248 compilationProgressMsg dflags msg
249   = ifVerbose dflags 1 (log_action dflags SevInfo noSrcSpan defaultUserStyle (text msg))
250
251 showPass :: DynFlags -> String -> IO ()
252 showPass dflags what 
253   = ifVerbose dflags 2 (log_action dflags SevInfo noSrcSpan defaultUserStyle (text "***" <+> text what <> colon))
254
255 debugTraceMsg :: DynFlags -> Int -> Message -> IO ()
256 debugTraceMsg dflags val msg
257   = ifVerbose dflags val (log_action dflags SevInfo noSrcSpan defaultDumpStyle msg)
258 \end{code}