Simon Hengel pushed to branch wip/sol/remove-ddump-json at Glasgow Haskell Compiler / GHC
Commits:
-
6188871b
by Simon Hengel at 2025-08-22T22:29:11+07:00
-
a05761aa
by Simon Hengel at 2025-08-22T22:29:19+07:00
-
b11ad603
by Simon Hengel at 2025-08-22T22:29:19+07:00
-
a45d2551
by Simon Hengel at 2025-08-22T22:30:01+07:00
-
97bb1ca0
by Simon Hengel at 2025-08-22T22:41:01+07:00
-
19596062
by Simon Hengel at 2025-08-22T22:48:55+07:00
21 changed files:
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Errors.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Monad.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Pipeline/LogQueue.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Runtime/Debugger.hs
- compiler/GHC/Stg/Lint.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Utils/Error.hs
- compiler/GHC/Utils/Logger.hs
- ghc/GHCi/UI.hs
- testsuite/tests/ghc-api/T7478/T7478.hs
- testsuite/tests/plugins/hooks-plugin/Hooks/LogPlugin.hs
Changes:
| ... | ... | @@ -26,6 +26,7 @@ module GHC.Core.Lint ( |
| 26 | 26 | -- ** Debug output
|
| 27 | 27 | EndPassConfig (..),
|
| 28 | 28 | endPassIO,
|
| 29 | + lintMessage,
|
|
| 29 | 30 | displayLintResults, dumpPassResult
|
| 30 | 31 | ) where
|
| 31 | 32 | |
| ... | ... | @@ -309,11 +310,6 @@ path does not result in allocation in the hot path. This can be surprisingly |
| 309 | 310 | impactful. Changing `lint_app` reduced allocations for one test program I was
|
| 310 | 311 | looking at by ~4%.
|
| 311 | 312 | |
| 312 | -Note [MCInfo for Lint]
|
|
| 313 | -~~~~~~~~~~~~~~~~~~~~~~
|
|
| 314 | -When printing a Lint message, use the MCInfo severity so that the
|
|
| 315 | -message is printed on stderr rather than stdout (#13342).
|
|
| 316 | - |
|
| 317 | 313 | ************************************************************************
|
| 318 | 314 | * *
|
| 319 | 315 | Beginning and ending passes
|
| ... | ... | @@ -321,6 +317,12 @@ message is printed on stderr rather than stdout (#13342). |
| 321 | 317 | ************************************************************************
|
| 322 | 318 | -}
|
| 323 | 319 | |
| 320 | +lintMessage :: Logger -> SDoc -> IO ()
|
|
| 321 | +lintMessage logger =
|
|
| 322 | + -- Note: Use logInfo when printing a Lint message, so that the message is
|
|
| 323 | + -- printed on stderr rather than stdout (#13342).
|
|
| 324 | + logInfo logger . withPprStyle defaultDumpStyle
|
|
| 325 | + |
|
| 324 | 326 | -- | Configuration for boilerplate operations at the end of a
|
| 325 | 327 | -- compilation pass producing Core.
|
| 326 | 328 | data EndPassConfig = EndPassConfig
|
| ... | ... | @@ -436,8 +438,7 @@ displayLintResults :: Logger |
| 436 | 438 | -> IO ()
|
| 437 | 439 | displayLintResults logger display_warnings pp_what pp_pgm (warns, errs)
|
| 438 | 440 | | not (isEmptyBag errs)
|
| 439 | - = do { logMsg logger Err.MCInfo noSrcSpan -- See Note [MCInfo for Lint]
|
|
| 440 | - $ withPprStyle defaultDumpStyle
|
|
| 441 | + = do { lintMessage logger
|
|
| 441 | 442 | (vcat [ lint_banner "errors" pp_what, Err.pprMessageBag errs
|
| 442 | 443 | , text "*** Offending Program ***"
|
| 443 | 444 | , pp_pgm
|
| ... | ... | @@ -447,8 +448,7 @@ displayLintResults logger display_warnings pp_what pp_pgm (warns, errs) |
| 447 | 448 | | not (isEmptyBag warns)
|
| 448 | 449 | , log_enable_debug (logFlags logger)
|
| 449 | 450 | , display_warnings
|
| 450 | - = logMsg logger Err.MCInfo noSrcSpan -- See Note [MCInfo for Lint]
|
|
| 451 | - $ withPprStyle defaultDumpStyle
|
|
| 451 | + = lintMessage logger
|
|
| 452 | 452 | (lint_banner "warnings" pp_what $$ Err.pprMessageBag (mapBag ($$ blankLine) warns))
|
| 453 | 453 | |
| 454 | 454 | | otherwise = return ()
|
| ... | ... | @@ -362,19 +362,22 @@ we aren't using annotations heavily. |
| 362 | 362 | ************************************************************************
|
| 363 | 363 | -}
|
| 364 | 364 | |
| 365 | -msg :: MessageClass -> SDoc -> CoreM ()
|
|
| 366 | -msg msg_class doc = do
|
|
| 365 | +msg :: Message -> CoreM ()
|
|
| 366 | +msg msg = do
|
|
| 367 | 367 | logger <- getLogger
|
| 368 | - loc <- getSrcSpanM
|
|
| 369 | 368 | name_ppr_ctx <- getNamePprCtx
|
| 370 | - let sty = case msg_class of
|
|
| 371 | - MCDiagnostic _ _ _ -> err_sty
|
|
| 372 | - MCDump -> dump_sty
|
|
| 373 | - _ -> user_sty
|
|
| 374 | - err_sty = mkErrStyle name_ppr_ctx
|
|
| 375 | - user_sty = mkUserStyle name_ppr_ctx AllTheWay
|
|
| 376 | - dump_sty = mkDumpStyle name_ppr_ctx
|
|
| 377 | - liftIO $ logMsg logger msg_class loc (withPprStyle sty doc)
|
|
| 369 | + let m = case msg of
|
|
| 370 | + MCDump doc -> MCDump (dump_sty doc)
|
|
| 371 | + UnsafeMCDiagnostic span severity reason code doc diagnostic -> UnsafeMCDiagnostic span severity reason code (err_sty doc) diagnostic
|
|
| 372 | + MCOutput doc -> MCOutput (user_sty doc)
|
|
| 373 | + MCFatal doc -> MCFatal (user_sty doc)
|
|
| 374 | + MCInteractive doc -> MCInteractive (user_sty doc)
|
|
| 375 | + MCInfo doc -> MCInfo (user_sty doc)
|
|
| 376 | + |
|
| 377 | + err_sty = withPprStyle $ mkErrStyle name_ppr_ctx
|
|
| 378 | + user_sty = withPprStyle $ mkUserStyle name_ppr_ctx AllTheWay
|
|
| 379 | + dump_sty = withPprStyle $ mkDumpStyle name_ppr_ctx
|
|
| 380 | + liftIO $ logMsg logger m
|
|
| 378 | 381 | |
| 379 | 382 | -- | Output a String message to the screen
|
| 380 | 383 | putMsgS :: String -> CoreM ()
|
| ... | ... | @@ -382,7 +385,7 @@ putMsgS = putMsg . text |
| 382 | 385 | |
| 383 | 386 | -- | Output a message to the screen
|
| 384 | 387 | putMsg :: SDoc -> CoreM ()
|
| 385 | -putMsg = msg MCInfo
|
|
| 388 | +putMsg = msg . MCInfo
|
|
| 386 | 389 | |
| 387 | 390 | diagnostic :: DiagnosticReason -> SDoc -> CoreM ()
|
| 388 | 391 | diagnostic reason doc = do
|
| ... | ... | @@ -407,7 +410,7 @@ fatalErrorMsgS = fatalErrorMsg . text |
| 407 | 410 | |
| 408 | 411 | -- | Output a fatal error to the screen. Does not cause the compiler to die.
|
| 409 | 412 | fatalErrorMsg :: SDoc -> CoreM ()
|
| 410 | -fatalErrorMsg = msg MCFatal
|
|
| 413 | +fatalErrorMsg = msg . MCFatal
|
|
| 411 | 414 | |
| 412 | 415 | -- | Output a string debugging message at verbosity level of @-v@ or higher
|
| 413 | 416 | debugTraceMsgS :: String -> CoreM ()
|
| ... | ... | @@ -415,4 +418,4 @@ debugTraceMsgS = debugTraceMsg . text |
| 415 | 418 | |
| 416 | 419 | -- | Outputs a debugging message at verbosity level of @-v@ or higher
|
| 417 | 420 | debugTraceMsg :: SDoc -> CoreM ()
|
| 418 | -debugTraceMsg = msg MCDump |
|
| 421 | +debugTraceMsg = msg . MCDump |
| ... | ... | @@ -18,6 +18,7 @@ import GHC.Prelude |
| 18 | 18 | import GHC.Platform
|
| 19 | 19 | import GHC.ForeignSrcLang
|
| 20 | 20 | import GHC.Data.FastString
|
| 21 | +import GHC.Core.Lint ( lintMessage )
|
|
| 21 | 22 | |
| 22 | 23 | import GHC.CmmToAsm ( nativeCodeGen )
|
| 23 | 24 | import GHC.CmmToLlvm ( llvmCodeGen )
|
| ... | ... | @@ -55,7 +56,6 @@ import GHC.Utils.Panic.Plain ( pgmError ) |
| 55 | 56 | import GHC.Unit
|
| 56 | 57 | import GHC.Unit.Finder ( mkStubPaths )
|
| 57 | 58 | |
| 58 | -import GHC.Types.SrcLoc
|
|
| 59 | 59 | import GHC.Types.CostCentre
|
| 60 | 60 | import GHC.Types.ForeignStubs
|
| 61 | 61 | import GHC.Types.Unique.DSM
|
| ... | ... | @@ -109,10 +109,7 @@ codeOutput logger tmpfs llvm_config dflags unit_state this_mod filenm location g |
| 109 | 109 | (text "CmmLint"<+>brackets (ppr this_mod))
|
| 110 | 110 | (const ()) $ do
|
| 111 | 111 | { case cmmLint (targetPlatform dflags) cmm of
|
| 112 | - Just err -> do { logMsg logger
|
|
| 113 | - MCInfo -- See Note [MCInfo for Lint] in "GHC.Core.Lint"
|
|
| 114 | - noSrcSpan
|
|
| 115 | - $ withPprStyle defaultDumpStyle err
|
|
| 112 | + Just err -> do { lintMessage logger err
|
|
| 116 | 113 | ; ghcExit logger 1
|
| 117 | 114 | }
|
| 118 | 115 | Nothing -> return ()
|
| ... | ... | @@ -46,19 +46,16 @@ printMessages logger msg_opts opts = mapM_ (printMessage logger msg_opts opts) . |
| 46 | 46 | sortMessages = sortMsgBag (Just opts) . getMessages
|
| 47 | 47 | |
| 48 | 48 | printMessage :: forall a. (Diagnostic a) => Logger -> DiagnosticOpts a -> DiagOpts -> MsgEnvelope a -> IO ()
|
| 49 | -printMessage logger msg_opts opts message
|
|
| 50 | - | log_diags_as_json = do
|
|
| 51 | - decorated <- decorateDiagnostic logflags messageClass location doc
|
|
| 52 | - let
|
|
| 53 | - rendered :: String
|
|
| 54 | - rendered = renderWithContext (log_default_user_context logflags) decorated
|
|
| 55 | - |
|
| 56 | - jsonMessage :: JsonDoc
|
|
| 57 | - jsonMessage = jsonDiagnostic rendered message
|
|
| 49 | +printMessage logger msg_opts opts message = do
|
|
| 50 | + decorated <- decorateDiagnostic logflags location severity reason code doc
|
|
| 51 | + let
|
|
| 52 | + rendered :: String
|
|
| 53 | + rendered = renderWithContext (log_default_user_context logflags) decorated
|
|
| 58 | 54 | |
| 59 | - logJsonMsg logger messageClass jsonMessage
|
|
| 55 | + jsonMessage :: JsonDoc
|
|
| 56 | + jsonMessage = jsonDiagnostic rendered message
|
|
| 60 | 57 | |
| 61 | - | otherwise = logMsg logger messageClass location doc
|
|
| 58 | + logMsg logger $ UnsafeMCDiagnostic location severity reason code decorated jsonMessage
|
|
| 62 | 59 | where
|
| 63 | 60 | logflags :: LogFlags
|
| 64 | 61 | logflags = logFlags logger
|
| ... | ... | @@ -66,9 +63,6 @@ printMessage logger msg_opts opts message |
| 66 | 63 | doc :: SDoc
|
| 67 | 64 | doc = updSDocContext (\_ -> ctx) (messageWithHints diagnostic)
|
| 68 | 65 | |
| 69 | - messageClass :: MessageClass
|
|
| 70 | - messageClass = UnsafeMCDiagnostic severity (errMsgReason message) (diagnosticCode diagnostic)
|
|
| 71 | - |
|
| 72 | 66 | style :: PprStyle
|
| 73 | 67 | style = mkErrStyle (errMsgContext message)
|
| 74 | 68 | |
| ... | ... | @@ -84,6 +78,12 @@ printMessage logger msg_opts opts message |
| 84 | 78 | severity :: Severity
|
| 85 | 79 | severity = errMsgSeverity message
|
| 86 | 80 | |
| 81 | + reason :: ResolvedDiagnosticReason
|
|
| 82 | + reason = errMsgReason message
|
|
| 83 | + |
|
| 84 | + code :: Maybe DiagnosticCode
|
|
| 85 | + code = diagnosticCode diagnostic
|
|
| 86 | + |
|
| 87 | 87 | messageWithHints :: a -> SDoc
|
| 88 | 88 | messageWithHints e =
|
| 89 | 89 | let main_msg = formatBulleted $ diagnosticMessage msg_opts e
|
| ... | ... | @@ -93,8 +93,22 @@ printMessage logger msg_opts opts message |
| 93 | 93 | hs -> main_msg $$ hang (text "Suggested fixes:") 2
|
| 94 | 94 | (formatBulleted $ mkDecorated . map ppr $ hs)
|
| 95 | 95 | |
| 96 | - log_diags_as_json :: Bool
|
|
| 97 | - log_diags_as_json = log_diagnostics_as_json (logFlags logger)
|
|
| 96 | +decorateDiagnostic :: LogFlags -> SrcSpan -> Severity -> ResolvedDiagnosticReason -> Maybe DiagnosticCode -> SDoc -> IO SDoc
|
|
| 97 | +decorateDiagnostic logflags span severity reason code doc = addCaret
|
|
| 98 | + where
|
|
| 99 | + -- Pretty print the warning flag, if any (#10752)
|
|
| 100 | + message :: SDoc
|
|
| 101 | + message = formatDiagnostic (log_show_warn_groups logflags) span severity reason code doc
|
|
| 102 | + |
|
| 103 | + addCaret :: IO SDoc
|
|
| 104 | + addCaret = do
|
|
| 105 | + caretDiagnostic <-
|
|
| 106 | + if log_show_caret logflags
|
|
| 107 | + then getCaretDiagnostic severity span
|
|
| 108 | + else pure empty
|
|
| 109 | + return $ getPprStyle $ \style ->
|
|
| 110 | + withPprStyle (setStyleColoured True style)
|
|
| 111 | + (message $+$ caretDiagnostic $+$ blankLine)
|
|
| 98 | 112 | |
| 99 | 113 | -- | Given a bag of diagnostics, turn them into an exception if
|
| 100 | 114 | -- any has 'SevError', or print them out otherwise.
|
| ... | ... | @@ -1835,7 +1835,7 @@ markUnsafeInfer tcg_env whyUnsafe = do |
| 1835 | 1835 | ]
|
| 1836 | 1836 | badFlags df = concatMap (badFlag df) unsafeFlagsForInfer
|
| 1837 | 1837 | badFlag df (ext,loc,on,_)
|
| 1838 | - | on df = [mkLocMessage MCOutput (loc df) $
|
|
| 1838 | + | on df = [formatLocMessage (loc df) $
|
|
| 1839 | 1839 | text "-X" <> ppr ext <+> text "is not allowed in Safe Haskell"]
|
| 1840 | 1840 | | otherwise = []
|
| 1841 | 1841 | badInsts insts = concatMap badInst insts
|
| ... | ... | @@ -1844,9 +1844,10 @@ markUnsafeInfer tcg_env whyUnsafe = do |
| 1844 | 1844 | checkOverlap _ = True
|
| 1845 | 1845 | |
| 1846 | 1846 | badInst ins | checkOverlap (overlapMode (is_flag ins))
|
| 1847 | - = [mkLocMessage MCOutput (nameSrcSpan $ getName $ is_dfun ins) $
|
|
| 1847 | + = [formatLocMessage (nameSrcSpan $ getName $ is_dfun ins) $
|
|
| 1848 | 1848 | ppr (overlapMode $ is_flag ins) <+>
|
| 1849 | - text "overlap mode isn't allowed in Safe Haskell"]
|
|
| 1849 | + text "overlap mode isn't allowed in Safe Haskell"
|
|
| 1850 | + ]
|
|
| 1850 | 1851 | | otherwise = []
|
| 1851 | 1852 | |
| 1852 | 1853 | -- | Figure out the final correct safe haskell mode
|
| ... | ... | @@ -1442,14 +1442,14 @@ withDeferredDiagnostics f = do |
| 1442 | 1442 | fatals <- liftIO $ newIORef []
|
| 1443 | 1443 | logger <- getLogger
|
| 1444 | 1444 | |
| 1445 | - let deferDiagnostics _dflags !msgClass !srcSpan !msg = do
|
|
| 1446 | - let action = logMsg logger msgClass srcSpan msg
|
|
| 1447 | - case msgClass of
|
|
| 1448 | - MCDiagnostic SevWarning _reason _code
|
|
| 1445 | + let deferDiagnostics _dflags !msg = do
|
|
| 1446 | + let action = logMsg logger msg
|
|
| 1447 | + case msg of
|
|
| 1448 | + MCDiagnostic _ SevWarning _reason _code
|
|
| 1449 | 1449 | -> atomicModifyIORef' warnings $ \(!i) -> (action: i, ())
|
| 1450 | - MCDiagnostic SevError _reason _code
|
|
| 1450 | + MCDiagnostic _ SevError _reason _code
|
|
| 1451 | 1451 | -> atomicModifyIORef' errors $ \(!i) -> (action: i, ())
|
| 1452 | - MCFatal
|
|
| 1452 | + MCFatal _
|
|
| 1453 | 1453 | -> atomicModifyIORef' fatals $ \(!i) -> (action: i, ())
|
| 1454 | 1454 | _ -> action
|
| 1455 | 1455 |
| ... | ... | @@ -23,8 +23,6 @@ module GHC.Driver.Monad ( |
| 23 | 23 | modifyLogger,
|
| 24 | 24 | pushLogHookM,
|
| 25 | 25 | popLogHookM,
|
| 26 | - pushJsonLogHookM,
|
|
| 27 | - popJsonLogHookM,
|
|
| 28 | 26 | putLogMsgM,
|
| 29 | 27 | putMsgM,
|
| 30 | 28 | withTimingM,
|
| ... | ... | @@ -47,7 +45,6 @@ import GHC.Utils.Exception |
| 47 | 45 | import GHC.Utils.Error
|
| 48 | 46 | import GHC.Utils.Logger
|
| 49 | 47 | |
| 50 | -import GHC.Types.SrcLoc
|
|
| 51 | 48 | import GHC.Types.SourceError
|
| 52 | 49 | |
| 53 | 50 | import Control.Monad
|
| ... | ... | @@ -123,12 +120,6 @@ pushLogHookM = modifyLogger . pushLogHook |
| 123 | 120 | popLogHookM :: GhcMonad m => m ()
|
| 124 | 121 | popLogHookM = modifyLogger popLogHook
|
| 125 | 122 | |
| 126 | -pushJsonLogHookM :: GhcMonad m => (LogJsonAction -> LogJsonAction) -> m ()
|
|
| 127 | -pushJsonLogHookM = modifyLogger . pushJsonLogHook
|
|
| 128 | - |
|
| 129 | -popJsonLogHookM :: GhcMonad m => m ()
|
|
| 130 | -popJsonLogHookM = modifyLogger popJsonLogHook
|
|
| 131 | - |
|
| 132 | 123 | -- | Put a log message
|
| 133 | 124 | putMsgM :: GhcMonad m => SDoc -> m ()
|
| 134 | 125 | putMsgM doc = do
|
| ... | ... | @@ -136,10 +127,10 @@ putMsgM doc = do |
| 136 | 127 | liftIO $ putMsg logger doc
|
| 137 | 128 | |
| 138 | 129 | -- | Put a log message
|
| 139 | -putLogMsgM :: GhcMonad m => MessageClass -> SrcSpan -> SDoc -> m ()
|
|
| 140 | -putLogMsgM msg_class loc doc = do
|
|
| 130 | +putLogMsgM :: GhcMonad m => Message -> m ()
|
|
| 131 | +putLogMsgM message = do
|
|
| 141 | 132 | logger <- getLogger
|
| 142 | - liftIO $ logMsg logger msg_class loc doc
|
|
| 133 | + liftIO $ logMsg logger message
|
|
| 143 | 134 | |
| 144 | 135 | -- | Time an action
|
| 145 | 136 | withTimingM :: GhcMonad m => SDoc -> (b -> ()) -> m b -> m b
|
| ... | ... | @@ -1162,7 +1162,7 @@ getHCFilePackages filename = |
| 1162 | 1162 | linkDynLibCheck :: Logger -> TmpFs -> DynFlags -> UnitEnv -> [String] -> [UnitId] -> IO ()
|
| 1163 | 1163 | linkDynLibCheck logger tmpfs dflags unit_env o_files dep_units = do
|
| 1164 | 1164 | when (haveRtsOptsFlags dflags) $
|
| 1165 | - logMsg logger MCInfo noSrcSpan
|
|
| 1165 | + logInfo logger
|
|
| 1166 | 1166 | $ withPprStyle defaultUserStyle
|
| 1167 | 1167 | (text "Warning: -rtsopts and -with-rtsopts have no effect with -shared." $$
|
| 1168 | 1168 | text " Call hs_init_ghc() from your main() function to set these options.")
|
| ... | ... | @@ -18,7 +18,6 @@ import GHC.Prelude |
| 18 | 18 | import Control.Concurrent
|
| 19 | 19 | import Data.IORef
|
| 20 | 20 | import GHC.Types.Error
|
| 21 | -import GHC.Types.SrcLoc
|
|
| 22 | 21 | import GHC.Utils.Logger
|
| 23 | 22 | import qualified Data.IntMap as IM
|
| 24 | 23 | import Control.Concurrent.STM
|
| ... | ... | @@ -30,7 +29,7 @@ import Control.Monad |
| 30 | 29 | -- to. A 'Nothing' value contains the result of compilation, and denotes the
|
| 31 | 30 | -- end of the message queue.
|
| 32 | 31 | data LogQueue = LogQueue { logQueueId :: !Int
|
| 33 | - , logQueueMessages :: !(IORef [Maybe (MessageClass, SrcSpan, SDoc, LogFlags)])
|
|
| 32 | + , logQueueMessages :: !(IORef [Maybe (Message, LogFlags)])
|
|
| 34 | 33 | , logQueueSemaphore :: !(MVar ())
|
| 35 | 34 | }
|
| 36 | 35 | |
| ... | ... | @@ -45,12 +44,12 @@ finishLogQueue lq = do |
| 45 | 44 | writeLogQueueInternal lq Nothing
|
| 46 | 45 | |
| 47 | 46 | |
| 48 | -writeLogQueue :: LogQueue -> (MessageClass,SrcSpan,SDoc, LogFlags) -> IO ()
|
|
| 47 | +writeLogQueue :: LogQueue -> (Message, LogFlags) -> IO ()
|
|
| 49 | 48 | writeLogQueue lq msg = do
|
| 50 | 49 | writeLogQueueInternal lq (Just msg)
|
| 51 | 50 | |
| 52 | 51 | -- | Internal helper for writing log messages
|
| 53 | -writeLogQueueInternal :: LogQueue -> Maybe (MessageClass,SrcSpan,SDoc, LogFlags) -> IO ()
|
|
| 52 | +writeLogQueueInternal :: LogQueue -> Maybe (Message, LogFlags) -> IO ()
|
|
| 54 | 53 | writeLogQueueInternal (LogQueue _n ref sem) msg = do
|
| 55 | 54 | atomicModifyIORef' ref $ \msgs -> (msg:msgs,())
|
| 56 | 55 | _ <- tryPutMVar sem ()
|
| ... | ... | @@ -59,8 +58,8 @@ writeLogQueueInternal (LogQueue _n ref sem) msg = do |
| 59 | 58 | -- The log_action callback that is used to synchronize messages from a
|
| 60 | 59 | -- worker thread.
|
| 61 | 60 | parLogAction :: LogQueue -> LogAction
|
| 62 | -parLogAction log_queue log_flags !msgClass !srcSpan !msg =
|
|
| 63 | - writeLogQueue log_queue (msgClass,srcSpan,msg, log_flags)
|
|
| 61 | +parLogAction log_queue log_flags !msg =
|
|
| 62 | + writeLogQueue log_queue (msg, log_flags)
|
|
| 64 | 63 | |
| 65 | 64 | -- Print each message from the log_queue using the global logger
|
| 66 | 65 | printLogs :: Logger -> LogQueue -> IO ()
|
| ... | ... | @@ -72,8 +71,8 @@ printLogs !logger (LogQueue _n ref sem) = read_msgs |
| 72 | 71 | |
| 73 | 72 | print_loop [] = read_msgs
|
| 74 | 73 | print_loop (x:xs) = case x of
|
| 75 | - Just (msgClass,srcSpan,msg,flags) -> do
|
|
| 76 | - logMsg (setLogFlags logger flags) msgClass srcSpan msg
|
|
| 74 | + Just (msg,flags) -> do
|
|
| 75 | + logMsg (setLogFlags logger flags) msg
|
|
| 77 | 76 | print_loop xs
|
| 78 | 77 | -- Exit the loop once we encounter the end marker.
|
| 79 | 78 | Nothing -> return ()
|
| ... | ... | @@ -94,7 +94,6 @@ import GHC.Types.SourceFile |
| 94 | 94 | import GHC.Types.SafeHaskell
|
| 95 | 95 | import GHC.Types.TypeEnv
|
| 96 | 96 | import GHC.Types.Unique.DSet
|
| 97 | -import GHC.Types.SrcLoc
|
|
| 98 | 97 | import GHC.Types.TyThing
|
| 99 | 98 | import GHC.Types.PkgQual
|
| 100 | 99 | |
| ... | ... | @@ -1105,7 +1104,7 @@ For some background on this choice see #15269. |
| 1105 | 1104 | showIface :: Logger -> DynFlags -> UnitState -> NameCache -> FilePath -> IO ()
|
| 1106 | 1105 | showIface logger dflags unit_state name_cache filename = do
|
| 1107 | 1106 | let profile = targetProfile dflags
|
| 1108 | - printer = logMsg logger MCOutput noSrcSpan . withPprStyle defaultDumpStyle
|
|
| 1107 | + printer = logOutput logger . withPprStyle defaultDumpStyle
|
|
| 1109 | 1108 | |
| 1110 | 1109 | -- skip the hi way check; we don't want to worry about profiled vs.
|
| 1111 | 1110 | -- non-profiled interfaces, for example.
|
| ... | ... | @@ -1119,7 +1118,7 @@ showIface logger dflags unit_state name_cache filename = do |
| 1119 | 1118 | neverQualifyModules
|
| 1120 | 1119 | neverQualifyPackages
|
| 1121 | 1120 | alwaysPrintPromTick
|
| 1122 | - logMsg logger MCDump noSrcSpan
|
|
| 1121 | + logMsg logger $ MCDump
|
|
| 1123 | 1122 | $ withPprStyle (mkDumpStyle name_ppr_ctx)
|
| 1124 | 1123 | $ pprModIface unit_state iface
|
| 1125 | 1124 |
| ... | ... | @@ -25,6 +25,7 @@ import GHC.Linker.Types |
| 25 | 25 | import GHC.Types.SrcLoc
|
| 26 | 26 | import GHC.Types.Unique.DSet
|
| 27 | 27 | import GHC.Types.Unique.DFM
|
| 28 | +import GHC.Types.Error (formatFatalLocMessage)
|
|
| 28 | 29 | |
| 29 | 30 | import GHC.Utils.Outputable
|
| 30 | 31 | import GHC.Utils.Panic
|
| ... | ... | @@ -231,7 +232,7 @@ splice point about what we would prefer. |
| 231 | 232 | -}
|
| 232 | 233 | |
| 233 | 234 | dieWith :: LinkDepsOpts -> SrcSpan -> SDoc -> IO a
|
| 234 | -dieWith opts span msg = throwProgramError opts (mkLocMessage MCFatal span msg)
|
|
| 235 | +dieWith opts span msg = throwProgramError opts (formatFatalLocMessage span msg)
|
|
| 235 | 236 | |
| 236 | 237 | throwProgramError :: LinkDepsOpts -> SDoc -> IO a
|
| 237 | 238 | throwProgramError opts doc = throwGhcExceptionIO (ProgramError (renderWithContext (ldPprOpts opts) doc))
|
| ... | ... | @@ -507,7 +507,7 @@ classifyLdInput logger platform f |
| 507 | 507 | | isObjectFilename platform f = return (Just (Objects [f]))
|
| 508 | 508 | | isDynLibFilename platform f = return (Just (DLLPath f))
|
| 509 | 509 | | otherwise = do
|
| 510 | - logMsg logger MCInfo noSrcSpan
|
|
| 510 | + logInfo logger
|
|
| 511 | 511 | $ withPprStyle defaultUserStyle
|
| 512 | 512 | (text ("Warning: ignoring unrecognised input `" ++ f ++ "'"))
|
| 513 | 513 | return Nothing
|
| ... | ... | @@ -1638,9 +1638,8 @@ addEnvPaths name list |
| 1638 | 1638 | maybePutSDoc :: Logger -> SDoc -> IO ()
|
| 1639 | 1639 | maybePutSDoc logger s
|
| 1640 | 1640 | = when (logVerbAtLeast logger 2) $
|
| 1641 | - logMsg logger
|
|
| 1641 | + logMsg logger $
|
|
| 1642 | 1642 | MCInteractive
|
| 1643 | - noSrcSpan
|
|
| 1644 | 1643 | $ withPprStyle defaultUserStyle s
|
| 1645 | 1644 | |
| 1646 | 1645 | maybePutStr :: Logger -> String -> IO ()
|
| ... | ... | @@ -209,7 +209,7 @@ showTerm term = do |
| 209 | 209 | setSession new_env
|
| 210 | 210 | |
| 211 | 211 | -- this disables logging of errors
|
| 212 | - let noop_log _ _ _ _ = return ()
|
|
| 212 | + let noop_log _ _ = return ()
|
|
| 213 | 213 | pushLogHookM (const noop_log)
|
| 214 | 214 | |
| 215 | 215 | return (hsc_env, bname)
|
| ... | ... | @@ -104,6 +104,7 @@ import GHC.Stg.Utils |
| 104 | 104 | import GHC.Core.DataCon
|
| 105 | 105 | import GHC.Core ( AltCon(..) )
|
| 106 | 106 | import GHC.Core.Type
|
| 107 | +import GHC.Core.Lint ( lintMessage )
|
|
| 107 | 108 | |
| 108 | 109 | import GHC.Types.Basic ( TopLevelFlag(..), isTopLevel, isMarkedCbv )
|
| 109 | 110 | import GHC.Types.CostCentre ( isCurrentCCS )
|
| ... | ... | @@ -148,8 +149,7 @@ lintStgTopBindings platform logger diag_opts opts extra_vars this_mod unarised w |
| 148 | 149 | Nothing ->
|
| 149 | 150 | return ()
|
| 150 | 151 | Just msg -> do
|
| 151 | - logMsg logger Err.MCInfo noSrcSpan -- See Note [MCInfo for Lint] in "GHC.Core.Lint"
|
|
| 152 | - $ withPprStyle defaultDumpStyle
|
|
| 152 | + lintMessage logger
|
|
| 153 | 153 | (vcat [ text "*** Stg Lint ErrMsgs: in" <+>
|
| 154 | 154 | text whodunit <+> text "***",
|
| 155 | 155 | msg,
|
| ... | ... | @@ -864,7 +864,7 @@ wrapDocLoc doc = do |
| 864 | 864 | if logHasDumpFlag logger Opt_D_ppr_debug
|
| 865 | 865 | then do
|
| 866 | 866 | loc <- getSrcSpanM
|
| 867 | - return (mkLocMessage MCOutput loc doc)
|
|
| 867 | + return (formatLocMessage loc doc)
|
|
| 868 | 868 | else
|
| 869 | 869 | return doc
|
| 870 | 870 | |
| ... | ... | @@ -2343,8 +2343,7 @@ failIfM msg = do |
| 2343 | 2343 | env <- getLclEnv
|
| 2344 | 2344 | let full_msg = (if_loc env <> colon) $$ nest 2 msg
|
| 2345 | 2345 | logger <- getLogger
|
| 2346 | - liftIO (logMsg logger MCFatal
|
|
| 2347 | - noSrcSpan $ withPprStyle defaultErrStyle full_msg)
|
|
| 2346 | + liftIO $ fatalErrorMsg logger full_msg
|
|
| 2348 | 2347 | failM
|
| 2349 | 2348 | |
| 2350 | 2349 | --------------------
|
| ... | ... | @@ -2376,10 +2375,7 @@ forkM doc thing_inside |
| 2376 | 2375 | logger <- getLogger
|
| 2377 | 2376 | let msg = hang (text "forkM failed:" <+> doc)
|
| 2378 | 2377 | 2 (text (show exn))
|
| 2379 | - liftIO $ logMsg logger
|
|
| 2380 | - MCFatal
|
|
| 2381 | - noSrcSpan
|
|
| 2382 | - $ withPprStyle defaultErrStyle msg
|
|
| 2378 | + liftIO $ fatalErrorMsg logger msg
|
|
| 2383 | 2379 | ; traceIf (text "} ending fork (badly)" <+> doc)
|
| 2384 | 2380 | ; pgmError "Cannot continue after interface file error" }
|
| 2385 | 2381 | }
|
| ... | ... | @@ -26,7 +26,7 @@ module GHC.Types.Error |
| 26 | 26 | |
| 27 | 27 | -- * Classifying Messages
|
| 28 | 28 | |
| 29 | - , MessageClass (MCDiagnostic, ..)
|
|
| 29 | + , Message (MCDiagnostic, ..)
|
|
| 30 | 30 | , Severity (..)
|
| 31 | 31 | , Diagnostic (..)
|
| 32 | 32 | , UnknownDiagnostic (..)
|
| ... | ... | @@ -70,8 +70,8 @@ module GHC.Types.Error |
| 70 | 70 | , mapDecoratedSDoc
|
| 71 | 71 | |
| 72 | 72 | , pprMessageBag
|
| 73 | - , mkLocMessage
|
|
| 74 | - , mkLocMessageWarningGroups
|
|
| 73 | + , formatLocMessage
|
|
| 74 | + , formatFatalLocMessage
|
|
| 75 | 75 | , formatDiagnostic
|
| 76 | 76 | , getCaretDiagnostic
|
| 77 | 77 | |
| ... | ... | @@ -479,22 +479,22 @@ data MsgEnvelope e = MsgEnvelope |
| 479 | 479 | -- | The class for a diagnostic message. The main purpose is to classify a
|
| 480 | 480 | -- message within GHC, to distinguish it from a debug/dump message vs a proper
|
| 481 | 481 | -- diagnostic, for which we include a 'DiagnosticReason'.
|
| 482 | -data MessageClass
|
|
| 483 | - = MCOutput
|
|
| 484 | - | MCFatal
|
|
| 485 | - | MCInteractive
|
|
| 482 | +data Message
|
|
| 483 | + = MCOutput SDoc
|
|
| 484 | + | MCFatal SDoc
|
|
| 485 | + | MCInteractive SDoc
|
|
| 486 | 486 | |
| 487 | - | MCDump
|
|
| 487 | + | MCDump SDoc
|
|
| 488 | 488 | -- ^ Log message intended for compiler developers
|
| 489 | 489 | -- No file\/line\/column stuff
|
| 490 | 490 | |
| 491 | - | MCInfo
|
|
| 491 | + | MCInfo SDoc
|
|
| 492 | 492 | -- ^ Log messages intended for end users.
|
| 493 | 493 | -- No file\/line\/column stuff.
|
| 494 | 494 | |
| 495 | - | UnsafeMCDiagnostic Severity ResolvedDiagnosticReason (Maybe DiagnosticCode)
|
|
| 495 | + | UnsafeMCDiagnostic SrcSpan Severity ResolvedDiagnosticReason (Maybe DiagnosticCode) SDoc JsonDoc
|
|
| 496 | 496 | -- ^ Diagnostics from the compiler. This constructor is very powerful as
|
| 497 | - -- it allows the construction of a 'MessageClass' with a completely
|
|
| 497 | + -- it allows the construction of a 'Message' with a completely
|
|
| 498 | 498 | -- arbitrary permutation of 'Severity' and 'DiagnosticReason'. As such,
|
| 499 | 499 | -- users are encouraged to use higher level primitives
|
| 500 | 500 | -- instead. Use this constructor directly only if you need to construct
|
| ... | ... | @@ -508,8 +508,8 @@ data MessageClass |
| 508 | 508 | -- should always have a 'DiagnosticCode'. See Note [Diagnostic codes].
|
| 509 | 509 | |
| 510 | 510 | {-# COMPLETE MCOutput, MCFatal, MCInteractive, MCDump, MCInfo, MCDiagnostic #-}
|
| 511 | -pattern MCDiagnostic :: Severity -> ResolvedDiagnosticReason -> Maybe DiagnosticCode -> MessageClass
|
|
| 512 | -pattern MCDiagnostic severity reason code <- UnsafeMCDiagnostic severity reason code
|
|
| 511 | +pattern MCDiagnostic :: SrcSpan -> Severity -> ResolvedDiagnosticReason -> Maybe DiagnosticCode -> Message
|
|
| 512 | +pattern MCDiagnostic span severity reason code <- UnsafeMCDiagnostic span severity reason code _diagnostic _json
|
|
| 513 | 513 | |
| 514 | 514 | {-
|
| 515 | 515 | Note [Suppressing Messages]
|
| ... | ... | @@ -538,9 +538,6 @@ the "SevIgnore one" for a number of reasons: |
| 538 | 538 | |
| 539 | 539 | |
| 540 | 540 | -- | Used to describe warnings and errors
|
| 541 | --- o The message has a file\/line\/column heading,
|
|
| 542 | --- plus "warning:" or "error:",
|
|
| 543 | --- added by mkLocMessage
|
|
| 544 | 541 | -- o With 'SevIgnore' the message is suppressed
|
| 545 | 542 | -- o Output is intended for end users
|
| 546 | 543 | data Severity
|
| ... | ... | @@ -637,35 +634,14 @@ showMsgEnvelope err = |
| 637 | 634 | pprMessageBag :: Bag SDoc -> SDoc
|
| 638 | 635 | pprMessageBag msgs = vcat (punctuate blankLine (bagToList msgs))
|
| 639 | 636 | |
| 640 | -mkLocMessage
|
|
| 641 | - :: MessageClass -- ^ What kind of message?
|
|
| 642 | - -> SrcSpan -- ^ location
|
|
| 643 | - -> SDoc -- ^ message
|
|
| 644 | - -> SDoc
|
|
| 645 | -mkLocMessage = mkLocMessageWarningGroups True
|
|
| 646 | - |
|
| 647 | --- | Make an error message with location info, specifying whether to show
|
|
| 648 | --- warning groups (if applicable).
|
|
| 649 | -mkLocMessageWarningGroups
|
|
| 650 | - :: Bool -- ^ Print warning groups (if applicable)?
|
|
| 651 | - -> MessageClass -- ^ What kind of message?
|
|
| 652 | - -> SrcSpan -- ^ location
|
|
| 653 | - -> SDoc -- ^ message
|
|
| 654 | - -> SDoc
|
|
| 655 | -mkLocMessageWarningGroups show_warn_groups msg_class locn msg
|
|
| 656 | - = case msg_class of
|
|
| 657 | - MCDiagnostic severity reason code -> formatDiagnostic show_warn_groups locn severity reason code msg
|
|
| 658 | - _ -> sdocOption sdocColScheme $ \col_scheme ->
|
|
| 659 | - let
|
|
| 660 | - msg_colour = getMessageClassColour msg_class col_scheme
|
|
| 661 | - |
|
| 662 | - msg_title = coloured msg_colour $
|
|
| 663 | - case msg_class of
|
|
| 664 | - MCFatal -> text "fatal"
|
|
| 665 | - _ -> empty
|
|
| 666 | - |
|
| 637 | +formatFatalLocMessage :: SrcSpan -> SDoc -> SDoc
|
|
| 638 | +formatFatalLocMessage locn msg = sdocOption sdocColScheme $ \col_scheme ->
|
|
| 639 | + let msg_title = coloured (Col.sFatal col_scheme) $ text "fatal"
|
|
| 667 | 640 | in formatLocMessageWarningGroups locn msg_title empty empty msg
|
| 668 | 641 | |
| 642 | +formatLocMessage :: SrcSpan -> SDoc -> SDoc
|
|
| 643 | +formatLocMessage span = formatLocMessageWarningGroups span empty empty empty
|
|
| 644 | + |
|
| 669 | 645 | formatDiagnostic
|
| 670 | 646 | :: Bool -- ^ Print warning groups?
|
| 671 | 647 | -> SrcSpan -- ^ location
|
| ... | ... | @@ -775,13 +751,7 @@ formatLocMessageWarningGroups locn msg_title code_doc warning_flag_doc msg |
| 775 | 751 | code_doc <+> warning_flag_doc
|
| 776 | 752 | |
| 777 | 753 | in coloured (Col.sMessage col_scheme)
|
| 778 | - (hang (coloured (Col.sHeader col_scheme) header) 4
|
|
| 779 | - msg)
|
|
| 780 | - |
|
| 781 | -getMessageClassColour :: MessageClass -> Col.Scheme -> Col.PprColour
|
|
| 782 | -getMessageClassColour (MCDiagnostic severity _reason _code) = getSeverityColour severity
|
|
| 783 | -getMessageClassColour MCFatal = Col.sFatal
|
|
| 784 | -getMessageClassColour _ = const mempty
|
|
| 754 | + $ hang (coloured (Col.sHeader col_scheme) header) 4 msg
|
|
| 785 | 755 | |
| 786 | 756 | getSeverityColour :: Severity -> Col.Scheme -> Col.PprColour
|
| 787 | 757 | getSeverityColour severity = case severity of
|
| ... | ... | @@ -789,9 +759,9 @@ getSeverityColour severity = case severity of |
| 789 | 759 | SevWarning -> Col.sWarning
|
| 790 | 760 | SevIgnore -> const mempty
|
| 791 | 761 | |
| 792 | -getCaretDiagnostic :: MessageClass -> SrcSpan -> IO SDoc
|
|
| 762 | +getCaretDiagnostic :: Severity -> SrcSpan -> IO SDoc
|
|
| 793 | 763 | getCaretDiagnostic _ (UnhelpfulSpan _) = pure empty
|
| 794 | -getCaretDiagnostic msg_class (RealSrcSpan span _) =
|
|
| 764 | +getCaretDiagnostic severity (RealSrcSpan span _) =
|
|
| 795 | 765 | caretDiagnostic <$> getSrcLine (srcSpanFile span) row
|
| 796 | 766 | where
|
| 797 | 767 | getSrcLine fn i =
|
| ... | ... | @@ -824,7 +794,7 @@ getCaretDiagnostic msg_class (RealSrcSpan span _) = |
| 824 | 794 | caretDiagnostic Nothing = empty
|
| 825 | 795 | caretDiagnostic (Just srcLineWithNewline) =
|
| 826 | 796 | sdocOption sdocColScheme$ \col_scheme ->
|
| 827 | - let sevColour = getMessageClassColour msg_class col_scheme
|
|
| 797 | + let sevColour = getSeverityColour severity col_scheme
|
|
| 828 | 798 | marginColour = Col.sMargin col_scheme
|
| 829 | 799 | in
|
| 830 | 800 | coloured marginColour (text marginSpace) <>
|
| ... | ... | @@ -14,7 +14,7 @@ module GHC.Utils.Error ( |
| 14 | 14 | -- * Messages
|
| 15 | 15 | Diagnostic(..),
|
| 16 | 16 | MsgEnvelope(..),
|
| 17 | - MessageClass(..),
|
|
| 17 | + Message(..),
|
|
| 18 | 18 | SDoc,
|
| 19 | 19 | DecoratedSDoc(unDecorated),
|
| 20 | 20 | Messages,
|
| ... | ... | @@ -28,7 +28,7 @@ module GHC.Utils.Error ( |
| 28 | 28 | |
| 29 | 29 | -- ** Construction
|
| 30 | 30 | DiagOpts (..), emptyDiagOpts, diag_wopt, diag_fatal_wopt,
|
| 31 | - emptyMessages, mkDecorated, mkLocMessage,
|
|
| 31 | + emptyMessages, mkDecorated,
|
|
| 32 | 32 | mkMsgEnvelope, mkPlainMsgEnvelope, mkPlainErrorMsgEnvelope,
|
| 33 | 33 | mkErrorMsgEnvelope,
|
| 34 | 34 | mkLintWarning, diagReasonSeverity,
|
| ... | ... | @@ -282,9 +282,8 @@ unsafePprLocMsgEnvelope opts (MsgEnvelope { errMsgSpan = s |
| 282 | 282 | , errMsgContext = name_ppr_ctx
|
| 283 | 283 | , errMsgReason = reason })
|
| 284 | 284 | = withErrStyle name_ppr_ctx $
|
| 285 | - mkLocMessage
|
|
| 286 | - (UnsafeMCDiagnostic sev reason (diagnosticCode e))
|
|
| 287 | - s
|
|
| 285 | + formatDiagnostic True
|
|
| 286 | + s sev reason (diagnosticCode e)
|
|
| 288 | 287 | (formatBulleted $ diagnosticMessage opts e)
|
| 289 | 288 | |
| 290 | 289 | sortMsgBag :: Maybe DiagOpts -> Bag (MsgEnvelope e) -> [MsgEnvelope e]
|
| ... | ... | @@ -314,7 +313,7 @@ ghcExit logger val |
| 314 | 313 | |
| 315 | 314 | fatalErrorMsg :: Logger -> SDoc -> IO ()
|
| 316 | 315 | fatalErrorMsg logger msg =
|
| 317 | - logMsg logger MCFatal noSrcSpan $ withPprStyle defaultErrStyle msg
|
|
| 316 | + logMsg logger $ MCFatal (withPprStyle defaultErrStyle msg)
|
|
| 318 | 317 | |
| 319 | 318 | compilationProgressMsg :: Logger -> SDoc -> IO ()
|
| 320 | 319 | compilationProgressMsg logger msg = do
|
| ... | ... | @@ -475,11 +474,11 @@ printOutputForUser logger name_ppr_ctx msg |
| 475 | 474 | = logOutput logger (withUserStyle name_ppr_ctx AllTheWay msg)
|
| 476 | 475 | |
| 477 | 476 | logInfo :: Logger -> SDoc -> IO ()
|
| 478 | -logInfo logger msg = logMsg logger MCInfo noSrcSpan msg
|
|
| 477 | +logInfo logger = logMsg logger . MCInfo
|
|
| 479 | 478 | |
| 480 | 479 | -- | Like 'logInfo' but with 'SevOutput' rather then 'SevInfo'
|
| 481 | 480 | logOutput :: Logger -> SDoc -> IO ()
|
| 482 | -logOutput logger msg = logMsg logger MCOutput noSrcSpan msg
|
|
| 481 | +logOutput logger = logMsg logger . MCOutput
|
|
| 483 | 482 | |
| 484 | 483 | |
| 485 | 484 | prettyPrintGhcErrors :: ExceptionMonad m => Logger -> m a -> m a
|
| ... | ... | @@ -24,7 +24,6 @@ module GHC.Utils.Logger |
| 24 | 24 | -- * Logger setup
|
| 25 | 25 | , initLogger
|
| 26 | 26 | , LogAction
|
| 27 | - , LogJsonAction
|
|
| 28 | 27 | , DumpAction
|
| 29 | 28 | , TraceAction
|
| 30 | 29 | , DumpFormat (..)
|
| ... | ... | @@ -32,8 +31,6 @@ module GHC.Utils.Logger |
| 32 | 31 | -- ** Hooks
|
| 33 | 32 | , popLogHook
|
| 34 | 33 | , pushLogHook
|
| 35 | - , popJsonLogHook
|
|
| 36 | - , pushJsonLogHook
|
|
| 37 | 34 | , popDumpHook
|
| 38 | 35 | , pushDumpHook
|
| 39 | 36 | , popTraceHook
|
| ... | ... | @@ -55,15 +52,11 @@ module GHC.Utils.Logger |
| 55 | 52 | , putLogMsg
|
| 56 | 53 | , defaultLogAction
|
| 57 | 54 | , defaultLogActionWithHandles
|
| 58 | - , defaultLogJsonAction
|
|
| 59 | 55 | , defaultLogActionHPrintDoc
|
| 60 | 56 | , defaultLogActionHPutStrDoc
|
| 61 | 57 | , logMsg
|
| 62 | - , logJsonMsg
|
|
| 63 | 58 | , logDumpMsg
|
| 64 | 59 | |
| 65 | - , decorateDiagnostic
|
|
| 66 | - |
|
| 67 | 60 | -- * Dumping
|
| 68 | 61 | , defaultDumpAction
|
| 69 | 62 | , putDumpFile
|
| ... | ... | @@ -85,12 +78,11 @@ where |
| 85 | 78 | import GHC.Prelude
|
| 86 | 79 | import GHC.Driver.Flags
|
| 87 | 80 | import GHC.Types.Error
|
| 88 | -import GHC.Types.SrcLoc
|
|
| 89 | 81 | |
| 90 | 82 | import qualified GHC.Utils.Ppr as Pretty
|
| 91 | 83 | import GHC.Utils.Outputable
|
| 92 | -import GHC.Utils.Json
|
|
| 93 | 84 | import GHC.Utils.Panic
|
| 85 | +import GHC.Utils.Json (renderJSON)
|
|
| 94 | 86 | |
| 95 | 87 | import GHC.Data.EnumSet (EnumSet)
|
| 96 | 88 | import qualified GHC.Data.EnumSet as EnumSet
|
| ... | ... | @@ -181,16 +173,9 @@ setLogFlags logger flags = logger { logFlags = flags } |
| 181 | 173 | ---------------------------------------------------------------
|
| 182 | 174 | |
| 183 | 175 | type LogAction = LogFlags
|
| 184 | - -> MessageClass
|
|
| 185 | - -> SrcSpan
|
|
| 186 | - -> SDoc
|
|
| 176 | + -> Message
|
|
| 187 | 177 | -> IO ()
|
| 188 | 178 | |
| 189 | -type LogJsonAction = LogFlags
|
|
| 190 | - -> MessageClass
|
|
| 191 | - -> JsonDoc
|
|
| 192 | - -> IO ()
|
|
| 193 | - |
|
| 194 | 179 | type DumpAction = LogFlags
|
| 195 | 180 | -> PprStyle
|
| 196 | 181 | -> DumpFlag
|
| ... | ... | @@ -228,9 +213,6 @@ data Logger = Logger |
| 228 | 213 | { log_hook :: [LogAction -> LogAction]
|
| 229 | 214 | -- ^ Log hooks stack
|
| 230 | 215 | |
| 231 | - , json_log_hook :: [LogJsonAction -> LogJsonAction]
|
|
| 232 | - -- ^ Json log hooks stack
|
|
| 233 | - |
|
| 234 | 216 | , dump_hook :: [DumpAction -> DumpAction]
|
| 235 | 217 | -- ^ Dump hooks stack
|
| 236 | 218 | |
| ... | ... | @@ -266,7 +248,6 @@ initLogger = do |
| 266 | 248 | dumps <- newMVar Map.empty
|
| 267 | 249 | return $ Logger
|
| 268 | 250 | { log_hook = []
|
| 269 | - , json_log_hook = []
|
|
| 270 | 251 | , dump_hook = []
|
| 271 | 252 | , trace_hook = []
|
| 272 | 253 | , generated_dumps = dumps
|
| ... | ... | @@ -278,10 +259,6 @@ initLogger = do |
| 278 | 259 | putLogMsg :: Logger -> LogAction
|
| 279 | 260 | putLogMsg logger = foldr ($) defaultLogAction (log_hook logger)
|
| 280 | 261 | |
| 281 | --- | Log a JsonDoc
|
|
| 282 | -putJsonLogMsg :: Logger -> LogJsonAction
|
|
| 283 | -putJsonLogMsg logger = foldr ($) defaultLogJsonAction (json_log_hook logger)
|
|
| 284 | - |
|
| 285 | 262 | -- | Dump something
|
| 286 | 263 | putDumpFile :: Logger -> DumpAction
|
| 287 | 264 | putDumpFile logger =
|
| ... | ... | @@ -306,15 +283,6 @@ popLogHook logger = case log_hook logger of |
| 306 | 283 | [] -> panic "popLogHook: empty hook stack"
|
| 307 | 284 | _:hs -> logger { log_hook = hs }
|
| 308 | 285 | |
| 309 | --- | Push a json log hook
|
|
| 310 | -pushJsonLogHook :: (LogJsonAction -> LogJsonAction) -> Logger -> Logger
|
|
| 311 | -pushJsonLogHook h logger = logger { json_log_hook = h:json_log_hook logger }
|
|
| 312 | - |
|
| 313 | -popJsonLogHook :: Logger -> Logger
|
|
| 314 | -popJsonLogHook logger = case json_log_hook logger of
|
|
| 315 | - [] -> panic "popJsonLogHook: empty hook stack"
|
|
| 316 | - _:hs -> logger { json_log_hook = hs}
|
|
| 317 | - |
|
| 318 | 286 | -- | Push a dump hook
|
| 319 | 287 | pushDumpHook :: (DumpAction -> DumpAction) -> Logger -> Logger
|
| 320 | 288 | pushDumpHook h logger = logger { dump_hook = h:dump_hook logger }
|
| ... | ... | @@ -343,8 +311,8 @@ makeThreadSafe logger = do |
| 343 | 311 | with_lock :: forall a. IO a -> IO a
|
| 344 | 312 | with_lock act = withMVar lock (const act)
|
| 345 | 313 | |
| 346 | - log action logflags msg_class loc doc =
|
|
| 347 | - with_lock (action logflags msg_class loc doc)
|
|
| 314 | + log action logflags message =
|
|
| 315 | + with_lock (action logflags message)
|
|
| 348 | 316 | |
| 349 | 317 | dmp action logflags sty opts str fmt doc =
|
| 350 | 318 | with_lock (action logflags sty opts str fmt doc)
|
| ... | ... | @@ -358,22 +326,6 @@ makeThreadSafe logger = do |
| 358 | 326 | $ pushTraceHook trc
|
| 359 | 327 | $ logger
|
| 360 | 328 | |
| 361 | -defaultLogJsonAction :: LogJsonAction
|
|
| 362 | -defaultLogJsonAction logflags msg_class jsdoc =
|
|
| 363 | - case msg_class of
|
|
| 364 | - MCOutput -> printOut msg
|
|
| 365 | - MCDump -> printOut (msg $$ blankLine)
|
|
| 366 | - MCInteractive -> putStrSDoc msg
|
|
| 367 | - MCInfo -> printErrs msg
|
|
| 368 | - MCFatal -> printErrs msg
|
|
| 369 | - MCDiagnostic SevIgnore _ _ -> pure () -- suppress the message
|
|
| 370 | - MCDiagnostic _sev _rea _code -> printErrs msg
|
|
| 371 | - where
|
|
| 372 | - printOut = defaultLogActionHPrintDoc logflags False stdout
|
|
| 373 | - printErrs = defaultLogActionHPrintDoc logflags False stderr
|
|
| 374 | - putStrSDoc = defaultLogActionHPutStrDoc logflags False stdout
|
|
| 375 | - msg = renderJSON jsdoc
|
|
| 376 | - |
|
| 377 | 329 | -- | The default 'LogAction' prints to 'stdout' and 'stderr'.
|
| 378 | 330 | --
|
| 379 | 331 | -- To replicate the default log action behaviour with different @out@ and @err@
|
| ... | ... | @@ -384,71 +336,24 @@ defaultLogAction = defaultLogActionWithHandles stdout stderr |
| 384 | 336 | -- | The default 'LogAction' parametrized over the standard output and standard error handles.
|
| 385 | 337 | -- Allows clients to replicate the log message formatting of GHC with custom handles.
|
| 386 | 338 | defaultLogActionWithHandles :: Handle {-^ Handle for standard output -} -> Handle {-^ Handle for standard errors -} -> LogAction
|
| 387 | -defaultLogActionWithHandles out err logflags msg_class srcSpan msg
|
|
| 388 | - = case msg_class of
|
|
| 389 | - MCOutput -> printOut msg
|
|
| 390 | - MCDump -> printOut (msg $$ blankLine)
|
|
| 391 | - MCInteractive -> putStrSDoc msg
|
|
| 392 | - MCInfo -> printErrs msg
|
|
| 393 | - MCFatal -> printErrs msg
|
|
| 394 | - MCDiagnostic SevIgnore _ _ -> pure () -- suppress the message
|
|
| 395 | - MCDiagnostic _sev _rea _code -> decorateDiagnostic logflags msg_class srcSpan msg >>= printErrs
|
|
| 339 | +defaultLogActionWithHandles out err logflags message
|
|
| 340 | + = case message of
|
|
| 341 | + MCOutput msg -> printOut msg
|
|
| 342 | + MCDump msg -> printOut (msg $$ blankLine)
|
|
| 343 | + MCInteractive msg -> putStrSDoc msg
|
|
| 344 | + MCInfo msg -> printErrs msg
|
|
| 345 | + MCFatal msg -> printErrs msg
|
|
| 346 | + MCDiagnostic _ SevIgnore _ _ -> pure () -- suppress the message
|
|
| 347 | + UnsafeMCDiagnostic _span _severity _reason _code doc json -> do
|
|
| 348 | + if log_diagnostics_as_json logflags then do
|
|
| 349 | + printErrs (renderJSON json)
|
|
| 350 | + else do
|
|
| 351 | + printErrs doc
|
|
| 396 | 352 | where
|
| 397 | 353 | printOut = defaultLogActionHPrintDoc logflags False out
|
| 398 | 354 | printErrs = defaultLogActionHPrintDoc logflags False err
|
| 399 | 355 | putStrSDoc = defaultLogActionHPutStrDoc logflags False out
|
| 400 | 356 | |
| 401 | --- This function is used by `defaultLogActionWithHandles` for non-JSON output,
|
|
| 402 | --- and also by `GHC.Driver.Errors.printMessages` to produce the `rendered`
|
|
| 403 | --- message on `-fdiagnostics-as-json`.
|
|
| 404 | ---
|
|
| 405 | --- We would want to eventually consolidate this. However, this is currently
|
|
| 406 | --- not feasible for the following reasons:
|
|
| 407 | ---
|
|
| 408 | --- 1. Some parts of the compiler sidestep `printMessages`, for that reason we
|
|
| 409 | --- can not decorate the message in `printMessages`.
|
|
| 410 | ---
|
|
| 411 | --- 2. GHC uses two different code paths for JSON and non-JSON diagnostics. For
|
|
| 412 | --- that reason we can not decorate the message in `defaultLogActionWithHandles`.
|
|
| 413 | ---
|
|
| 414 | --- See also Note [JSON Error Messages]:
|
|
| 415 | ---
|
|
| 416 | --- `jsonLogAction` should be removed along with -ddump-json
|
|
| 417 | ---
|
|
| 418 | --- Also note that (1) is the reason why some parts of the compiler produce
|
|
| 419 | --- diagnostics that don't respect `-fdiagnostics-as-json`.
|
|
| 420 | ---
|
|
| 421 | --- The plan as I see it is as follows:
|
|
| 422 | ---
|
|
| 423 | --- 1. Refactor all places in the compiler that report diagnostics to go
|
|
| 424 | --- through `GHC.Driver.Errors.printMessages`.
|
|
| 425 | ---
|
|
| 426 | --- (It's easy to find all those places by looking for who creates
|
|
| 427 | --- MCDiagnostic, either directly or via `mkMCDiagnostic` or
|
|
| 428 | --- `errorDiagnostic`.)
|
|
| 429 | ---
|
|
| 430 | --- 2. Get rid of `-ddump-json`, `jsonLogAction` and consolidate message
|
|
| 431 | --- decoration at one place (either `printMessages` or
|
|
| 432 | --- `defaultLogActionWithHandles`)
|
|
| 433 | ---
|
|
| 434 | --- This story is tracked by #24113.
|
|
| 435 | -decorateDiagnostic :: LogFlags -> MessageClass -> SrcSpan -> SDoc -> IO SDoc
|
|
| 436 | -decorateDiagnostic logflags msg_class srcSpan msg = addCaret
|
|
| 437 | - where
|
|
| 438 | - -- Pretty print the warning flag, if any (#10752)
|
|
| 439 | - message :: SDoc
|
|
| 440 | - message = mkLocMessageWarningGroups (log_show_warn_groups logflags) msg_class srcSpan msg
|
|
| 441 | - |
|
| 442 | - addCaret :: IO SDoc
|
|
| 443 | - addCaret = do
|
|
| 444 | - caretDiagnostic <-
|
|
| 445 | - if log_show_caret logflags
|
|
| 446 | - then getCaretDiagnostic msg_class srcSpan
|
|
| 447 | - else pure empty
|
|
| 448 | - return $ getPprStyle $ \style ->
|
|
| 449 | - withPprStyle (setStyleColoured True style)
|
|
| 450 | - (message $+$ caretDiagnostic $+$ blankLine)
|
|
| 451 | - |
|
| 452 | 357 | -- | Like 'defaultLogActionHPutStrDoc' but appends an extra newline.
|
| 453 | 358 | defaultLogActionHPrintDoc :: LogFlags -> Bool -> Handle -> SDoc -> IO ()
|
| 454 | 359 | defaultLogActionHPrintDoc logflags asciiSpace h d
|
| ... | ... | @@ -494,10 +399,10 @@ dumpSDocWithStyle dumps log_action sty logflags flag hdr doc = |
| 494 | 399 | |
| 495 | 400 | -- write the dump to stdout
|
| 496 | 401 | writeDump Nothing = do
|
| 497 | - let (doc', msg_class)
|
|
| 498 | - | null hdr = (doc, MCOutput)
|
|
| 499 | - | otherwise = (mkDumpDoc hdr doc, MCDump)
|
|
| 500 | - log_action logflags msg_class noSrcSpan (withPprStyle sty doc')
|
|
| 402 | + let message
|
|
| 403 | + | null hdr = MCOutput (withPprStyle sty doc)
|
|
| 404 | + | otherwise = MCDump (withPprStyle sty $ mkDumpDoc hdr doc)
|
|
| 405 | + log_action logflags message
|
|
| 501 | 406 | |
| 502 | 407 | |
| 503 | 408 | -- | Run an action with the handle of a 'DumpFlag' if we are outputting to a
|
| ... | ... | @@ -587,11 +492,8 @@ defaultTraceAction logflags title doc x = |
| 587 | 492 | |
| 588 | 493 | |
| 589 | 494 | -- | Log something
|
| 590 | -logMsg :: Logger -> MessageClass -> SrcSpan -> SDoc -> IO ()
|
|
| 591 | -logMsg logger mc loc msg = putLogMsg logger (logFlags logger) mc loc msg
|
|
| 592 | - |
|
| 593 | -logJsonMsg :: Logger -> MessageClass -> JsonDoc -> IO ()
|
|
| 594 | -logJsonMsg logger mc = putJsonLogMsg logger (logFlags logger) mc
|
|
| 495 | +logMsg :: Logger -> Message -> IO ()
|
|
| 496 | +logMsg logger = putLogMsg logger (logFlags logger)
|
|
| 595 | 497 | |
| 596 | 498 | -- | Dump something
|
| 597 | 499 | logDumpFile :: Logger -> PprStyle -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
|
| ... | ... | @@ -603,7 +505,7 @@ logTraceMsg logger hdr doc a = putTraceMsg logger (logFlags logger) hdr doc a |
| 603 | 505 | |
| 604 | 506 | -- | Log a dump message (not a dump file)
|
| 605 | 507 | logDumpMsg :: Logger -> String -> SDoc -> IO ()
|
| 606 | -logDumpMsg logger hdr doc = logMsg logger MCDump noSrcSpan
|
|
| 508 | +logDumpMsg logger hdr doc = logMsg logger $ MCDump
|
|
| 607 | 509 | (withPprStyle defaultDumpStyle
|
| 608 | 510 | (mkDumpDoc hdr doc))
|
| 609 | 511 |
| ... | ... | @@ -833,10 +833,10 @@ resetLastErrorLocations = do |
| 833 | 833 | |
| 834 | 834 | ghciLogAction :: IORef [(FastString, Int)] -> LogAction -> LogAction
|
| 835 | 835 | ghciLogAction lastErrLocations old_log_action
|
| 836 | - dflags msg_class srcSpan msg = do
|
|
| 837 | - old_log_action dflags msg_class srcSpan msg
|
|
| 838 | - case msg_class of
|
|
| 839 | - MCDiagnostic SevError _reason _code -> case srcSpan of
|
|
| 836 | + dflags msg = do
|
|
| 837 | + old_log_action dflags msg
|
|
| 838 | + case msg of
|
|
| 839 | + MCDiagnostic srcSpan SevError _reason _code -> case srcSpan of
|
|
| 840 | 840 | RealSrcSpan rsp _ -> modifyIORef lastErrLocations
|
| 841 | 841 | (++ [(srcLocFile (realSrcSpanStart rsp), srcLocLine (realSrcSpanStart rsp))])
|
| 842 | 842 | _ -> return ()
|
| ... | ... | @@ -24,11 +24,11 @@ compileInGhc targets handlerOutput = do |
| 24 | 24 | flags0 <- getSessionDynFlags
|
| 25 | 25 | let flags = flags0 {verbosity = 1 }
|
| 26 | 26 | setSessionDynFlags flags
|
| 27 | - let collectSrcError handlerOutput _flags MCOutput _srcspan msg
|
|
| 27 | + let collectSrcError _flags (MCOutput msg)
|
|
| 28 | 28 | = handlerOutput $ GHC.showSDocForUser flags emptyUnitState alwaysQualify msg
|
| 29 | - collectSrcError _ _ _ _ _
|
|
| 29 | + collectSrcError _ _
|
|
| 30 | 30 | = return ()
|
| 31 | - pushLogHookM (const (collectSrcError handlerOutput))
|
|
| 31 | + pushLogHookM (const collectSrcError)
|
|
| 32 | 32 | -- Set up targets.
|
| 33 | 33 | oldTargets <- getTargets
|
| 34 | 34 | let oldFiles = map fileFromTarget oldTargets
|
| ... | ... | @@ -19,6 +19,6 @@ hooksP opts hsc_env = do |
| 19 | 19 | return hsc_env'
|
| 20 | 20 | |
| 21 | 21 | logHook :: LogAction -> LogAction
|
| 22 | -logHook action logFlags messageClass srcSpan msgDoc = do
|
|
| 22 | +logHook action logFlags message = do
|
|
| 23 | 23 | putStrLn "Log hook called"
|
| 24 | - action logFlags messageClass srcSpan msgDoc |
|
| 24 | + action logFlags message |