X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Fmain%2FErrUtils.lhs;h=90e5dc87b6a204cdf98fc6d0f42e377df1527cc9;hb=28a464a75e14cece5db40f2765a29348273ff2d2;hp=d6f1ae1debcbd3162cd3414922d26a8db57d4f7f;hpb=d4a2fe2b1578d162fa2880f760cfcfd547973039;p=ghc-hetmet.git diff --git a/ghc/compiler/main/ErrUtils.lhs b/ghc/compiler/main/ErrUtils.lhs index d6f1ae1..90e5dc8 100644 --- a/ghc/compiler/main/ErrUtils.lhs +++ b/ghc/compiler/main/ErrUtils.lhs @@ -6,24 +6,25 @@ \begin{code} module ErrUtils ( Message, mkLocMessage, printError, + Severity(..), ErrMsg, WarnMsg, - errMsgSpans, errMsgShortDoc, errMsgExtraInfo, + errMsgSpans, errMsgContext, errMsgShortDoc, errMsgExtraInfo, Messages, errorsFound, emptyMessages, mkErrMsg, mkWarnMsg, mkPlainErrMsg, mkLongErrMsg, - printErrorsAndWarnings, pprBagOfErrors, pprBagOfWarnings, + printErrorsAndWarnings, printBagOfErrors, printBagOfWarnings, ghcExit, doIfSet, doIfSet_dyn, - dumpIfSet, dumpIfSet_core, dumpIfSet_dyn, dumpIfSet_dyn_or, mkDumpDoc, - showPass, + dumpIfSet, dumpIfSet_core, dumpIfSet_dyn, dumpIfSet_dyn_or, mkDumpDoc, - -- * Messages during compilation - setMsgHandler, + -- * Messages during compilation putMsg, - compilationProgressMsg, - debugTraceMsg, errorMsg, + fatalErrorMsg, + compilationProgressMsg, + showPass, + debugTraceMsg, ) where #include "HsVersions.h" @@ -33,14 +34,13 @@ import SrcLoc ( SrcSpan ) import Util ( sortLe, global ) import Outputable import qualified Pretty -import SrcLoc ( srcSpanStart ) -import CmdLineOpts ( DynFlags(..), DynFlag(..), dopt, - opt_ErrorSpans ) - -import List ( replicate, sortBy ) +import SrcLoc ( srcSpanStart, noSrcSpan ) +import DynFlags ( DynFlags(..), DynFlag(..), dopt ) +import StaticFlags ( opt_ErrorSpans ) import System ( ExitCode(..), exitWith ) import DATA_IOREF -import IO ( hPutStrLn, stderr, stdout ) +import IO ( hPutStrLn, stderr ) +import DYNAMIC -- ----------------------------------------------------------------------------- @@ -48,6 +48,12 @@ import IO ( hPutStrLn, stderr, stdout ) type Message = SDoc +data Severity + = SevInfo + | SevWarning + | SevError + | SevFatal + mkLocMessage :: SrcSpan -> Message -> Message mkLocMessage locn msg | opt_ErrorSpans = hang (ppr locn <> colon) 4 msg @@ -73,6 +79,17 @@ data ErrMsg = ErrMsg { -- NB Pretty.Doc not SDoc: we deal with the printing style (in ptic -- whether to qualify an External Name) at the error occurrence +-- So we can throw these things as exceptions +errMsgTc :: TyCon +errMsgTc = mkTyCon "ErrMsg" +{-# NOINLINE errMsgTc #-} +instance Typeable ErrMsg where +#if __GLASGOW_HASKELL__ < 603 + typeOf _ = mkAppTy errMsgTc [] +#else + typeOf _ = mkTyConApp errMsgTc [] +#endif + type WarnMsg = ErrMsg -- A short (one-line) error message, with context to tell us whether @@ -92,18 +109,9 @@ mkLongErrMsg :: SrcSpan -> PrintUnqualified -> Message -> Message -> ErrMsg mkLongErrMsg locn print_unqual msg extra = ErrMsg [locn] print_unqual msg extra --- A long (multi-line) error message, with context to tell us whether --- to qualify names in the message or not. -mkLongMultiLocErrMsg :: [SrcSpan] -> PrintUnqualified -> Message -> Message -> ErrMsg -mkLongMultiLocErrMsg locns print_unqual msg extra - = ErrMsg locns print_unqual msg extra - mkWarnMsg :: SrcSpan -> PrintUnqualified -> Message -> WarnMsg mkWarnMsg = mkErrMsg -mkLongWarnMsg :: SrcSpan -> PrintUnqualified -> Message -> Message -> WarnMsg -mkLongWarnMsg = mkLongErrMsg - type Messages = (Bag WarnMsg, Bag ErrMsg) emptyMessages :: Messages @@ -116,22 +124,20 @@ errorsFound dflags (warns, errs) | dopt Opt_WarnIsError dflags = not (isEmptyBag errs) || not (isEmptyBag warns) | otherwise = not (isEmptyBag errs) -printErrorsAndWarnings :: Messages -> IO () -printErrorsAndWarnings (warns, errs) +printErrorsAndWarnings :: DynFlags -> Messages -> IO () +printErrorsAndWarnings dflags (warns, errs) | no_errs && no_warns = return () - | no_errs = printErrs (pprBagOfWarnings warns) + | no_errs = printBagOfWarnings dflags warns -- Don't print any warnings if there are errors - | otherwise = printErrs (pprBagOfErrors errs) + | otherwise = printBagOfErrors dflags errs where no_warns = isEmptyBag warns no_errs = isEmptyBag errs -pprBagOfErrors :: Bag ErrMsg -> Pretty.Doc -pprBagOfErrors bag_of_errors - = Pretty.vcat [ let style = mkErrStyle unqual - doc = mkLocMessage s (d $$ e) - in - Pretty.text "" Pretty.$$ doc style +printBagOfErrors :: DynFlags -> Bag ErrMsg -> IO () +printBagOfErrors dflags bag_of_errors + = sequence_ [ let style = mkErrStyle unqual + in log_action dflags SevError s style (d $$ e) | ErrMsg { errMsgSpans = s:ss, errMsgShortDoc = d, errMsgExtraInfo = e, @@ -146,15 +152,30 @@ pprBagOfErrors bag_of_errors EQ -> True GT -> False -pprBagOfWarnings :: Bag WarnMsg -> Pretty.Doc -pprBagOfWarnings bag_of_warns = pprBagOfErrors bag_of_warns +printBagOfWarnings :: DynFlags -> Bag ErrMsg -> IO () +printBagOfWarnings dflags bag_of_warns + = sequence_ [ let style = mkErrStyle unqual + in log_action dflags SevWarning s style (d $$ e) + | ErrMsg { errMsgSpans = s:ss, + errMsgShortDoc = d, + errMsgExtraInfo = e, + errMsgContext = unqual } <- sorted_errs ] + where + bag_ls = bagToList bag_of_warns + sorted_errs = sortLe occ'ed_before bag_ls + + occ'ed_before err1 err2 = + case compare (head (errMsgSpans err1)) (head (errMsgSpans err2)) of + LT -> True + EQ -> True + GT -> False \end{code} \begin{code} -ghcExit :: Int -> IO () -ghcExit val +ghcExit :: DynFlags -> Int -> IO () +ghcExit dflags val | val == 0 = exitWith ExitSuccess - | otherwise = do errorMsg "\nCompilation had errors\n\n" + | otherwise = do errorMsg dflags (text "\nCompilation had errors\n\n") exitWith (ExitFailure val) \end{code} @@ -169,9 +190,6 @@ doIfSet_dyn dflags flag action | dopt flag dflags = action \end{code} \begin{code} -showPass :: DynFlags -> String -> IO () -showPass dflags what = compilationPassMsg dflags ("*** "++what++":") - dumpIfSet :: Bool -> String -> SDoc -> IO () dumpIfSet flag hdr doc | not flag = return () @@ -219,26 +237,24 @@ ifVerbose dflags val act | verbosity dflags >= val = act | otherwise = return () -errorMsg :: String -> IO () -errorMsg = putMsg - -compilationProgressMsg :: DynFlags -> String -> IO () -compilationProgressMsg dflags msg - = ifVerbose dflags 1 (putMsg msg) +putMsg :: DynFlags -> Message -> IO () +putMsg dflags msg = log_action dflags SevInfo noSrcSpan defaultUserStyle msg -compilationPassMsg :: DynFlags -> String -> IO () -compilationPassMsg dflags msg - = ifVerbose dflags 2 (putMsg msg) +errorMsg :: DynFlags -> Message -> IO () +errorMsg dflags msg = log_action dflags SevError noSrcSpan defaultErrStyle msg -debugTraceMsg :: DynFlags -> String -> IO () -debugTraceMsg dflags msg - = ifVerbose dflags 2 (putMsg msg) +fatalErrorMsg :: DynFlags -> Message -> IO () +fatalErrorMsg dflags msg = log_action dflags SevFatal noSrcSpan defaultErrStyle msg -GLOBAL_VAR(msgHandler, hPutStrLn stderr, (String -> IO ())) +compilationProgressMsg :: DynFlags -> String -> IO () +compilationProgressMsg dflags msg + = ifVerbose dflags 1 (log_action dflags SevInfo noSrcSpan defaultUserStyle (text msg)) -setMsgHandler :: (String -> IO ()) -> IO () -setMsgHandler handle_msg = writeIORef msgHandler handle_msg +showPass :: DynFlags -> String -> IO () +showPass dflags what + = ifVerbose dflags 2 (log_action dflags SevInfo noSrcSpan defaultUserStyle (text "***" <+> text what <> colon)) -putMsg :: String -> IO () -putMsg msg = do h <- readIORef msgHandler; h msg +debugTraceMsg :: DynFlags -> Int -> Message -> IO () +debugTraceMsg dflags val msg + = ifVerbose dflags val (log_action dflags SevInfo noSrcSpan defaultDumpStyle msg) \end{code}