Simon Hengel pushed to branch wip/sol/remove-ddump-json at Glasgow Haskell Compiler / GHC

Commits:

11 changed files:

Changes:

  • compiler/GHC/Driver/Flags.hs
    ... ... @@ -526,7 +526,6 @@ data DumpFlag
    526 526
        | Opt_D_dump_view_pattern_commoning
    
    527 527
        | Opt_D_verbose_core2core
    
    528 528
        | Opt_D_dump_debug
    
    529
    -   | Opt_D_dump_json
    
    530 529
        | Opt_D_ppr_debug
    
    531 530
        | Opt_D_no_debug_output
    
    532 531
        | Opt_D_dump_faststrings
    

  • compiler/GHC/Driver/Session.hs
    ... ... @@ -1657,9 +1657,6 @@ dynamic_flags_deps = [
    1657 1657
             (NoArg (setGeneralFlag Opt_NoTypeableBinds))
    
    1658 1658
       , make_ord_flag defGhcFlag "ddump-debug"
    
    1659 1659
             (setDumpFlag Opt_D_dump_debug)
    
    1660
    -  , make_dep_flag defGhcFlag "ddump-json"
    
    1661
    -        (setDumpFlag Opt_D_dump_json)
    
    1662
    -        "Use `-fdiagnostics-as-json` instead"
    
    1663 1660
       , make_ord_flag defGhcFlag "dppr-debug"
    
    1664 1661
             (setDumpFlag Opt_D_ppr_debug)
    
    1665 1662
       , make_ord_flag defGhcFlag "ddebug-output"
    

  • compiler/GHC/Utils/Logger.hs
    ... ... @@ -92,7 +92,6 @@ import GHC.Utils.Panic
    92 92
     
    
    93 93
     import GHC.Data.EnumSet (EnumSet)
    
    94 94
     import qualified GHC.Data.EnumSet as EnumSet
    
    95
    -import GHC.Data.FastString
    
    96 95
     
    
    97 96
     import System.Directory
    
    98 97
     import System.FilePath  ( takeDirectory, (</>) )
    
    ... ... @@ -357,7 +356,6 @@ makeThreadSafe logger = do
    357 356
                $ pushTraceHook trc
    
    358 357
                $ logger
    
    359 358
     
    
    360
    --- See Note [JSON Error Messages]
    
    361 359
     defaultLogJsonAction :: LogJsonAction
    
    362 360
     defaultLogJsonAction logflags msg_class jsdoc =
    
    363 361
       case msg_class of
    
    ... ... @@ -374,32 +372,6 @@ defaultLogJsonAction logflags msg_class jsdoc =
    374 372
         putStrSDoc = defaultLogActionHPutStrDoc logflags False stdout
    
    375 373
         msg = renderJSON jsdoc
    
    376 374
     
    
    377
    --- See Note [JSON Error Messages]
    
    378
    --- this is to be removed
    
    379
    -jsonLogActionWithHandle :: Handle {-^ Standard out -} -> LogAction
    
    380
    -jsonLogActionWithHandle _ _ (MCDiagnostic SevIgnore _ _) _ _ = return () -- suppress the message
    
    381
    -jsonLogActionWithHandle out logflags msg_class srcSpan msg
    
    382
    -  =
    
    383
    -    defaultLogActionHPutStrDoc logflags True out
    
    384
    -      (withPprStyle PprCode (doc $$ text ""))
    
    385
    -    where
    
    386
    -      str = renderWithContext (log_default_user_context logflags) msg
    
    387
    -      doc = renderJSON $
    
    388
    -              JSObject [ ( "span", spanToDumpJSON srcSpan )
    
    389
    -                       , ( "doc" , JSString str )
    
    390
    -                       , ( "messageClass", json msg_class )
    
    391
    -                       ]
    
    392
    -      spanToDumpJSON :: SrcSpan -> JsonDoc
    
    393
    -      spanToDumpJSON s = case s of
    
    394
    -                 (RealSrcSpan rss _) -> JSObject [ ("file", json file)
    
    395
    -                                                , ("startLine", json $ srcSpanStartLine rss)
    
    396
    -                                                , ("startCol", json $ srcSpanStartCol rss)
    
    397
    -                                                , ("endLine", json $ srcSpanEndLine rss)
    
    398
    -                                                , ("endCol", json $ srcSpanEndCol rss)
    
    399
    -                                                ]
    
    400
    -                   where file = unpackFS $ srcSpanFile rss
    
    401
    -                 UnhelpfulSpan _ -> JSNull
    
    402
    -
    
    403 375
     -- | The default 'LogAction' prints to 'stdout' and 'stderr'.
    
    404 376
     --
    
    405 377
     -- To replicate the default log action behaviour with different @out@ and @err@
    
    ... ... @@ -411,8 +383,7 @@ defaultLogAction = defaultLogActionWithHandles stdout stderr
    411 383
     -- Allows clients to replicate the log message formatting of GHC with custom handles.
    
    412 384
     defaultLogActionWithHandles :: Handle {-^ Handle for standard output -} -> Handle {-^ Handle for standard errors -} -> LogAction
    
    413 385
     defaultLogActionWithHandles out err logflags msg_class srcSpan msg
    
    414
    -  | log_dopt Opt_D_dump_json logflags = jsonLogActionWithHandle out logflags msg_class srcSpan msg
    
    415
    -  | otherwise = case msg_class of
    
    386
    +  = case msg_class of
    
    416 387
           MCOutput                     -> printOut msg
    
    417 388
           MCDump                       -> printOut (msg $$ blankLine)
    
    418 389
           MCInteractive                -> putStrSDoc msg
    
    ... ... @@ -453,28 +424,6 @@ defaultLogActionHPutStrDoc logflags asciiSpace h d
    453 424
       -- calls to this log-action can output all on the same line
    
    454 425
       = printSDoc (log_default_user_context logflags) (Pretty.PageMode asciiSpace) h d
    
    455 426
     
    
    456
    ---
    
    457
    --- Note [JSON Error Messages]
    
    458
    --- ~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    459
    ---
    
    460
    --- When the user requests the compiler output to be dumped as json
    
    461
    --- we used to collect them all in an IORef and then print them at the end.
    
    462
    --- This doesn't work very well with GHCi. (See #14078) So instead we now
    
    463
    --- use the simpler method of just outputting a JSON document inplace to
    
    464
    --- stdout.
    
    465
    ---
    
    466
    --- Before the compiler calls log_action, it has already turned the `ErrMsg`
    
    467
    --- into a formatted message. This means that we lose some possible
    
    468
    --- information to provide to the user but refactoring log_action is quite
    
    469
    --- invasive as it is called in many places. So, for now I left it alone
    
    470
    --- and we can refine its behaviour as users request different output.
    
    471
    ---
    
    472
    --- The recent work here replaces the purpose of flag -ddump-json with
    
    473
    --- -fdiagnostics-as-json. For temporary backwards compatibility while
    
    474
    --- -ddump-json is being deprecated, `jsonLogAction` has been added in, but
    
    475
    --- it should be removed along with -ddump-json. Similarly, the guard in
    
    476
    --- `defaultLogAction` should be removed. This cleanup is tracked in #24113.
    
    477
    -
    
    478 427
     -- | Default action for 'dumpAction' hook
    
    479 428
     defaultDumpAction :: DumpCache -> LogAction -> DumpAction
    
    480 429
     defaultDumpAction dumps log_action logflags sty flag title _fmt doc =
    

  • docs/users_guide/debugging.rst
    ... ... @@ -55,13 +55,6 @@ Dumping out compiler intermediate structures
    55 55
         ``Main.p.dump-simpl`` and ``Main.dump-simpl`` instead of overwriting the
    
    56 56
         output of one way with the output of another.
    
    57 57
     
    
    58
    -.. ghc-flag:: -ddump-json
    
    59
    -    :shortdesc: *(deprecated)* Use :ghc-flag:`-fdiagnostics-as-json` instead
    
    60
    -    :type: dynamic
    
    61
    -
    
    62
    -    This flag was previously used to generated JSON formatted GHC diagnostics,
    
    63
    -    but has been deprecated. Instead, use :ghc-flag:`-fdiagnostics-as-json`.
    
    64
    -
    
    65 58
     .. ghc-flag:: -dshow-passes
    
    66 59
         :shortdesc: Print out each pass name as it happens
    
    67 60
         :type: dynamic
    

  • ghc/GHCi/UI.hs
    ... ... @@ -495,8 +495,6 @@ interactiveUI config srcs maybe_exprs = do
    495 495
     
    
    496 496
        installInteractiveHomeUnits
    
    497 497
     
    
    498
    -   -- Update the LogAction. Ensure we don't override the user's log action lest
    
    499
    -   -- we break -ddump-json (#14078)
    
    500 498
        lastErrLocationsRef <- liftIO $ newIORef []
    
    501 499
        pushLogHookM (ghciLogAction lastErrLocationsRef)
    
    502 500
     
    

  • testsuite/tests/driver/T16167.stderr
    1
    +{"version":"1.1","ghcVersion":"ghc-9.13.20250627","span":{"file":"T16167.hs","start":{"line":1,"column":8},"end":{"line":1,"column":9}},"severity":"Error","code":58481,"message":["parse error on input \u2018f\u2019"],"hints":[]}
    
    1 2
     *** Exception: ExitFailure 1

  • testsuite/tests/driver/T16167.stdout deleted
    1
    -{"span":null,"doc":"-ddump-json is deprecated: Use `-fdiagnostics-as-json` instead","messageClass":"MCDiagnostic SevWarning WarningWithFlags Opt_WarnDeprecatedFlags :| [] Just GHC-53692"}
    
    2
    -{"span":{"file":"T16167.hs","startLine":1,"startCol":8,"endLine":1,"endCol":9},"doc":"parse error on input \u2018f\u2019","messageClass":"MCDiagnostic SevError ErrorWithoutFlag Just GHC-58481"}

  • testsuite/tests/driver/all.T
    ... ... @@ -274,12 +274,11 @@ test('T12752pass', normal, compile, ['-DSHOULD_PASS=1 -Wcpp-undef'])
    274 274
     test('T12955', normal, makefile_test, [])
    
    275 275
     
    
    276 276
     test('T12971', [when(opsys('mingw32'), fragile(17945)), ignore_stdout], makefile_test, [])
    
    277
    -test('json_dump', normal, compile_fail, ['-ddump-json'])
    
    278 277
     test('json', normalise_version('ghc'), compile_fail, ['-fdiagnostics-as-json'])
    
    279 278
     test('json_warn', normalise_version('ghc'), compile, ['-fdiagnostics-as-json -Wunused-matches -Wx-partial'])
    
    280
    -test('json2', normalise_version('ghc-internal', 'base','ghc-prim'), compile, ['-ddump-types -ddump-json -Wno-unsupported-llvm-version'])
    
    279
    +test('json2', normalise_version('ghc-internal', 'base','ghc-prim'), compile, ['-ddump-types -fdiagnostics-as-json -Wno-unsupported-llvm-version'])
    
    281 280
     test('T16167', [normalise_version('ghc'),req_interp,exit_code(1)], run_command,
    
    282
    -     ['{compiler} -x hs -e ":set prog T16167.hs" -ddump-json T16167.hs'])
    
    281
    +     ['{compiler} -x hs -e ":set prog T16167.hs" -fdiagnostics-as-json T16167.hs'])
    
    283 282
     test('T13604', [], makefile_test, [])
    
    284 283
     test('T13604a',
    
    285 284
       [ js_broken(22261) # require HPC support
    

  • testsuite/tests/driver/json2.stderr
    1
    -{"span":null,"doc":"-ddump-json is deprecated: Use `-fdiagnostics-as-json` instead","messageClass":"MCDiagnostic SevWarning WarningWithFlags Opt_WarnDeprecatedFlags :| [] Just GHC-53692"}
    
    2
    -{"span":null,"doc":"TYPE SIGNATURES\n  foo :: forall a. a -> a\nDependent modules: []\nDependent packages: [(normal, base-4.21.0.0)]","messageClass":"MCOutput"}
    1
    +TYPE SIGNATURES
    
    2
    +  foo :: forall a. a -> a
    
    3
    +Dependent modules: []
    
    4
    +Dependent packages: [(normal, base-4.21.0.0)]

  • testsuite/tests/driver/json_dump.hs deleted
    1
    -module Foo where
    
    2
    -
    
    3
    -import Data.List
    
    4
    -
    
    5
    -id1 :: a -> a
    
    6
    -id1 = 5

  • testsuite/tests/driver/json_dump.stderr deleted
    1
    -{"span":null,"doc":"-ddump-json is deprecated: Use `-fdiagnostics-as-json` instead","messageClass":"MCDiagnostic SevWarning WarningWithFlags Opt_WarnDeprecatedFlags :| [] Just GHC-53692"}
    
    2
    -{"span":{"file":"json_dump.hs","startLine":6,"startCol":7,"endLine":6,"endCol":8},"doc":"\u2022 No instance for \u2018Num (a -> a)\u2019 arising from the literal \u20185\u2019\n    (maybe you haven't applied a function to enough arguments?)\n\u2022 In the expression: 5\n  In an equation for \u2018id1\u2019: id1 = 5","messageClass":"MCDiagnostic SevError ErrorWithoutFlag Just GHC-39999"}