module GHC.Utils.Error (
Validity(..), andValid, allValid, isValid, getInvalids, orValid,
Severity(..),
WarnMsg,
MsgEnvelope(..),
SDoc,
DecoratedSDoc(unDecorated),
Messages, ErrorMessages, WarningMessages,
unionMessages,
errorsFound, isEmptyMessages,
pprMessageBag, pprMsgEnvelopeBagWithLoc,
pprLocMsgEnvelope,
formatBulleted,
emptyMessages, mkDecorated, mkLocMessage, mkLocMessageAnn, makeIntoWarning,
mkMsgEnvelope, mkPlainMsgEnvelope, mkErr, mkLongMsgEnvelope, mkWarnMsg,
mkPlainWarnMsg,
mkLongWarnMsg,
doIfSet, doIfSet_dyn,
getCaretDiagnostic,
putMsg, printInfoForUser, printOutputForUser,
logInfo, logOutput,
errorMsg, warningMsg,
fatalErrorMsg, fatalErrorMsg'',
compilationProgressMsg,
showPass,
withTiming, withTimingSilent,
debugTraceMsg,
ghcExit,
prettyPrintGhcErrors,
traceCmd,
sortMsgBag
) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Driver.Session
import GHC.Driver.Ppr
import GHC.Data.Bag
import GHC.Utils.Exception
import GHC.Utils.Outputable as Outputable
import GHC.Utils.Panic
import GHC.Utils.Logger
import GHC.Types.Error
import GHC.Types.SrcLoc as SrcLoc
import System.Exit ( ExitCode(..), exitWith )
import Data.List ( sortBy )
import Data.Maybe ( fromMaybe )
import Data.Function
import Debug.Trace
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Catch as MC (handle)
import GHC.Conc ( getAllocationCounter )
import System.CPUTime
data Validity
= IsValid
| NotValid SDoc
isValid :: Validity -> Bool
isValid IsValid = True
isValid (NotValid {}) = False
andValid :: Validity -> Validity -> Validity
andValid IsValid v = v
andValid v _ = v
allValid :: [Validity] -> Validity
allValid [] = IsValid
allValid (v : vs) = v `andValid` allValid vs
getInvalids :: [Validity] -> [SDoc]
getInvalids vs = [d | NotValid d <- vs]
orValid :: Validity -> Validity -> Validity
orValid IsValid _ = IsValid
orValid _ v = v
formatBulleted :: SDocContext -> DecoratedSDoc -> SDoc
formatBulleted ctx (unDecorated -> docs)
= case msgs of
[] -> Outputable.empty
[msg] -> msg
_ -> vcat $ map starred msgs
where
msgs = filter (not . Outputable.isEmpty ctx) docs
starred = (bullet<+>)
pprMsgEnvelopeBagWithLoc :: Bag (MsgEnvelope DecoratedSDoc) -> [SDoc]
pprMsgEnvelopeBagWithLoc bag = [ pprLocMsgEnvelope item | item <- sortMsgBag Nothing bag ]
pprLocMsgEnvelope :: RenderableDiagnostic e => MsgEnvelope e -> SDoc
pprLocMsgEnvelope (MsgEnvelope { errMsgSpan = s
, errMsgDiagnostic = e
, errMsgSeverity = sev
, errMsgContext = unqual })
= sdocWithContext $ \ctx ->
withErrStyle unqual $ mkLocMessage sev s (formatBulleted ctx $ renderDiagnostic e)
sortMsgBag :: Maybe DynFlags -> Bag (MsgEnvelope e) -> [MsgEnvelope e]
sortMsgBag dflags = maybeLimit . sortBy (cmp `on` errMsgSpan) . bagToList
where cmp
| fromMaybe False (fmap reverseErrors dflags) = SrcLoc.rightmost_smallest
| otherwise = SrcLoc.leftmost_smallest
maybeLimit = case join (fmap maxErrors dflags) of
Nothing -> id
Just err_limit -> take err_limit
ghcExit :: Logger -> DynFlags -> Int -> IO ()
ghcExit logger dflags val
| val == 0 = exitWith ExitSuccess
| otherwise = do errorMsg logger dflags (text "\nCompilation had errors\n\n")
exitWith (ExitFailure val)
doIfSet :: Bool -> IO () -> IO ()
doIfSet flag action | flag = action
| otherwise = return ()
doIfSet_dyn :: DynFlags -> GeneralFlag -> IO () -> IO()
doIfSet_dyn dflags flag action | gopt flag dflags = action
| otherwise = return ()
ifVerbose :: DynFlags -> Int -> IO () -> IO ()
ifVerbose dflags val act
| verbosity dflags >= val = act
| otherwise = return ()
errorMsg :: Logger -> DynFlags -> SDoc -> IO ()
errorMsg logger dflags msg
= putLogMsg logger dflags NoReason SevError noSrcSpan $ withPprStyle defaultErrStyle msg
warningMsg :: Logger -> DynFlags -> SDoc -> IO ()
warningMsg logger dflags msg
= putLogMsg logger dflags NoReason SevWarning noSrcSpan $ withPprStyle defaultErrStyle msg
fatalErrorMsg :: Logger -> DynFlags -> SDoc -> IO ()
fatalErrorMsg logger dflags msg =
putLogMsg logger dflags NoReason SevFatal noSrcSpan $ withPprStyle defaultErrStyle msg
fatalErrorMsg'' :: FatalMessager -> String -> IO ()
fatalErrorMsg'' fm msg = fm msg
compilationProgressMsg :: Logger -> DynFlags -> SDoc -> IO ()
compilationProgressMsg logger dflags msg = do
let str = showSDoc dflags msg
traceEventIO $ "GHC progress: " ++ str
ifVerbose dflags 1 $
logOutput logger dflags $ withPprStyle defaultUserStyle msg
showPass :: Logger -> DynFlags -> String -> IO ()
showPass logger dflags what
= ifVerbose dflags 2 $
logInfo logger dflags $ withPprStyle defaultUserStyle (text "***" <+> text what <> colon)
data PrintTimings = PrintTimings | DontPrintTimings
deriving (Eq, Show)
withTiming :: MonadIO m
=> Logger
-> DynFlags
-> SDoc
-> (a -> ())
-> m a
-> m a
withTiming logger dflags what force action =
withTiming' logger dflags what force PrintTimings action
withTimingSilent
:: MonadIO m
=> Logger
-> DynFlags
-> SDoc
-> (a -> ())
-> m a
-> m a
withTimingSilent logger dflags what force action =
withTiming' logger dflags what force DontPrintTimings action
withTiming' :: MonadIO m
=> Logger
-> DynFlags
-> SDoc
-> (a -> ())
-> PrintTimings
-> m a
-> m a
withTiming' logger dflags what force_result prtimings action
= if verbosity dflags >= 2 || dopt Opt_D_dump_timings dflags
then do whenPrintTimings $
logInfo logger dflags $ withPprStyle defaultUserStyle $
text "***" <+> what <> colon
let ctx = initDefaultSDocContext dflags
alloc0 <- liftIO getAllocationCounter
start <- liftIO getCPUTime
eventBegins ctx what
recordAllocs alloc0
!r <- action
() <- pure $ force_result r
eventEnds ctx what
end <- liftIO getCPUTime
alloc1 <- liftIO getAllocationCounter
recordAllocs alloc1
let alloc = alloc0 alloc1
time = realToFrac (end start) * 1e-9
when (verbosity dflags >= 2 && prtimings == PrintTimings)
$ liftIO $ logInfo logger dflags $ withPprStyle defaultUserStyle
(text "!!!" <+> what <> colon <+> text "finished in"
<+> doublePrec 2 time
<+> text "milliseconds"
<> comma
<+> text "allocated"
<+> doublePrec 3 (realToFrac alloc / 1024 / 1024)
<+> text "megabytes")
whenPrintTimings $
dumpIfSet_dyn logger dflags Opt_D_dump_timings "" FormatText
$ text $ showSDocOneLine ctx
$ hsep [ what <> colon
, text "alloc=" <> ppr alloc
, text "time=" <> doublePrec 3 time
]
pure r
else action
where whenPrintTimings = liftIO . when (prtimings == PrintTimings)
recordAllocs alloc =
liftIO $ traceMarkerIO $ "GHC:allocs:" ++ show alloc
eventBegins ctx w = do
let doc = eventBeginsDoc ctx w
whenPrintTimings $ traceMarkerIO doc
liftIO $ traceEventIO doc
eventEnds ctx w = do
let doc = eventEndsDoc ctx w
whenPrintTimings $ traceMarkerIO doc
liftIO $ traceEventIO doc
eventBeginsDoc ctx w = showSDocOneLine ctx $ text "GHC:started:" <+> w
eventEndsDoc ctx w = showSDocOneLine ctx $ text "GHC:finished:" <+> w
debugTraceMsg :: Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg logger dflags val msg =
ifVerbose dflags val $
logInfo logger dflags (withPprStyle defaultDumpStyle msg)
putMsg :: Logger -> DynFlags -> SDoc -> IO ()
putMsg logger dflags msg = logInfo logger dflags (withPprStyle defaultUserStyle msg)
printInfoForUser :: Logger -> DynFlags -> PrintUnqualified -> SDoc -> IO ()
printInfoForUser logger dflags print_unqual msg
= logInfo logger dflags (withUserStyle print_unqual AllTheWay msg)
printOutputForUser :: Logger -> DynFlags -> PrintUnqualified -> SDoc -> IO ()
printOutputForUser logger dflags print_unqual msg
= logOutput logger dflags (withUserStyle print_unqual AllTheWay msg)
logInfo :: Logger -> DynFlags -> SDoc -> IO ()
logInfo logger dflags msg
= putLogMsg logger dflags NoReason SevInfo noSrcSpan msg
logOutput :: Logger -> DynFlags -> SDoc -> IO ()
logOutput logger dflags msg
= putLogMsg logger dflags NoReason SevOutput noSrcSpan msg
prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a
prettyPrintGhcErrors dflags
= MC.handle $ \e -> case e of
PprPanic str doc ->
pprDebugAndThen ctx panic (text str) doc
PprSorry str doc ->
pprDebugAndThen ctx sorry (text str) doc
PprProgramError str doc ->
pprDebugAndThen ctx pgmError (text str) doc
_ ->
liftIO $ throwIO e
where
ctx = initSDocContext dflags defaultUserStyle
traceCmd :: Logger -> DynFlags -> String -> String -> IO a -> IO a
traceCmd logger dflags phase_name cmd_line action
= do { let verb = verbosity dflags
; showPass logger dflags phase_name
; debugTraceMsg logger dflags 3 (text cmd_line)
; case flushErr dflags of
FlushErr io -> io
; action `catchIO` handle_exn verb
}
where
handle_exn _verb exn = do { debugTraceMsg logger dflags 2 (char '\n')
; debugTraceMsg logger dflags 2
(text "Failed:"
<+> text cmd_line
<+> text (show exn))
; throwGhcExceptionIO (ProgramError (show exn))}