[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: Include the rendered message in -fdiagnostics-as-json output
by Marge Bot (@marge-bot) 24 Jul '25
by Marge Bot (@marge-bot) 24 Jul '25
24 Jul '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
2217137b by Simon Hengel at 2025-07-24T00:10:59-04:00
Include the rendered message in -fdiagnostics-as-json output
This implements #26173.
- - - - -
f348d643 by Ben Gamari at 2025-07-24T00:11:00-04:00
rts/Interpreter: Factor out ctoi tuple info tables into data
Instead of a massive case let's put this into data which we can reuse
elsewhere.
- - - - -
9 changed files:
- compiler/GHC/Driver/Errors.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Utils/Logger.hs
- docs/users_guide/9.14.1-notes.rst
- + docs/users_guide/diagnostics-as-json-schema-1_2.json
- docs/users_guide/using.rst
- rts/Interpreter.c
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json_warn.stderr
Changes:
=====================================
compiler/GHC/Driver/Errors.hs
=====================================
@@ -12,6 +12,7 @@ import GHC.Prelude
import GHC.Types.SrcLoc
import GHC.Types.SourceError
import GHC.Types.Error
+import GHC.Utils.Json
import GHC.Utils.Error
import GHC.Utils.Outputable
import GHC.Utils.Logger
@@ -46,9 +47,22 @@ printMessages logger msg_opts opts = mapM_ (printMessage logger msg_opts opts) .
printMessage :: forall a. (Diagnostic a) => Logger -> DiagnosticOpts a -> DiagOpts -> MsgEnvelope a -> IO ()
printMessage logger msg_opts opts message
- | log_diags_as_json = logJsonMsg logger messageClass message
+ | log_diags_as_json = do
+ decorated <- decorateDiagnostic logflags messageClass location doc
+ let
+ rendered :: String
+ rendered = renderWithContext (log_default_user_context logflags) decorated
+
+ jsonMessage :: JsonDoc
+ jsonMessage = jsonDiagnostic rendered message
+
+ logJsonMsg logger messageClass jsonMessage
+
| otherwise = logMsg logger messageClass location doc
where
+ logflags :: LogFlags
+ logflags = logFlags logger
+
doc :: SDoc
doc = updSDocContext (\_ -> ctx) (messageWithHints diagnostic)
=====================================
compiler/GHC/Types/Error.hs
=====================================
@@ -73,6 +73,9 @@ module GHC.Types.Error
, mkLocMessage
, mkLocMessageWarningGroups
, getCaretDiagnostic
+
+ , jsonDiagnostic
+
-- * Queries
, isIntrinsicErrorMessage
, isExtrinsicErrorMessage
@@ -109,7 +112,7 @@ import GHC.Utils.Panic
import GHC.Version (cProjectVersion)
import Data.Bifunctor
-import Data.Foldable ( fold, toList )
+import Data.Foldable
import Data.List.NonEmpty ( NonEmpty (..) )
import qualified Data.List.NonEmpty as NE
import Data.List ( intercalate )
@@ -171,9 +174,6 @@ instance Diagnostic e => Outputable (Messages e) where
pprDiagnostic (errMsgDiagnostic envelope)
]
-instance (Diagnostic e) => ToJson (Messages e) where
- json msgs = JSArray . toList $ json <$> getMessages msgs
-
{- Note [Discarding Messages]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -573,7 +573,7 @@ instance ToJson DiagnosticCode where
{- Note [Diagnostic Message JSON Schema]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The below instance of ToJson must conform to the JSON schema
-specified in docs/users_guide/diagnostics-as-json-schema-1_1.json.
+specified in docs/users_guide/diagnostics-as-json-schema-1_2.json.
When the schema is altered, please bump the version.
If the content is altered in a backwards compatible way,
update the minor version (e.g. 1.3 ~> 1.4).
@@ -586,15 +586,17 @@ https://json-schema.org
-}
schemaVersion :: String
-schemaVersion = "1.1"
+schemaVersion = "1.2"
+
-- See Note [Diagnostic Message JSON Schema] before editing!
-instance Diagnostic e => ToJson (MsgEnvelope e) where
- json m = JSObject $ [
+jsonDiagnostic :: forall e. Diagnostic e => String -> MsgEnvelope e -> JsonDoc
+jsonDiagnostic rendered m = JSObject $ [
("version", JSString schemaVersion),
("ghcVersion", JSString $ "ghc-" ++ cProjectVersion),
("span", json $ errMsgSpan m),
("severity", json $ errMsgSeverity m),
("code", maybe JSNull json (diagnosticCode diag)),
+ ("rendered", JSString rendered),
("message", JSArray $ map renderToJSString diagMsg),
("hints", JSArray $ map (renderToJSString . ppr) (diagnosticHints diag) ) ]
++ [ ("reason", reasonJson)
=====================================
compiler/GHC/Utils/Logger.hs
=====================================
@@ -62,6 +62,8 @@ module GHC.Utils.Logger
, logJsonMsg
, logDumpMsg
+ , decorateDiagnostic
+
-- * Dumping
, defaultDumpAction
, putDumpFile
@@ -419,26 +421,62 @@ defaultLogActionWithHandles out err logflags msg_class srcSpan msg
MCInfo -> printErrs msg
MCFatal -> printErrs msg
MCDiagnostic SevIgnore _ _ -> pure () -- suppress the message
- MCDiagnostic _sev _rea _code -> printDiagnostics
+ MCDiagnostic _sev _rea _code -> decorateDiagnostic logflags msg_class srcSpan msg >>= printErrs
where
printOut = defaultLogActionHPrintDoc logflags False out
printErrs = defaultLogActionHPrintDoc logflags False err
putStrSDoc = defaultLogActionHPutStrDoc logflags False out
+
+-- This function is used by `defaultLogActionWithHandles` for non-JSON output,
+-- and also by `GHC.Driver.Errors.printMessages` to produce the `rendered`
+-- message on `-fdiagnostics-as-json`.
+--
+-- We would want to eventually consolidate this. However, this is currently
+-- not feasible for the following reasons:
+--
+-- 1. Some parts of the compiler sidestep `printMessages`, for that reason we
+-- can not decorate the message in `printMessages`.
+--
+-- 2. GHC uses two different code paths for JSON and non-JSON diagnostics. For
+-- that reason we can not decorate the message in `defaultLogActionWithHandles`.
+--
+-- See also Note [JSON Error Messages]:
+--
+-- `jsonLogAction` should be removed along with -ddump-json
+--
+-- Also note that (1) is the reason why some parts of the compiler produce
+-- diagnostics that don't respect `-fdiagnostics-as-json`.
+--
+-- The plan as I see it is as follows:
+--
+-- 1. Refactor all places in the compiler that report diagnostics to go
+-- through `GHC.Driver.Errors.printMessages`.
+--
+-- (It's easy to find all those places by looking for who creates
+-- MCDiagnostic, either directly or via `mkMCDiagnostic` or
+-- `errorDiagnostic`.)
+--
+-- 2. Get rid of `-ddump-json`, `jsonLogAction` and consolidate message
+-- decoration at one place (either `printMessages` or
+-- `defaultLogActionWithHandles`)
+--
+-- This story is tracked by #24113.
+decorateDiagnostic :: LogFlags -> MessageClass -> SrcSpan -> SDoc -> IO SDoc
+decorateDiagnostic logflags msg_class srcSpan msg = addCaret
+ where
-- Pretty print the warning flag, if any (#10752)
+ message :: SDoc
message = mkLocMessageWarningGroups (log_show_warn_groups logflags) msg_class srcSpan msg
- printDiagnostics = do
+ addCaret :: IO SDoc
+ addCaret = do
caretDiagnostic <-
if log_show_caret logflags
then getCaretDiagnostic msg_class srcSpan
else pure empty
- printErrs $ getPprStyle $ \style ->
+ return $ getPprStyle $ \style ->
withPprStyle (setStyleColoured True style)
(message $+$ caretDiagnostic $+$ blankLine)
- -- careful (#2302): printErrs prints in UTF-8,
- -- whereas converting to string first and using
- -- hPutStr would just emit the low 8 bits of
- -- each unicode char.
-- | Like 'defaultLogActionHPutStrDoc' but appends an extra newline.
defaultLogActionHPrintDoc :: LogFlags -> Bool -> Handle -> SDoc -> IO ()
@@ -603,8 +641,8 @@ defaultTraceAction logflags title doc x =
logMsg :: Logger -> MessageClass -> SrcSpan -> SDoc -> IO ()
logMsg logger mc loc msg = putLogMsg logger (logFlags logger) mc loc msg
-logJsonMsg :: ToJson a => Logger -> MessageClass -> a -> IO ()
-logJsonMsg logger mc d = putJsonLogMsg logger (logFlags logger) mc (json d)
+logJsonMsg :: Logger -> MessageClass -> JsonDoc -> IO ()
+logJsonMsg logger mc = putJsonLogMsg logger (logFlags logger) mc
-- | Dump something
logDumpFile :: Logger -> PprStyle -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -147,6 +147,11 @@ Compiler
integer operations. Also, ``shuffleFloatX4#`` and ``shuffleDoubleX2#`` no longer
require ``-mavx``.
+- JSON diagnostics produced with (:ghc-flag:`-fdiagnostics-as-json`) now
+ include the `rendered` diagnostics message, in the exact same format as what
+ GHC would have produced without -fdiagnostics-as-json (including ANSI escape
+ sequences).
+
GHCi
~~~~
=====================================
docs/users_guide/diagnostics-as-json-schema-1_2.json
=====================================
@@ -0,0 +1,144 @@
+{
+ "$schema": "https://json-schema.org/draft/2020-12/schema",
+ "title": "JSON Diagnostic Schema",
+ "description": "A Schema for specifying GHC diagnostics output as JSON",
+ "type": "object",
+ "properties": {
+ "version": {
+ "description": "The current JSON schema version this object conforms to",
+ "type": "string"
+ },
+ "ghcVersion": {
+ "description": "The GHC version",
+ "type": "string"
+ },
+ "span": {
+ "oneOf": [
+ { "$ref": "#/$defs/span" },
+ { "type": "null" }
+ ]
+ },
+ "severity": {
+ "description": "The diagnostic severity",
+ "type": "string",
+ "enum": [
+ "Warning",
+ "Error"
+ ]
+ },
+ "code": {
+ "description": "The diagnostic code (if it exists)",
+ "type": [
+ "integer",
+ "null"
+ ]
+ },
+ "rendered": {
+ "description": "The rendered diagnostics message, in the exact same format as what GHC would have produced without -fdiagnostics-as-json (including ANSI escape sequences)",
+ "type": "string"
+ },
+ "message": {
+ "description": "The string output of the diagnostic message by GHC",
+ "type": "array",
+ "items": {
+ "type": "string"
+ }
+ },
+ "hints": {
+ "description": "The suggested fixes",
+ "type": "array",
+ "items": {
+ "type": "string"
+ }
+ },
+ "reason" : {
+ "description": "The GHC flag that was responsible for the emission of the diagnostic message",
+ "oneOf": [
+ {
+ "type": "object",
+ "description": "The diagnostic message was controlled by one or more GHC flags",
+ "properties": {
+ "flags": {
+ "type": "array",
+ "items": {
+ "description": "The name of a GHC flag controlling the diagnostic message",
+ "type": "string"
+ },
+ "minItems": 1
+ }
+ },
+ "required": ["flags"]
+ },
+ {
+ "type": "object",
+ "description": "The diagnostic message was controlled by a GHC diagnostic message category",
+ "properties": {
+ "category": {
+ "description": "The name of the GHC diagnostic message category controlling the diagnostic message",
+ "type": "string"
+ }
+ },
+ "required": ["category"]
+ }
+ ]
+ }
+ },
+
+ "$comment": "NOTE: \"rendered\" is not a required field so that the schema is backward compatible with version 1.1. If you bump the schema version to 2.0 the please also add \"rendered\" to the \"required\" fields.",
+ "required": [
+ "version",
+ "ghcVersion",
+ "span",
+ "severity",
+ "code",
+ "message",
+ "hints"
+ ],
+
+ "additionalProperties": false,
+ "$defs": {
+ "span": {
+ "description": "The span of the diagnostic",
+ "type": "object",
+ "properties": {
+ "file": {
+ "description": "The file in which the diagnostic occurs",
+ "type": "string"
+ },
+ "start": {
+ "description": "The start location of the diagnostic",
+ "$ref": "#/$defs/location"
+ },
+ "end": {
+ "description": "The end location of the diagnostic",
+ "$ref": "#/$defs/location"
+ }
+ },
+ "required": [
+ "file",
+ "start",
+ "end"
+ ],
+ "additionalProperties": false
+ },
+ "location": {
+ "description": "A location in a text file",
+ "type": "object",
+ "properties": {
+ "line": {
+ "description": "The line number",
+ "type": "integer"
+ },
+ "column": {
+ "description": "The column number",
+ "type": "integer"
+ }
+ },
+ "required": [
+ "line",
+ "column"
+ ],
+ "additionalProperties": false
+ }
+ }
+}
=====================================
docs/users_guide/using.rst
=====================================
@@ -1428,7 +1428,7 @@ messages and in GHCi:
a new line.
The structure of the output is described by a `JSON Schema <https://json-schema.org/>`_.
- The schema can be downloaded :download:`here <diagnostics-as-json-schema-1_1.json>`.
+ The schema can be downloaded :download:`here <diagnostics-as-json-schema-1_2.json>`.
.. ghc-flag:: -fdiagnostics-color=⟨always|auto|never⟩
:shortdesc: Use colors in error messages
=====================================
rts/Interpreter.c
=====================================
@@ -473,6 +473,72 @@ void interp_shutdown( void ){
#endif
+const StgPtr ctoi_tuple_infos[] = {
+ (StgPtr) &stg_ctoi_t0_info,
+ (StgPtr) &stg_ctoi_t1_info,
+ (StgPtr) &stg_ctoi_t2_info,
+ (StgPtr) &stg_ctoi_t3_info,
+ (StgPtr) &stg_ctoi_t4_info,
+ (StgPtr) &stg_ctoi_t5_info,
+ (StgPtr) &stg_ctoi_t6_info,
+ (StgPtr) &stg_ctoi_t7_info,
+ (StgPtr) &stg_ctoi_t8_info,
+ (StgPtr) &stg_ctoi_t9_info,
+ (StgPtr) &stg_ctoi_t10_info,
+ (StgPtr) &stg_ctoi_t11_info,
+ (StgPtr) &stg_ctoi_t12_info,
+ (StgPtr) &stg_ctoi_t13_info,
+ (StgPtr) &stg_ctoi_t14_info,
+ (StgPtr) &stg_ctoi_t15_info,
+ (StgPtr) &stg_ctoi_t16_info,
+ (StgPtr) &stg_ctoi_t17_info,
+ (StgPtr) &stg_ctoi_t18_info,
+ (StgPtr) &stg_ctoi_t19_info,
+ (StgPtr) &stg_ctoi_t20_info,
+ (StgPtr) &stg_ctoi_t21_info,
+ (StgPtr) &stg_ctoi_t22_info,
+ (StgPtr) &stg_ctoi_t23_info,
+ (StgPtr) &stg_ctoi_t24_info,
+ (StgPtr) &stg_ctoi_t25_info,
+ (StgPtr) &stg_ctoi_t26_info,
+ (StgPtr) &stg_ctoi_t27_info,
+ (StgPtr) &stg_ctoi_t28_info,
+ (StgPtr) &stg_ctoi_t29_info,
+ (StgPtr) &stg_ctoi_t30_info,
+ (StgPtr) &stg_ctoi_t31_info,
+ (StgPtr) &stg_ctoi_t32_info,
+ (StgPtr) &stg_ctoi_t33_info,
+ (StgPtr) &stg_ctoi_t34_info,
+ (StgPtr) &stg_ctoi_t35_info,
+ (StgPtr) &stg_ctoi_t36_info,
+ (StgPtr) &stg_ctoi_t37_info,
+ (StgPtr) &stg_ctoi_t38_info,
+ (StgPtr) &stg_ctoi_t39_info,
+ (StgPtr) &stg_ctoi_t40_info,
+ (StgPtr) &stg_ctoi_t41_info,
+ (StgPtr) &stg_ctoi_t42_info,
+ (StgPtr) &stg_ctoi_t43_info,
+ (StgPtr) &stg_ctoi_t44_info,
+ (StgPtr) &stg_ctoi_t45_info,
+ (StgPtr) &stg_ctoi_t46_info,
+ (StgPtr) &stg_ctoi_t47_info,
+ (StgPtr) &stg_ctoi_t48_info,
+ (StgPtr) &stg_ctoi_t49_info,
+ (StgPtr) &stg_ctoi_t50_info,
+ (StgPtr) &stg_ctoi_t51_info,
+ (StgPtr) &stg_ctoi_t52_info,
+ (StgPtr) &stg_ctoi_t53_info,
+ (StgPtr) &stg_ctoi_t54_info,
+ (StgPtr) &stg_ctoi_t55_info,
+ (StgPtr) &stg_ctoi_t56_info,
+ (StgPtr) &stg_ctoi_t57_info,
+ (StgPtr) &stg_ctoi_t58_info,
+ (StgPtr) &stg_ctoi_t59_info,
+ (StgPtr) &stg_ctoi_t60_info,
+ (StgPtr) &stg_ctoi_t61_info,
+ (StgPtr) &stg_ctoi_t62_info,
+};
+
#if defined(PROFILING)
//
@@ -1828,82 +1894,11 @@ run_BCO:
SpW(-1) = BCO_PTR(o_tuple_bco);
SpW(-2) = tuple_info;
SpW(-3) = BCO_PTR(o_bco);
- W_ ctoi_t_offset;
int tuple_stack_words = (tuple_info >> 24) & 0xff;
- switch(tuple_stack_words) {
- case 0: ctoi_t_offset = (W_)&stg_ctoi_t0_info; break;
- case 1: ctoi_t_offset = (W_)&stg_ctoi_t1_info; break;
- case 2: ctoi_t_offset = (W_)&stg_ctoi_t2_info; break;
- case 3: ctoi_t_offset = (W_)&stg_ctoi_t3_info; break;
- case 4: ctoi_t_offset = (W_)&stg_ctoi_t4_info; break;
- case 5: ctoi_t_offset = (W_)&stg_ctoi_t5_info; break;
- case 6: ctoi_t_offset = (W_)&stg_ctoi_t6_info; break;
- case 7: ctoi_t_offset = (W_)&stg_ctoi_t7_info; break;
- case 8: ctoi_t_offset = (W_)&stg_ctoi_t8_info; break;
- case 9: ctoi_t_offset = (W_)&stg_ctoi_t9_info; break;
-
- case 10: ctoi_t_offset = (W_)&stg_ctoi_t10_info; break;
- case 11: ctoi_t_offset = (W_)&stg_ctoi_t11_info; break;
- case 12: ctoi_t_offset = (W_)&stg_ctoi_t12_info; break;
- case 13: ctoi_t_offset = (W_)&stg_ctoi_t13_info; break;
- case 14: ctoi_t_offset = (W_)&stg_ctoi_t14_info; break;
- case 15: ctoi_t_offset = (W_)&stg_ctoi_t15_info; break;
- case 16: ctoi_t_offset = (W_)&stg_ctoi_t16_info; break;
- case 17: ctoi_t_offset = (W_)&stg_ctoi_t17_info; break;
- case 18: ctoi_t_offset = (W_)&stg_ctoi_t18_info; break;
- case 19: ctoi_t_offset = (W_)&stg_ctoi_t19_info; break;
-
- case 20: ctoi_t_offset = (W_)&stg_ctoi_t20_info; break;
- case 21: ctoi_t_offset = (W_)&stg_ctoi_t21_info; break;
- case 22: ctoi_t_offset = (W_)&stg_ctoi_t22_info; break;
- case 23: ctoi_t_offset = (W_)&stg_ctoi_t23_info; break;
- case 24: ctoi_t_offset = (W_)&stg_ctoi_t24_info; break;
- case 25: ctoi_t_offset = (W_)&stg_ctoi_t25_info; break;
- case 26: ctoi_t_offset = (W_)&stg_ctoi_t26_info; break;
- case 27: ctoi_t_offset = (W_)&stg_ctoi_t27_info; break;
- case 28: ctoi_t_offset = (W_)&stg_ctoi_t28_info; break;
- case 29: ctoi_t_offset = (W_)&stg_ctoi_t29_info; break;
-
- case 30: ctoi_t_offset = (W_)&stg_ctoi_t30_info; break;
- case 31: ctoi_t_offset = (W_)&stg_ctoi_t31_info; break;
- case 32: ctoi_t_offset = (W_)&stg_ctoi_t32_info; break;
- case 33: ctoi_t_offset = (W_)&stg_ctoi_t33_info; break;
- case 34: ctoi_t_offset = (W_)&stg_ctoi_t34_info; break;
- case 35: ctoi_t_offset = (W_)&stg_ctoi_t35_info; break;
- case 36: ctoi_t_offset = (W_)&stg_ctoi_t36_info; break;
- case 37: ctoi_t_offset = (W_)&stg_ctoi_t37_info; break;
- case 38: ctoi_t_offset = (W_)&stg_ctoi_t38_info; break;
- case 39: ctoi_t_offset = (W_)&stg_ctoi_t39_info; break;
-
- case 40: ctoi_t_offset = (W_)&stg_ctoi_t40_info; break;
- case 41: ctoi_t_offset = (W_)&stg_ctoi_t41_info; break;
- case 42: ctoi_t_offset = (W_)&stg_ctoi_t42_info; break;
- case 43: ctoi_t_offset = (W_)&stg_ctoi_t43_info; break;
- case 44: ctoi_t_offset = (W_)&stg_ctoi_t44_info; break;
- case 45: ctoi_t_offset = (W_)&stg_ctoi_t45_info; break;
- case 46: ctoi_t_offset = (W_)&stg_ctoi_t46_info; break;
- case 47: ctoi_t_offset = (W_)&stg_ctoi_t47_info; break;
- case 48: ctoi_t_offset = (W_)&stg_ctoi_t48_info; break;
- case 49: ctoi_t_offset = (W_)&stg_ctoi_t49_info; break;
-
- case 50: ctoi_t_offset = (W_)&stg_ctoi_t50_info; break;
- case 51: ctoi_t_offset = (W_)&stg_ctoi_t51_info; break;
- case 52: ctoi_t_offset = (W_)&stg_ctoi_t52_info; break;
- case 53: ctoi_t_offset = (W_)&stg_ctoi_t53_info; break;
- case 54: ctoi_t_offset = (W_)&stg_ctoi_t54_info; break;
- case 55: ctoi_t_offset = (W_)&stg_ctoi_t55_info; break;
- case 56: ctoi_t_offset = (W_)&stg_ctoi_t56_info; break;
- case 57: ctoi_t_offset = (W_)&stg_ctoi_t57_info; break;
- case 58: ctoi_t_offset = (W_)&stg_ctoi_t58_info; break;
- case 59: ctoi_t_offset = (W_)&stg_ctoi_t59_info; break;
-
- case 60: ctoi_t_offset = (W_)&stg_ctoi_t60_info; break;
- case 61: ctoi_t_offset = (W_)&stg_ctoi_t61_info; break;
- case 62: ctoi_t_offset = (W_)&stg_ctoi_t62_info; break;
-
- default: barf("unsupported tuple size %d", tuple_stack_words);
+ if (tuple_stack_words > 62) {
+ barf("unsupported tuple size %d", tuple_stack_words);
}
-
+ W_ ctoi_t_offset = (W_) ctoi_tuple_infos[tuple_stack_words];
SpW(-4) = ctoi_t_offset;
Sp_subW(4);
goto nextInsn;
=====================================
testsuite/tests/driver/json.stderr
=====================================
@@ -1 +1 @@
-{"version":"1.1","ghcVersion":"ghc-9.13.20250529","span":{"file":"json.hs","start":{"line":9,"column":11},"end":{"line":9,"column":21}},"severity":"Error","code":48010,"message":["Empty list of alternatives in case expression"],"hints":["Perhaps you intended to use the \u2018EmptyCase\u2019 extension"]}
+{"version":"1.2","ghcVersion":"ghc-9.13.20250627","span":{"file":"json.hs","start":{"line":9,"column":11},"end":{"line":9,"column":21}},"severity":"Error","code":48010,"rendered":"json.hs:9:11: error: [GHC-48010]\n Empty list of alternatives in case expression\n Suggested fix:\n Perhaps you intended to use the \u2018EmptyCase\u2019 extension\n","message":["Empty list of alternatives in case expression"],"hints":["Perhaps you intended to use the \u2018EmptyCase\u2019 extension"]}
=====================================
testsuite/tests/driver/json_warn.stderr
=====================================
@@ -1,2 +1,2 @@
-{"version":"1.1","ghcVersion":"ghc-9.13.20250529","span":{"file":"json_warn.hs","start":{"line":4,"column":3},"end":{"line":4,"column":4}},"severity":"Warning","code":40910,"message":["Defined but not used: \u2018x\u2019"],"hints":[],"reason":{"flags":["unused-matches"]}}
-{"version":"1.1","ghcVersion":"ghc-9.13.20250529","span":{"file":"json_warn.hs","start":{"line":7,"column":5},"end":{"line":7,"column":9}},"severity":"Warning","code":63394,"message":["In the use of \u2018head\u2019\n(imported from Prelude, but defined in GHC.Internal.List):\n\"This is a partial function, it throws an error on empty lists. Use pattern matching, 'Data.List.uncons' or 'Data.Maybe.listToMaybe' instead. Consider refactoring to use \"Data.List.NonEmpty\".\""],"hints":[],"reason":{"category":"x-partial"}}
+{"version":"1.2","ghcVersion":"ghc-9.13.20250627","span":{"file":"json_warn.hs","start":{"line":4,"column":3},"end":{"line":4,"column":4}},"severity":"Warning","code":40910,"rendered":"json_warn.hs:4:3: warning: [GHC-40910] [-Wunused-matches (in -Wextra)]\n Defined but not used: \u2018x\u2019\n","message":["Defined but not used: \u2018x\u2019"],"hints":[],"reason":{"flags":["unused-matches"]}}
+{"version":"1.2","ghcVersion":"ghc-9.13.20250627","span":{"file":"json_warn.hs","start":{"line":7,"column":5},"end":{"line":7,"column":9}},"severity":"Warning","code":63394,"rendered":"json_warn.hs:7:5: warning: [GHC-63394] [-Wx-partial (in -Wextended-warnings)]\n In the use of \u2018head\u2019\n (imported from Prelude, but defined in GHC.Internal.List):\n \"This is a partial function, it throws an error on empty lists. Use pattern matching, 'Data.List.uncons' or 'Data.Maybe.listToMaybe' instead. Consider refactoring to use \"Data.List.NonEmpty\".\"\n","message":["In the use of \u2018head\u2019\n(imported from Prelude, but defined in GHC.Internal.List):\n\"This is a partial function, it throws an error on empty lists. Use pattern matching, 'Data.List.uncons' or 'Data.Maybe.listToMaybe' instead. Consider refactoring to use \"Data.List.NonEmpty\".\""],"hints":[],"reason":{"category":"x-partial"}}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0c5588c5c99f99660375d40fb22443…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0c5588c5c99f99660375d40fb22443…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/9.10.3-backports] 27 commits: testsuite: add T26120 marked as broken
by Zubin (@wz1000) 24 Jul '25
by Zubin (@wz1000) 24 Jul '25
24 Jul '25
Zubin pushed to branch wip/9.10.3-backports at Glasgow Haskell Compiler / GHC
Commits:
05545de7 by Cheng Shao at 2025-07-24T07:39:03+05:30
testsuite: add T26120 marked as broken
(cherry picked from commit 44b8cee2d5c114b238898ce4ee7b44ecaa0bf491)
- - - - -
7fb42ed3 by Cheng Shao at 2025-07-24T07:39:03+05:30
compiler: fix GHC.SysTools.Ar archive member size writing logic
This patch fixes a long-standing bug in `GHC.SysTools.Ar` that emits
the wrong archive member size in each archive header. It should encode
the exact length of the member payload, excluding any padding byte,
otherwise malformed archive that extracts a broken object with an
extra trailing byte could be created.
Apart from the in-tree `T26120` test, I've also created an out-of-tree
testsuite at https://github.com/TerrorJack/ghc-ar-quickcheck that
contains QuickCheck roundtrip tests for `GHC.SysTools.Ar`. With this
fix, simple roundtrip tests and `writeGNUAr`/GNU `ar` roundtrip test
passes. There might be more bugs lurking in here, but this patch is
still a critical bugfix already.
Fixes #26120 #22586.
Co-authored-by: Codex <codex(a)openai.com>
(cherry picked from commit 894a04f3a82dd39ecef71619e2032c4dfead556e)
- - - - -
41db0a0b by Vladislav Zavialov at 2025-07-24T07:39:03+05:30
Error message with EmptyCase and RequiredTypeArguments (#25004)
Fix a panic triggered by a combination of \case{} and forall t ->
ghci> let f :: forall (xs :: Type) -> (); f = \case {}
panic! (the 'impossible' happened)
GHC version 9.10.1:
Util: only
The new error message looks like this:
ghci> let f :: forall (xs :: Type) -> (); f = \case {}
<interactive>:5:41: error: [GHC-48010]
• Empty list of alternatives in \case expression
checked against a forall-type: forall xs -> ...
This is achieved as follows:
* A new data type, BadEmptyCaseReason, is now used to describe
why an empty case has been rejected. Used in TcRnEmptyCase.
* HsMatchContextRn is passed to tcMatches, so that the type checker
can attach the syntactic context to the error message.
* tcMatches now rejects type arguments if the list of alternatives is
empty. This is what fixes the bug.
(cherry picked from commit cce869ea2439bb16c284ce7ed71a173d54a8c9ad)
- - - - -
7f9c7f22 by Vladislav Zavialov at 2025-07-24T07:39:03+05:30
Fix EmptyCase panic in tcMatches (#25960)
Due to faulty reasoning in Note [Pattern types for EmptyCase],
tcMatches was too keen to panic.
* Old (incorrect) assumption: pat_tys is a singleton list.
This does not hold when \case{} is checked against a function type
preceded by invisible forall. See the new T25960 test case.
* New (hopefully correct) assumption: vis_pat_tys is a singleton list.
This should follow from:
checkArgCounts :: MatchGroup GhcRn ... -> TcM VisArity
checkArgCounts (MG { mg_alts = L _ [] })
= return 1
...
(cherry picked from commit b34890c7d4803041caff060391eec298e2b0a098)
- - - - -
418bb568 by Vladislav Zavialov at 2025-07-24T07:39:03+05:30
Take subordinate 'type' specifiers into account
This patch fixes multiple bugs (#22581, #25983, #25984, #25991)
in name resolution of subordinate import lists.
Bug #22581
----------
In subordinate import lists, the use of the `type` namespace specifier
used to be ignored. For example, this import statement was incorrectly
accepted:
import Prelude (Bool(type True))
Now it results in an error message:
<interactive>:2:17: error: [GHC-51433]
In the import of ‘Prelude’:
a data type called ‘Bool’ is exported,
but its subordinate item ‘True’ is not in the type namespace.
Bug #25983
----------
In subordinate import lists within a `hiding` clause, non-existent
items led to a poor warning message with -Wdodgy-imports. Consider:
import Prelude hiding (Bool(X))
The warning message for this import statement used to misreport the
cause of the problem:
<interactive>:3:24: warning: [GHC-56449] [-Wdodgy-imports]
In the import of ‘Prelude’:
an item called ‘Bool’ is exported, but it is a type.
Now the warning message is correct:
<interactive>:2:24: warning: [GHC-10237] [-Wdodgy-imports]
In the import of ‘Prelude’:
a data type called ‘Bool’ is exported, but it does not export
any constructors or record fields called ‘X’.
Bug #25984
----------
In subordinate import lists within a `hiding` clause, non-existent
items resulted in the entire import declaration being discarded.
For example, this program was incorrectly accepted:
import Prelude hiding (Bool(True,X))
t = True
Now it results in an error message:
<interactive>:2:5: error: [GHC-88464]
Data constructor not in scope: True
Bug #25991
----------
In subordinate import lists, it was not possible to refer to a class
method if there was an associated type of the same name:
module M_helper where
class C a b where
type a # b
(#) :: a -> b -> ()
module M where
import M_helper (C((#)))
This import declaration failed with:
M.hs:2:28: error: [GHC-10237]
In the import of ‘M_helper’:
an item called ‘C’ is exported, but it does not export any children
(constructors, class methods or field names) called ‘#’.
Now it is accepted.
Summary
-------
The changes required to fix these bugs are almost entirely confined to
GHC.Rename.Names. Other than that, there is a new error constructor
BadImportNonTypeSubordinates with error code [GHC-51433].
Test cases:
T22581a T22581b T22581c T22581d
T25983a T25983b T25983c T25983d T25983e T25983f T25983g
T25984a T25984b
T25991a T25991b1 T25991b2
(cherry picked from commit 282df90570fa9c777c914ae543fea291f7158482)
- - - - -
89d6c4ff by Zubin Duggal at 2025-07-24T07:39:03+05:30
fetch_gitlab: Ensure we copy users_guide.pdf and Haddock.pdf to the release docs directory
Fixes #24093
(cherry picked from commit 48cf32dbd2cf52e1db7ee68bc79a5511ff52a2a6)
- - - - -
cf1f18c3 by Ben Gamari at 2025-07-24T07:39:03+05:30
configure: Drop probing of ld.gold
As noted in #25716, `gold` has been dropped from binutils-2.44.
Fixes #25716.
Metric Increase:
size_hello_artifact_gzip
size_hello_unicode_gzip
ghc_prim_so
(cherry picked from commit c635f164cb62bcb3f34166adc24e5a9437415311)
- - - - -
a4123c53 by Ben Gamari at 2025-07-24T07:39:03+05:30
testsuite/recomp015: Ignore stderr
This is necessary since ld.bfd complains
that we don't have a .note.GNU-stack section,
potentially resulting in an executable stack.
(cherry picked from commit 637bb53825b9414f7c7dbed4cc3e5cc1ed4d2329)
- - - - -
e6b14504 by Andreas Klebinger at 2025-07-24T07:39:03+05:30
Add since tag and more docs for do-clever-arg-eta-expansion
Fixes #26113
(cherry picked from commit 699deef58bf89ef2f111b35f72d303a3624d219d)
- - - - -
0a8dcfb9 by Zubin Duggal at 2025-07-24T07:39:03+05:30
release: copy index.html from correct directory
(cherry picked from commit cbfd0829cd61928976c9eb17ba4af18272466063)
(cherry picked from commit ea3f7fd5f702d41077fff0a749b9c443d54e4844)
- - - - -
1f698c03 by Tamar Christina at 2025-07-24T07:39:03+05:30
rts: Handle API set symbol versioning conflicts
(cherry picked from commit 63373b95331f07c16e3eef511379fe3bed484839)
- - - - -
e5e2f396 by Tamar Christina at 2025-07-24T07:39:03+05:30
rts: Implement WEAK EXTERNAL undef redirection by target symbol name
(cherry picked from commit e3bfc62416dd738bfd1a4464f0a622c9d0b7c393)
- - - - -
deb3c132 by Zubin Duggal at 2025-07-24T07:39:03+05:30
bump deepseq to 1.5.2.0
- - - - -
c6832839 by Zubin Duggal at 2025-07-24T07:39:03+05:30
bump os-string to 2.0.7
- - - - -
2dd1198f by Zubin Duggal at 2025-07-24T07:39:03+05:30
bump process to 1.6.26.1
- - - - -
21752924 by Zubin Duggal at 2025-07-24T07:39:03+05:30
bump unix to 2.8.7.0
- - - - -
55fcc2b0 by Jens Petersen at 2025-07-24T07:39:03+05:30
9.10 hadrian can build with Cabal-3.12.1
fixes #25605
(cherry picked from commit 07f17b6ed1bb0ba7134ee8dfd992036e97552c94)
- - - - -
b13d35de by sheaf at 2025-07-24T07:39:03+05:30
Don't cache solved [W] HasCallStack constraints
This commit ensures we do not add solved Wanted constraints that mention
HasCallStack or HasExceptionContext constraints to the set of solved
Wanted dictionary constraints: caching them is invalid, because re-using
such cached dictionaries means using an old call-stack instead of
constructing a new one, as was reported in #25529.
Fixes #25529.
(cherry picked from commit 256ac29c8df4f17a1d50ea243408d506ebf395d6)
- - - - -
83dd65ac by Zubin Duggal at 2025-07-24T07:39:03+05:30
In commit "Don't cache solved [W] HasCallStack constraints" (256ac29c8df4f17a1d50ea243408d506ebf395d6),
we attempt to use `tryM` to avoid errors when looking up certain known-key names like CallStack while
compiling ghc-prim and ghc-internal.
Unfortunately, `tryM` doesn't catch module lookup errors. This manifests as a failure to build ghc-prim
in `--make` mode on the GHC 9.10 branch.
Instead, we explicitly avoid doing lookups when we are compiling ghc-prim or ghc-internal instead of
relying on catching the exception.
- - - - -
d87d99b0 by Zubin Duggal at 2025-07-24T07:51:30+05:30
Consider `PromotedDataCon` in `tyConStupidTheta`
Haddock checks data declarations for the stupid theta so as not to
pretty-print them as empty contexts. Type data declarations end up as
`PromotedDataCon`s by the time Haddock performs this check, causing a
panic. This commit extends `tyConStupidTheta` so that it returns an
empty list for `PromotedDataCon`s. This decision was guided by the fact
that type data declarations never have data type contexts (see (R1) in
Note [Type data declarations]).
Fixes #25739.
(cherry picked from commit 8d33d048dbe159a045a4c304fa92318365a3dfe2)
- - - - -
69eacf31 by Ryan Hendrickson at 2025-07-24T07:51:30+05:30
haddock: Preserve indentation in multiline examples
Intended for use with :{ :}, but doesn't look for those characters. Any
consecutive lines with birdtracks will only have initial whitespace
stripped up to the column of the first line.
(cherry picked from commit 2c73250494fd9f48ebda6d6fe72f0cd03182aff1)
- - - - -
4defb0de by Ryan Hendrickson at 2025-07-24T07:51:30+05:30
haddock: Parse math even after ordinary characters
Fixes a bug where math sections were not recognized if preceded by a
character that isn't special (like space or a markup character).
(cherry picked from commit b790d647c1ccdcc9aa8f166c3e0e42d0a5c29625)
- - - - -
c6abe994 by Ryan Hendrickson at 2025-07-24T07:51:30+05:30
haddock: Fix links to type operators
(cherry picked from commit a0adc30d892f14f543f39d5c45faccacbc28afb4)
- - - - -
fa6e4d7d by Ryan Hendrickson at 2025-07-24T07:51:30+05:30
haddock: Document instances from other packages
When attaching instances to `Interface`s, it isn't enough just to look
for instances in the list of `Interface`s being processed. We also need
to look in the modules on which they depend, including those outside of
this package.
Fixes #25147.
Fixes #26079.
(cherry picked from commit a26243fde4680271712a3d774e17f6cd6da4a652)
- - - - -
c4cea7f3 by Zubin Duggal at 2025-07-24T07:51:30+05:30
haddock: Don't warn about missing link destinations for derived names.
Fixes #26114
(cherry picked from commit 5dabc718a04bfc4d277c5ff7f815ee3d6b9670cb)
- - - - -
64334e30 by Zubin Duggal at 2025-07-24T07:51:30+05:30
Bump haddock version to 2.31.3
- - - - -
0450ef3c by Zubin Duggal at 2025-07-24T07:51:57+05:30
Prepare 9.10.3 prerelease
- - - - -
99 changed files:
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/SysTools/Ar.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Types.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Utils/Outputable.hs
- configure.ac
- + docs/users_guide/9.10.3-notes.rst
- docs/users_guide/exts/explicit_namespaces.rst
- docs/users_guide/using-optimisation.rst
- hadrian/hadrian.cabal
- hadrian/src/Context.hs
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Hadrian/Haskell/Cabal/Type.hs
- hadrian/src/Rules/BinaryDist.hs
- hadrian/src/Rules/CabalReinstall.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Rules/Rts.hs
- hadrian/src/Settings/Builders/Ghc.hs
- libraries/deepseq
- libraries/os-string
- libraries/process
- libraries/unix
- m4/find_ld.m4
- rts/linker/PEi386.c
- testsuite/driver/testlib.py
- testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout
- testsuite/tests/driver/T20604/T20604.stdout
- testsuite/tests/driver/recomp015/all.T
- + testsuite/tests/ghc-api/T26120.hs
- + testsuite/tests/ghc-api/T26120.stdout
- testsuite/tests/ghc-api/all.T
- testsuite/tests/ghci/scripts/ghci064.stdout
- testsuite/tests/module/T21826.stderr
- testsuite/tests/module/mod81.stderr
- testsuite/tests/module/mod91.stderr
- testsuite/tests/plugins/plugins10.stdout
- testsuite/tests/plugins/static-plugins.stdout
- + testsuite/tests/rename/should_compile/T22581c.hs
- + testsuite/tests/rename/should_compile/T22581c_helper.hs
- + testsuite/tests/rename/should_compile/T22581d.script
- + testsuite/tests/rename/should_compile/T22581d.stdout
- + testsuite/tests/rename/should_compile/T25983a.hs
- + testsuite/tests/rename/should_compile/T25983a.stderr
- + testsuite/tests/rename/should_compile/T25983b.hs
- + testsuite/tests/rename/should_compile/T25983b.stderr
- + testsuite/tests/rename/should_compile/T25983c.hs
- + testsuite/tests/rename/should_compile/T25983c.stderr
- + testsuite/tests/rename/should_compile/T25983d.hs
- + testsuite/tests/rename/should_compile/T25983d.stderr
- + testsuite/tests/rename/should_compile/T25983e.hs
- + testsuite/tests/rename/should_compile/T25983e.stderr
- + testsuite/tests/rename/should_compile/T25983f.hs
- + testsuite/tests/rename/should_compile/T25983f.stderr
- + testsuite/tests/rename/should_compile/T25983g.hs
- + testsuite/tests/rename/should_compile/T25983g.stderr
- + testsuite/tests/rename/should_compile/T25984a.hs
- + testsuite/tests/rename/should_compile/T25984a.stderr
- + testsuite/tests/rename/should_compile/T25984a_helper.hs
- + testsuite/tests/rename/should_compile/T25991a.hs
- + testsuite/tests/rename/should_compile/T25991a_helper.hs
- testsuite/tests/rename/should_compile/all.T
- + testsuite/tests/rename/should_fail/T22581a.hs
- + testsuite/tests/rename/should_fail/T22581a.stderr
- + testsuite/tests/rename/should_fail/T22581a_helper.hs
- + testsuite/tests/rename/should_fail/T22581b.hs
- + testsuite/tests/rename/should_fail/T22581b.stderr
- + testsuite/tests/rename/should_fail/T22581b_helper.hs
- + testsuite/tests/rename/should_fail/T25984b.hs
- + testsuite/tests/rename/should_fail/T25984b.stderr
- + testsuite/tests/rename/should_fail/T25991b1.hs
- + testsuite/tests/rename/should_fail/T25991b1.stderr
- + testsuite/tests/rename/should_fail/T25991b2.hs
- + testsuite/tests/rename/should_fail/T25991b2.stderr
- + testsuite/tests/rename/should_fail/T25991b_helper.hs
- testsuite/tests/rename/should_fail/T9006.stderr
- testsuite/tests/rename/should_fail/all.T
- + testsuite/tests/typecheck/should_compile/T25960.hs
- testsuite/tests/typecheck/should_compile/all.T
- + testsuite/tests/typecheck/should_fail/T25004.hs
- + testsuite/tests/typecheck/should_fail/T25004.stderr
- + testsuite/tests/typecheck/should_fail/T25004k.hs
- + testsuite/tests/typecheck/should_fail/T25004k.stderr
- testsuite/tests/typecheck/should_fail/all.T
- + testsuite/tests/typecheck/should_run/T25529.hs
- + testsuite/tests/typecheck/should_run/T25529.stdout
- testsuite/tests/typecheck/should_run/all.T
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/haddock
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/39ddc1cc1d72f58b6cc0d92497dee5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/39ddc1cc1d72f58b6cc0d92497dee5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/9.10.3-backports] 9 commits: In commit "Don't cache solved [W] HasCallStack constraints"...
by Zubin (@wz1000) 24 Jul '25
by Zubin (@wz1000) 24 Jul '25
24 Jul '25
Zubin pushed to branch wip/9.10.3-backports at Glasgow Haskell Compiler / GHC
Commits:
2b947fe9 by Zubin Duggal at 2025-07-24T07:23:48+05:30
In commit "Don't cache solved [W] HasCallStack constraints" (256ac29c8df4f17a1d50ea243408d506ebf395d6),
we attempt to use `tryM` to avoid errors when looking up certain known-key names like CallStack while
compiling ghc-prim and ghc-internal.
Unfortunately, `tryM` doesn't catch module lookup errors. This manifests as a failure to build ghc-prim
in `--make` mode on the GHC 9.10 branch.
Instead, we explicitly avoid doing lookups when we are compiling ghc-prim or ghc-internal instead of
relying on catching the exception.
- - - - -
2fe8af25 by Zubin Duggal at 2025-07-24T07:23:48+05:30
Prepare 9.10.3 prerelease
- - - - -
a5ca2b8d by Zubin Duggal at 2025-07-24T07:23:48+05:30
Consider `PromotedDataCon` in `tyConStupidTheta`
Haddock checks data declarations for the stupid theta so as not to
pretty-print them as empty contexts. Type data declarations end up as
`PromotedDataCon`s by the time Haddock performs this check, causing a
panic. This commit extends `tyConStupidTheta` so that it returns an
empty list for `PromotedDataCon`s. This decision was guided by the fact
that type data declarations never have data type contexts (see (R1) in
Note [Type data declarations]).
Fixes #25739.
(cherry picked from commit 8d33d048dbe159a045a4c304fa92318365a3dfe2)
- - - - -
00066a2f by Ryan Hendrickson at 2025-07-24T07:23:48+05:30
haddock: Preserve indentation in multiline examples
Intended for use with :{ :}, but doesn't look for those characters. Any
consecutive lines with birdtracks will only have initial whitespace
stripped up to the column of the first line.
(cherry picked from commit 2c73250494fd9f48ebda6d6fe72f0cd03182aff1)
- - - - -
cf374ab9 by Ryan Hendrickson at 2025-07-24T07:23:48+05:30
haddock: Parse math even after ordinary characters
Fixes a bug where math sections were not recognized if preceded by a
character that isn't special (like space or a markup character).
(cherry picked from commit b790d647c1ccdcc9aa8f166c3e0e42d0a5c29625)
- - - - -
aa0d533a by Ryan Hendrickson at 2025-07-24T07:23:48+05:30
haddock: Fix links to type operators
(cherry picked from commit a0adc30d892f14f543f39d5c45faccacbc28afb4)
- - - - -
7ca8a0fa by Ryan Hendrickson at 2025-07-24T07:23:48+05:30
haddock: Document instances from other packages
When attaching instances to `Interface`s, it isn't enough just to look
for instances in the list of `Interface`s being processed. We also need
to look in the modules on which they depend, including those outside of
this package.
Fixes #25147.
Fixes #26079.
(cherry picked from commit a26243fde4680271712a3d774e17f6cd6da4a652)
- - - - -
13b5e6f7 by Zubin Duggal at 2025-07-24T07:23:48+05:30
haddock: Don't warn about missing link destinations for derived names.
Fixes #26114
(cherry picked from commit 5dabc718a04bfc4d277c5ff7f815ee3d6b9670cb)
- - - - -
39ddc1cc by Zubin Duggal at 2025-07-24T07:23:48+05:30
Bump haddock version to 2.31.3
- - - - -
5 changed files:
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Tc/Solver/Monad.hs
- configure.ac
- + docs/users_guide/9.10.3-notes.rst
- utils/haddock
Changes:
=====================================
compiler/GHC/Core/TyCon.hs
=====================================
@@ -2659,6 +2659,7 @@ tyConStupidTheta :: TyCon -> [PredType]
tyConStupidTheta tc@(TyCon { tyConDetails = details })
| AlgTyCon {algTcStupidTheta = stupid} <- details = stupid
| PrimTyCon {} <- details = []
+ | PromotedDataCon {} <- details = []
| otherwise = pprPanic "tyConStupidTheta" (ppr tc)
-- | Extract the 'TyVar's bound by a vanilla type synonym
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -178,7 +178,7 @@ import GHC.Types.Var.Set
import GHC.Types.Unique.Supply
import GHC.Types.Unique.Set( elementOfUniqSet )
-import GHC.Unit.Module ( HasModule, getModule, extractModule )
+import GHC.Unit.Module ( HasModule, getModule, extractModule, primUnit, moduleUnit, ghcInternalUnit, bignumUnit)
import qualified GHC.Rename.Env as TcM
import GHC.Utils.Outputable
@@ -508,7 +508,11 @@ updSolvedDicts what dict_ct@(DictCt { di_cls = cls, di_tys = tys, di_ev = ev })
-- See Note [Using isCallStackTy in mentionsIP].
is_tyConTy :: (Type -> Bool) -> Name -> TcS (Type -> Bool)
is_tyConTy is_eq tc_name
- = do { (mb_tc, _) <- wrapTcS $ TcM.tryTc $ TcM.tcLookupTyCon tc_name
+ = do { mb_tc <- wrapTcS $ do
+ mod <- tcg_mod <$> TcM.getGblEnv
+ if moduleUnit mod `elem` [primUnit, ghcInternalUnit, bignumUnit]
+ then return Nothing
+ else Just <$> TcM.tcLookupTyCon tc_name
; case mb_tc of
Just tc ->
return $ \ ty -> not (typesAreApart ty (mkTyConTy tc))
=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.10.2], [glasgow-ha
AC_CONFIG_MACRO_DIRS([m4])
# Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
# The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
# above. If this is not a released version, then we will append the
=====================================
docs/users_guide/9.10.3-notes.rst
=====================================
@@ -0,0 +1,165 @@
+.. _release-9-10-3:
+
+Version 9.10.3
+===============
+The significant changes to the various parts of the compiler are listed in the
+following sections. See the `migration guide
+<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.10>`_ on the GHC Wiki
+for specific guidance on migrating programs to this release.
+
+
+Compiler
+~~~~~~~~
+
+- Don't cache solved [W] HasCallStack constraints to avoid re-using old
+ call-stacks instead of constructing new ones. (:ghc-ticket:`25529`)
+
+- Fix EmptyCase panic in tcMatches when \case{} is checked against a function
+ type preceded by invisible forall. (:ghc-ticket:`25960`)
+
+- Fix panic triggered by combination of \case{} and forall t ->. (:ghc-ticket:`25004`)
+
+- Fix GHC.SysTools.Ar archive member size writing logic that was emitting wrong
+ archive member sizes in headers. (:ghc-ticket:`26120`, :ghc-ticket:`22586`)
+
+- Fix multiple bugs in name resolution of subordinate import lists related to
+ type namespace specifiers and hiding clauses. (:ghc-ticket:`22581`, :ghc-ticket:`25983`, :ghc-ticket:`25984`, :ghc-ticket:`25991`)
+
+- Use mkTrAppChecked in ds_ev_typeable to avoid false negatives for type
+ equality involving function types. (:ghc-ticket:`25998`)
+
+- Fix bytecode generation for ``tagToEnum# <LITERAL>``. (:ghc-ticket:`25975`)
+
+- Don't report used duplicate record fields as unused. (:ghc-ticket:`24035`)
+
+- Propagate long distance info to guarded let binds for better pattern-match
+ checking warnings. (:ghc-ticket:`25749`)
+
+- Prevent incorrect unpacking optimizations for GADTs with multiple constructors. (:ghc-ticket:`25672`)
+
+- Introduce a separate argument limit for forced specs via SPEC argument with
+ warning when limit is exceeded. (:ghc-ticket:`25197`)
+
+Build system and packaging
+~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+- 9.10 hadrian can build with Cabal-3.12.1. (:ghc-ticket:`25605`)
+
+- GHC settings: always unescape escaped spaces to fix handling of spaces in
+ executable paths. (:ghc-ticket:`25204`)
+
+Native code generator backend
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+- x86 NCG: Fix code generation of bswap64 on i386. (:ghc-ticket:`25601`)
+
+- AArch64 NCG: Fix sub-word arithmetic right shift by zero-extending sub-word
+ values. (:ghc-ticket:`26061`)
+
+- NCG: AArch64 - Add -finter-module-far-jumps flag for modules with far jumps
+ outside the current module. (:ghc-ticket:`24648`)
+
+LLVM backend
+~~~~~~~~~~~~
+
+- LLVM: fix typo in padLiveArgs that was incorrectly computing too many padding
+ registers causing segfaults. (:ghc-ticket:`25770`, :ghc-ticket:`25773`)
+
+- llvmGen: Fix linkage of built-in arrays to use Appending linkage instead of
+ Internal. (:ghc-ticket:`25769`)
+
+- llvmGen: Fix built-in variable predicate to check for `@llvm` rather than
+ `$llvm`.
+
+WebAssembly backend
+~~~~~~~~~~~~~~~~~~~
+
+- wasm: use primitive opcodes for fabs and sqrt operations.
+
+Runtime system
+~~~~~~~~~~~~~~
+
+- rts: Implement WEAK EXTERNAL undef redirection by target symbol name.
+
+- rts: Handle API set symbol versioning conflicts.
+
+- rts: fix rts_clearMemory logic when sanity checks are enabled. (:ghc-ticket:`26011`)
+
+- rts/linker: Improve efficiency of proddable blocks structure by using binary
+ search instead of linked lists for better performance with split sections. (:ghc-ticket:`26009`)
+
+- rts/linker/PEi386: Don't repeatedly load DLLs by maintaining a hash-set of
+ loaded DLL names. (:ghc-ticket:`26009`, :ghc-ticket:`26052`)
+
+- rts/linker: Don't fail due to RTLD_NOW by attempting eager binding first,
+ then reverting to lazy binding on failure. (:ghc-ticket:`25943`)
+
+``base`` library
+~~~~~~~~~~~~~~~~
+
+- base: Expose Backtraces constructor and fields. (:ghc-ticket:`26049`)
+
+- base: Note strictness changes made in 4.16.0.0. (:ghc-ticket:`25886`)
+
+- Fix bugs in ``integerRecipMod`` and ``integerPowMod`` return values. (:ghc-ticket:`26017`)
+
+``ghc`` library
+~~~~~~~~~~~~~~~
+
+- perf: Replace uses of genericLength with strictGenericLength to reduce time
+ spent in 'assembleBCOs' and allocations. (:ghc-ticket:`25706`)
+
+Build tools
+~~~~~~~~~~~
+
+- configure: Drop probing of ld.gold since `gold` has been dropped from
+ binutils-2.44. (:ghc-ticket:`25716`)
+
+- get-win32-tarballs.py: List tarball files to be downloaded if we cannot find
+ them. (:ghc-ticket:`25929`)
+
+- hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc.
+
+Included libraries
+~~~~~~~~~~~~~~~~~~
+
+The package database provided with this distribution also contains a number of
+packages other than GHC itself. See the changelogs provided with these packages
+for further change information.
+
+.. ghc-package-list::
+
+ libraries/array/array.cabal: Dependency of ``ghc`` library
+ libraries/base/base.cabal: Core library
+ libraries/binary/binary.cabal: Dependency of ``ghc`` library
+ libraries/bytestring/bytestring.cabal: Dependency of ``ghc`` library
+ libraries/Cabal/Cabal/Cabal.cabal: Dependency of ``ghc-pkg`` utility
+ libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal: Dependency of ``ghc-pkg`` utility
+ libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
+ libraries/deepseq/deepseq.cabal: Dependency of ``ghc`` library
+ libraries/directory/directory.cabal: Dependency of ``ghc`` library
+ libraries/exceptions/exceptions.cabal: Dependency of ``ghc`` and ``haskeline`` library
+ libraries/filepath/filepath.cabal: Dependency of ``ghc`` library
+ compiler/ghc.cabal: The compiler itself
+ libraries/ghci/ghci.cabal: The REPL interface
+ libraries/ghc-boot/ghc-boot.cabal: Internal compiler library
+ libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
+ libraries/ghc-compact/ghc-compact.cabal: Core library
+ libraries/ghc-heap/ghc-heap.cabal: GHC heap-walking library
+ libraries/ghc-prim/ghc-prim.cabal: Core library
+ libraries/haskeline/haskeline.cabal: Dependency of ``ghci`` executable
+ libraries/hpc/hpc.cabal: Dependency of ``hpc`` executable
+ libraries/integer-gmp/integer-gmp.cabal: Core library
+ libraries/mtl/mtl.cabal: Dependency of ``Cabal`` library
+ libraries/parsec/parsec.cabal: Dependency of ``Cabal`` library
+ libraries/pretty/pretty.cabal: Dependency of ``ghc`` library
+ libraries/process/process.cabal: Dependency of ``ghc`` library
+ libraries/stm/stm.cabal: Dependency of ``haskeline`` library
+ libraries/template-haskell/template-haskell.cabal: Core library
+ libraries/terminfo/terminfo.cabal: Dependency of ``haskeline`` library
+ libraries/text/text.cabal: Dependency of ``Cabal`` library
+ libraries/time/time.cabal: Dependency of ``ghc`` library
+ libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
+ libraries/unix/unix.cabal: Dependency of ``ghc`` library
+ libraries/Win32/Win32.cabal: Dependency of ``ghc`` library
+ libraries/xhtml/xhtml.cabal: Dependency of ``haddock`` executable
\ No newline at end of file
=====================================
utils/haddock
=====================================
@@ -1 +1 @@
-Subproject commit f6116257ff838bb0b9def2c49d2f629756527ad2
+Subproject commit 050fe4bbb455fb6b79e02afc7567f3a246fea5ea
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/00352d68f3708340ba267c26bb4aef…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/00352d68f3708340ba267c26bb4aef…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/9.10.3-backports] 7 commits: Consider `PromotedDataCon` in `tyConStupidTheta`
by Zubin (@wz1000) 24 Jul '25
by Zubin (@wz1000) 24 Jul '25
24 Jul '25
Zubin pushed to branch wip/9.10.3-backports at Glasgow Haskell Compiler / GHC
Commits:
9a111592 by Zubin Duggal at 2025-07-24T06:39:35+05:30
Consider `PromotedDataCon` in `tyConStupidTheta`
Haddock checks data declarations for the stupid theta so as not to
pretty-print them as empty contexts. Type data declarations end up as
`PromotedDataCon`s by the time Haddock performs this check, causing a
panic. This commit extends `tyConStupidTheta` so that it returns an
empty list for `PromotedDataCon`s. This decision was guided by the fact
that type data declarations never have data type contexts (see (R1) in
Note [Type data declarations]).
Fixes #25739.
(cherry picked from commit 8d33d048dbe159a045a4c304fa92318365a3dfe2)
- - - - -
277c7048 by Ryan Hendrickson at 2025-07-24T06:46:24+05:30
haddock: Preserve indentation in multiline examples
Intended for use with :{ :}, but doesn't look for those characters. Any
consecutive lines with birdtracks will only have initial whitespace
stripped up to the column of the first line.
(cherry picked from commit 2c73250494fd9f48ebda6d6fe72f0cd03182aff1)
- - - - -
11726850 by Ryan Hendrickson at 2025-07-24T06:49:54+05:30
haddock: Parse math even after ordinary characters
Fixes a bug where math sections were not recognized if preceded by a
character that isn't special (like space or a markup character).
(cherry picked from commit b790d647c1ccdcc9aa8f166c3e0e42d0a5c29625)
- - - - -
529c45a4 by Ryan Hendrickson at 2025-07-24T06:52:35+05:30
haddock: Fix links to type operators
(cherry picked from commit a0adc30d892f14f543f39d5c45faccacbc28afb4)
- - - - -
cede8da7 by Ryan Hendrickson at 2025-07-24T07:01:06+05:30
haddock: Document instances from other packages
When attaching instances to `Interface`s, it isn't enough just to look
for instances in the list of `Interface`s being processed. We also need
to look in the modules on which they depend, including those outside of
this package.
Fixes #25147.
Fixes #26079.
(cherry picked from commit a26243fde4680271712a3d774e17f6cd6da4a652)
- - - - -
56b572dd by Zubin Duggal at 2025-07-24T07:03:03+05:30
haddock: Don't warn about missing link destinations for derived names.
Fixes #26114
(cherry picked from commit 5dabc718a04bfc4d277c5ff7f815ee3d6b9670cb)
- - - - -
00352d68 by Zubin Duggal at 2025-07-24T07:12:55+05:30
Bump haddock version to 2.31.3
- - - - -
2 changed files:
- compiler/GHC/Core/TyCon.hs
- utils/haddock
Changes:
=====================================
compiler/GHC/Core/TyCon.hs
=====================================
@@ -2659,6 +2659,7 @@ tyConStupidTheta :: TyCon -> [PredType]
tyConStupidTheta tc@(TyCon { tyConDetails = details })
| AlgTyCon {algTcStupidTheta = stupid} <- details = stupid
| PrimTyCon {} <- details = []
+ | PromotedDataCon {} <- details = []
| otherwise = pprPanic "tyConStupidTheta" (ppr tc)
-- | Extract the 'TyVar's bound by a vanilla type synonym
=====================================
utils/haddock
=====================================
@@ -1 +1 @@
-Subproject commit f6116257ff838bb0b9def2c49d2f629756527ad2
+Subproject commit 050fe4bbb455fb6b79e02afc7567f3a246fea5ea
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ad925e3bba94d7f7a2e71c11a97a41…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ad925e3bba94d7f7a2e71c11a97a41…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/9.10.3-backports] 4 commits: 9.10 hadrian can build with Cabal-3.12.1
by Zubin (@wz1000) 24 Jul '25
by Zubin (@wz1000) 24 Jul '25
24 Jul '25
Zubin pushed to branch wip/9.10.3-backports at Glasgow Haskell Compiler / GHC
Commits:
c009fa15 by Jens Petersen at 2025-07-24T06:03:25+05:30
9.10 hadrian can build with Cabal-3.12.1
fixes #25605
(cherry picked from commit 07f17b6ed1bb0ba7134ee8dfd992036e97552c94)
- - - - -
8a3b2e2a by sheaf at 2025-07-24T06:03:25+05:30
Don't cache solved [W] HasCallStack constraints
This commit ensures we do not add solved Wanted constraints that mention
HasCallStack or HasExceptionContext constraints to the set of solved
Wanted dictionary constraints: caching them is invalid, because re-using
such cached dictionaries means using an old call-stack instead of
constructing a new one, as was reported in #25529.
Fixes #25529.
(cherry picked from commit 256ac29c8df4f17a1d50ea243408d506ebf395d6)
- - - - -
9c0bc522 by Zubin Duggal at 2025-07-24T06:03:25+05:30
In commit "Don't cache solved [W] HasCallStack constraints" (256ac29c8df4f17a1d50ea243408d506ebf395d6),
we attempt to use `tryM` to avoid errors when looking up certain known-key names like CallStack while
compiling ghc-prim and ghc-internal.
Unfortunately, `tryM` doesn't catch module lookup errors. This manifests as a failure to build ghc-prim
in `--make` mode on the GHC 9.10 branch.
Instead, we explicitly avoid doing lookups when we are compiling ghc-prim or ghc-internal instead of
relying on catching the exception.
- - - - -
ad925e3b by Zubin Duggal at 2025-07-24T06:03:25+05:30
Prepare 9.10.3 prerelease
- - - - -
20 changed files:
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Types.hs
- configure.ac
- + docs/users_guide/9.10.3-notes.rst
- hadrian/hadrian.cabal
- hadrian/src/Context.hs
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Hadrian/Haskell/Cabal/Type.hs
- hadrian/src/Rules/BinaryDist.hs
- hadrian/src/Rules/CabalReinstall.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Rules/Rts.hs
- hadrian/src/Settings/Builders/Ghc.hs
- testsuite/tests/plugins/plugins10.stdout
- testsuite/tests/plugins/static-plugins.stdout
- + testsuite/tests/typecheck/should_run/T25529.hs
- + testsuite/tests/typecheck/should_run/T25529.stdout
- testsuite/tests/typecheck/should_run/all.T
Changes:
=====================================
compiler/GHC/Core/Predicate.hs
=====================================
@@ -27,7 +27,7 @@ module GHC.Core.Predicate (
-- Implicit parameters
isIPLikePred, mentionsIP, isIPTyCon, isIPClass,
isCallStackTy, isCallStackPred, isCallStackPredTy,
- isExceptionContextPred,
+ isExceptionContextPred, isExceptionContextTy,
isIPPred_maybe,
-- Evidence variables
@@ -39,7 +39,6 @@ import GHC.Prelude
import GHC.Core.Type
import GHC.Core.Class
-import GHC.Core.TyCo.Compare( eqType )
import GHC.Core.TyCon
import GHC.Core.TyCon.RecWalk
import GHC.Types.Var
@@ -292,7 +291,7 @@ isExceptionContextPred cls tys
| otherwise
= Nothing
--- | Is a type a 'CallStack'?
+-- | Is a type an 'ExceptionContext'?
isExceptionContextTy :: Type -> Bool
isExceptionContextTy ty
| Just tc <- tyConAppTyCon_maybe ty
@@ -338,31 +337,38 @@ isCallStackTy ty
isIPLikePred :: Type -> Bool
-- Is `pred`, or any of its superclasses, an implicit parameter?
-- See Note [Local implicit parameters]
-isIPLikePred pred = mentions_ip_pred initIPRecTc Nothing pred
-
-mentionsIP :: Type -> Class -> [Type] -> Bool
--- Is (cls tys) an implicit parameter with key `str_ty`, or
--- is any of its superclasses such at thing.
+isIPLikePred pred =
+ mentions_ip_pred initIPRecTc (const True) (const True) pred
+
+mentionsIP :: (Type -> Bool) -- ^ predicate on the string
+ -> (Type -> Bool) -- ^ predicate on the type
+ -> Class
+ -> [Type] -> Bool
+-- ^ @'mentionsIP' str_cond ty_cond cls tys@ returns @True@ if:
+--
+-- - @cls tys@ is of the form @IP str ty@, where @str_cond str@ and @ty_cond ty@
+-- are both @True@,
+-- - or any superclass of @cls tys@ has this property.
+--
-- See Note [Local implicit parameters]
-mentionsIP str_ty cls tys = mentions_ip initIPRecTc (Just str_ty) cls tys
-
-mentions_ip :: RecTcChecker -> Maybe Type -> Class -> [Type] -> Bool
-mentions_ip rec_clss mb_str_ty cls tys
- | Just (str_ty', _) <- isIPPred_maybe cls tys
- = case mb_str_ty of
- Nothing -> True
- Just str_ty -> str_ty `eqType` str_ty'
+mentionsIP = mentions_ip initIPRecTc
+
+mentions_ip :: RecTcChecker -> (Type -> Bool) -> (Type -> Bool) -> Class -> [Type] -> Bool
+mentions_ip rec_clss str_cond ty_cond cls tys
+ | Just (str_ty, ty) <- isIPPred_maybe cls tys
+ = str_cond str_ty && ty_cond ty
| otherwise
- = or [ mentions_ip_pred rec_clss mb_str_ty (classMethodInstTy sc_sel_id tys)
+ = or [ mentions_ip_pred rec_clss str_cond ty_cond (classMethodInstTy sc_sel_id tys)
| sc_sel_id <- classSCSelIds cls ]
-mentions_ip_pred :: RecTcChecker -> Maybe Type -> Type -> Bool
-mentions_ip_pred rec_clss mb_str_ty ty
+
+mentions_ip_pred :: RecTcChecker -> (Type -> Bool) -> (Type -> Bool) -> Type -> Bool
+mentions_ip_pred rec_clss str_cond ty_cond ty
| Just (cls, tys) <- getClassPredTys_maybe ty
, let tc = classTyCon cls
, Just rec_clss' <- if isTupleTyCon tc then Just rec_clss
else checkRecTc rec_clss tc
- = mentions_ip rec_clss' mb_str_ty cls tys
+ = mentions_ip rec_clss' str_cond ty_cond cls tys
| otherwise
= False -- Includes things like (D []) where D is
-- a Constraint-ranged family; #7785
@@ -429,7 +435,38 @@ Small worries (Sept 20):
* The superclass hunt stops when it encounters the same class again,
but in principle we could have the same class, differently instantiated,
and the second time it could have an implicit parameter
-I'm going to treat these as problems for another day. They are all exotic. -}
+I'm going to treat these as problems for another day. They are all exotic.
+
+Note [Using typesAreApart when calling mentionsIP]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We call 'mentionsIP' in two situations:
+
+ (1) to check that a predicate does not contain any implicit parameters
+ IP str ty, for a fixed literal str and any type ty,
+ (2) to check that a predicate does not contain any HasCallStack or
+ HasExceptionContext constraints.
+
+In both of these cases, we want to be sure, so we should be conservative:
+
+ For (1), the predicate might contain an implicit parameter IP Str a, where
+ Str is a type family such as:
+
+ type family MyStr where MyStr = "abc"
+
+ To safeguard against this (niche) situation, instead of doing a simple
+ type equality check, we use 'typesAreApart'. This allows us to recognise
+ that 'IP MyStr a' contains an implicit parameter of the form 'IP "abc" ty'.
+
+ For (2), we similarly might have
+
+ type family MyCallStack where MyCallStack = CallStack
+
+ Again, here we use 'typesAreApart'. This allows us to see that
+
+ (?foo :: MyCallStack)
+
+ is indeed a CallStack constraint, hidden under a type family.
+-}
{- *********************************************************************
* *
=====================================
compiler/GHC/Tc/Solver/Dict.hs
=====================================
@@ -32,7 +32,7 @@ import GHC.Core.InstEnv ( DFunInstType )
import GHC.Core.Class
import GHC.Core.Predicate
import GHC.Core.Multiplicity ( scaledThing )
-import GHC.Core.Unify ( ruleMatchTyKiX )
+import GHC.Core.Unify ( ruleMatchTyKiX , typesAreApart )
import GHC.Types.Name
import GHC.Types.Name.Set
@@ -105,21 +105,25 @@ updInertDicts :: DictCt -> TcS ()
updInertDicts dict_ct@(DictCt { di_cls = cls, di_ev = ev, di_tys = tys })
= do { traceTcS "Adding inert dict" (ppr dict_ct $$ ppr cls <+> ppr tys)
- ; if | isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys
+ ; if | isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys
-> -- See (SIP1) and (SIP2) in Note [Shadowing of implicit parameters]
-- Update /both/ inert_cans /and/ inert_solved_dicts.
updInertSet $ \ inerts@(IS { inert_cans = ics, inert_solved_dicts = solved }) ->
- inerts { inert_cans = updDicts (filterDicts (not_ip_for str_ty)) ics
- , inert_solved_dicts = filterDicts (not_ip_for str_ty) solved }
- | otherwise
+ inerts { inert_cans = updDicts (filterDicts (does_not_mention_ip_for str_ty)) ics
+ , inert_solved_dicts = filterDicts (does_not_mention_ip_for str_ty) solved }
+ | otherwise
-> return ()
-- Add the new constraint to the inert set
; updInertCans (updDicts (addDict dict_ct)) }
where
- not_ip_for :: Type -> DictCt -> Bool
- not_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys })
- = not (mentionsIP str_ty cls tys)
+ -- Does this class constraint or any of its superclasses mention
+ -- an implicit parameter (?str :: ty) for the given 'str' and any type 'ty'?
+ does_not_mention_ip_for :: Type -> DictCt -> Bool
+ does_not_mention_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys })
+ = not $ mentionsIP (not . typesAreApart str_ty) (const True) cls tys
+ -- See Note [Using typesAreApart when calling mentionsIP]
+ -- in GHC.Core.Predicate
canDictCt :: CtEvidence -> Class -> [Type] -> SolverStage DictCt
-- Once-only processing of Dict constraints:
@@ -201,7 +205,7 @@ in two places:
* In `GHC.Tc.Solver.InertSet.solveOneFromTheOther`, be careful when we have
(?x :: ty) in the inert set and an identical (?x :: ty) as the work item.
-* In `updInertDicts` in this module, when adding [G] (?x :: ty), remove any
+* In `updInertDicts`, in this module, when adding [G] (?x :: ty), remove any
existing [G] (?x :: ty'), regardless of ty'.
* Wrinkle (SIP1): we must be careful of superclasses. Consider
@@ -221,7 +225,7 @@ in two places:
An important special case is constraint tuples like [G] (% ?x::ty, Eq a %).
But it could happen for `class xx => D xx where ...` and the constraint D
(?x :: int). This corner (constraint-kinded variables instantiated with
- implicit parameter constraints) is not well explorered.
+ implicit parameter constraints) is not well explored.
Example in #14218, and #23761
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -158,7 +158,7 @@ import GHC.Tc.Types.Origin
import GHC.Tc.Types.Constraint
import GHC.Tc.Utils.Unify
-import GHC.Builtin.Names ( unsatisfiableClassNameKey )
+import GHC.Builtin.Names ( unsatisfiableClassNameKey, callStackTyConName, exceptionContextTyConName )
import GHC.Core.Type
import GHC.Core.TyCo.Rep as Rep
@@ -168,6 +168,7 @@ import GHC.Core.Predicate
import GHC.Core.Reduction
import GHC.Core.Class
import GHC.Core.TyCon
+import GHC.Core.Unify (typesAreApart)
import GHC.Types.Name
import GHC.Types.TyThing
@@ -177,13 +178,13 @@ import GHC.Types.Var.Set
import GHC.Types.Unique.Supply
import GHC.Types.Unique.Set( elementOfUniqSet )
-import GHC.Unit.Module ( HasModule, getModule, extractModule )
+import GHC.Unit.Module ( HasModule, getModule, extractModule, primUnit, moduleUnit, ghcInternalUnit)
import qualified GHC.Rename.Env as TcM
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Logger
-import GHC.Utils.Misc (HasDebugCallStack)
+import GHC.Utils.Misc (HasDebugCallStack, (<||>))
import GHC.Data.Bag as Bag
import GHC.Data.Pair
@@ -478,14 +479,92 @@ getSafeOverlapFailures
updSolvedDicts :: InstanceWhat -> DictCt -> TcS ()
-- Conditionally add a new item in the solved set of the monad
-- See Note [Solved dictionaries] in GHC.Tc.Solver.InertSet
-updSolvedDicts what dict_ct@(DictCt { di_ev = ev })
+updSolvedDicts what dict_ct@(DictCt { di_cls = cls, di_tys = tys, di_ev = ev })
| isWanted ev
, instanceReturnsDictCon what
- = do { traceTcS "updSolvedDicts:" $ ppr dict_ct
+ = do { is_callstack <- is_tyConTy isCallStackTy callStackTyConName
+ ; is_exceptionCtx <- is_tyConTy isExceptionContextTy exceptionContextTyConName
+ ; let contains_callstack_or_exceptionCtx =
+ mentionsIP
+ (const True)
+ -- NB: the name of the call-stack IP is irrelevant
+ -- e.g (?foo :: CallStack) counts!
+ (is_callstack <||> is_exceptionCtx)
+ cls tys
+ -- See Note [Don't add HasCallStack constraints to the solved set]
+ ; unless contains_callstack_or_exceptionCtx $
+ do { traceTcS "updSolvedDicts:" $ ppr dict_ct
; updInertSet $ \ ics ->
- ics { inert_solved_dicts = addSolvedDict dict_ct (inert_solved_dicts ics) } }
+ ics { inert_solved_dicts = addSolvedDict dict_ct (inert_solved_dicts ics) }
+ } }
| otherwise
= return ()
+ where
+
+ -- Return a predicate that decides whether a type is CallStack
+ -- or ExceptionContext, accounting for e.g. type family reduction, as
+ -- per Note [Using typesAreApart when calling mentionsIP].
+ --
+ -- See Note [Using isCallStackTy in mentionsIP].
+ is_tyConTy :: (Type -> Bool) -> Name -> TcS (Type -> Bool)
+ is_tyConTy is_eq tc_name
+ = do { mb_tc <- wrapTcS $ do
+ mod <- tcg_mod <$> TcM.getGblEnv
+ if moduleUnit mod `elem` [primUnit, ghcInternalUnit]
+ then return Nothing
+ else Just <$> TcM.tcLookupTyCon tc_name
+ ; case mb_tc of
+ Just tc ->
+ return $ \ ty -> not (typesAreApart ty (mkTyConTy tc))
+ Nothing ->
+ return is_eq
+ }
+
+{- Note [Don't add HasCallStack constraints to the solved set]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We must not add solved Wanted dictionaries that mention HasCallStack constraints
+to the solved set, or we might fail to accumulate the proper call stack, as was
+reported in #25529.
+
+Recall that HasCallStack constraints (and the related HasExceptionContext
+constraints) are implicit parameter constraints, and are accumulated as per
+Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence.
+
+When we solve a Wanted that contains a HasCallStack constraint, we don't want
+to cache the result, because re-using that solution means re-using the call-stack
+in a different context!
+
+See also Note [Shadowing of implicit parameters], which deals with a similar
+problem with Given implicit parameter constraints.
+
+Note [Using isCallStackTy in mentionsIP]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+To implement Note [Don't add HasCallStack constraints to the solved set],
+we need to check whether a constraint contains a HasCallStack or HasExceptionContext
+constraint. We do this using the 'mentionsIP' function, but as per
+Note [Using typesAreApart when calling mentionsIP] we don't want to simply do:
+
+ mentionsIP
+ (const True) -- (ignore the implicit parameter string)
+ (isCallStackTy <||> isExceptionContextTy)
+
+because this does not account for e.g. a type family that reduces to CallStack.
+The predicate we want to use instead is:
+
+ \ ty -> not (typesAreApart ty callStackTy && typesAreApart ty exceptionContextTy)
+
+However, this is made difficult by the fact that CallStack and ExceptionContext
+are not wired-in types; they are only known-key. This means we must look them
+up using 'tcLookupTyCon'. However, this might fail, e.g. if we are in the middle
+of typechecking ghc-internal and these data-types have not been typechecked yet!
+
+In that case, we simply fall back to the naive 'isCallStackTy'/'isExceptionContextTy'
+logic.
+
+Note that it would be somewhat painful to wire-in ExceptionContext: at the time
+of writing (March 2025), this would require wiring in the ExceptionAnnotation
+class, as well as SomeExceptionAnnotation, which is a data type with existentials.
+-}
getSolvedDicts :: TcS (DictMap DictCt)
getSolvedDicts = do { ics <- getInertSet; return (inert_solved_dicts ics) }
=====================================
compiler/GHC/Tc/Solver/Types.hs
=====================================
@@ -166,7 +166,7 @@ Suppose f :: HasCallStack => blah. Then
IP "callStack" CallStack
See Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence
-* We cannonicalise such constraints, in GHC.Tc.Solver.Dict.canDictNC, by
+* We canonicalise such constraints, in GHC.Tc.Solver.Dict.canDictNC, by
pushing the call-site info on the stack, and changing the CtOrigin
to record that has been done.
Bind: s1 = pushCallStack <site-info> s2
=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.10.2], [glasgow-ha
AC_CONFIG_MACRO_DIRS([m4])
# Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
# The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
# above. If this is not a released version, then we will append the
=====================================
docs/users_guide/9.10.3-notes.rst
=====================================
@@ -0,0 +1,165 @@
+.. _release-9-10-3:
+
+Version 9.10.3
+===============
+The significant changes to the various parts of the compiler are listed in the
+following sections. See the `migration guide
+<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.10>`_ on the GHC Wiki
+for specific guidance on migrating programs to this release.
+
+
+Compiler
+~~~~~~~~
+
+- Don't cache solved [W] HasCallStack constraints to avoid re-using old
+ call-stacks instead of constructing new ones. (:ghc-ticket:`25529`)
+
+- Fix EmptyCase panic in tcMatches when \case{} is checked against a function
+ type preceded by invisible forall. (:ghc-ticket:`25960`)
+
+- Fix panic triggered by combination of \case{} and forall t ->. (:ghc-ticket:`25004`)
+
+- Fix GHC.SysTools.Ar archive member size writing logic that was emitting wrong
+ archive member sizes in headers. (:ghc-ticket:`26120`, :ghc-ticket:`22586`)
+
+- Fix multiple bugs in name resolution of subordinate import lists related to
+ type namespace specifiers and hiding clauses. (:ghc-ticket:`22581`, :ghc-ticket:`25983`, :ghc-ticket:`25984`, :ghc-ticket:`25991`)
+
+- Use mkTrAppChecked in ds_ev_typeable to avoid false negatives for type
+ equality involving function types. (:ghc-ticket:`25998`)
+
+- Fix bytecode generation for ``tagToEnum# <LITERAL>``. (:ghc-ticket:`25975`)
+
+- Don't report used duplicate record fields as unused. (:ghc-ticket:`24035`)
+
+- Propagate long distance info to guarded let binds for better pattern-match
+ checking warnings. (:ghc-ticket:`25749`)
+
+- Prevent incorrect unpacking optimizations for GADTs with multiple constructors. (:ghc-ticket:`25672`)
+
+- Introduce a separate argument limit for forced specs via SPEC argument with
+ warning when limit is exceeded. (:ghc-ticket:`25197`)
+
+Build system and packaging
+~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+- 9.10 hadrian can build with Cabal-3.12.1. (:ghc-ticket:`25605`)
+
+- GHC settings: always unescape escaped spaces to fix handling of spaces in
+ executable paths. (:ghc-ticket:`25204`)
+
+Native code generator backend
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+- x86 NCG: Fix code generation of bswap64 on i386. (:ghc-ticket:`25601`)
+
+- AArch64 NCG: Fix sub-word arithmetic right shift by zero-extending sub-word
+ values. (:ghc-ticket:`26061`)
+
+- NCG: AArch64 - Add -finter-module-far-jumps flag for modules with far jumps
+ outside the current module. (:ghc-ticket:`24648`)
+
+LLVM backend
+~~~~~~~~~~~~
+
+- LLVM: fix typo in padLiveArgs that was incorrectly computing too many padding
+ registers causing segfaults. (:ghc-ticket:`25770`, :ghc-ticket:`25773`)
+
+- llvmGen: Fix linkage of built-in arrays to use Appending linkage instead of
+ Internal. (:ghc-ticket:`25769`)
+
+- llvmGen: Fix built-in variable predicate to check for `@llvm` rather than
+ `$llvm`.
+
+WebAssembly backend
+~~~~~~~~~~~~~~~~~~~
+
+- wasm: use primitive opcodes for fabs and sqrt operations.
+
+Runtime system
+~~~~~~~~~~~~~~
+
+- rts: Implement WEAK EXTERNAL undef redirection by target symbol name.
+
+- rts: Handle API set symbol versioning conflicts.
+
+- rts: fix rts_clearMemory logic when sanity checks are enabled. (:ghc-ticket:`26011`)
+
+- rts/linker: Improve efficiency of proddable blocks structure by using binary
+ search instead of linked lists for better performance with split sections. (:ghc-ticket:`26009`)
+
+- rts/linker/PEi386: Don't repeatedly load DLLs by maintaining a hash-set of
+ loaded DLL names. (:ghc-ticket:`26009`, :ghc-ticket:`26052`)
+
+- rts/linker: Don't fail due to RTLD_NOW by attempting eager binding first,
+ then reverting to lazy binding on failure. (:ghc-ticket:`25943`)
+
+``base`` library
+~~~~~~~~~~~~~~~~
+
+- base: Expose Backtraces constructor and fields. (:ghc-ticket:`26049`)
+
+- base: Note strictness changes made in 4.16.0.0. (:ghc-ticket:`25886`)
+
+- Fix bugs in ``integerRecipMod`` and ``integerPowMod`` return values. (:ghc-ticket:`26017`)
+
+``ghc`` library
+~~~~~~~~~~~~~~~
+
+- perf: Replace uses of genericLength with strictGenericLength to reduce time
+ spent in 'assembleBCOs' and allocations. (:ghc-ticket:`25706`)
+
+Build tools
+~~~~~~~~~~~
+
+- configure: Drop probing of ld.gold since `gold` has been dropped from
+ binutils-2.44. (:ghc-ticket:`25716`)
+
+- get-win32-tarballs.py: List tarball files to be downloaded if we cannot find
+ them. (:ghc-ticket:`25929`)
+
+- hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc.
+
+Included libraries
+~~~~~~~~~~~~~~~~~~
+
+The package database provided with this distribution also contains a number of
+packages other than GHC itself. See the changelogs provided with these packages
+for further change information.
+
+.. ghc-package-list::
+
+ libraries/array/array.cabal: Dependency of ``ghc`` library
+ libraries/base/base.cabal: Core library
+ libraries/binary/binary.cabal: Dependency of ``ghc`` library
+ libraries/bytestring/bytestring.cabal: Dependency of ``ghc`` library
+ libraries/Cabal/Cabal/Cabal.cabal: Dependency of ``ghc-pkg`` utility
+ libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal: Dependency of ``ghc-pkg`` utility
+ libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
+ libraries/deepseq/deepseq.cabal: Dependency of ``ghc`` library
+ libraries/directory/directory.cabal: Dependency of ``ghc`` library
+ libraries/exceptions/exceptions.cabal: Dependency of ``ghc`` and ``haskeline`` library
+ libraries/filepath/filepath.cabal: Dependency of ``ghc`` library
+ compiler/ghc.cabal: The compiler itself
+ libraries/ghci/ghci.cabal: The REPL interface
+ libraries/ghc-boot/ghc-boot.cabal: Internal compiler library
+ libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
+ libraries/ghc-compact/ghc-compact.cabal: Core library
+ libraries/ghc-heap/ghc-heap.cabal: GHC heap-walking library
+ libraries/ghc-prim/ghc-prim.cabal: Core library
+ libraries/haskeline/haskeline.cabal: Dependency of ``ghci`` executable
+ libraries/hpc/hpc.cabal: Dependency of ``hpc`` executable
+ libraries/integer-gmp/integer-gmp.cabal: Core library
+ libraries/mtl/mtl.cabal: Dependency of ``Cabal`` library
+ libraries/parsec/parsec.cabal: Dependency of ``Cabal`` library
+ libraries/pretty/pretty.cabal: Dependency of ``ghc`` library
+ libraries/process/process.cabal: Dependency of ``ghc`` library
+ libraries/stm/stm.cabal: Dependency of ``haskeline`` library
+ libraries/template-haskell/template-haskell.cabal: Core library
+ libraries/terminfo/terminfo.cabal: Dependency of ``haskeline`` library
+ libraries/text/text.cabal: Dependency of ``Cabal`` library
+ libraries/time/time.cabal: Dependency of ``ghc`` library
+ libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
+ libraries/unix/unix.cabal: Dependency of ``ghc`` library
+ libraries/Win32/Win32.cabal: Dependency of ``ghc`` library
+ libraries/xhtml/xhtml.cabal: Dependency of ``haddock`` executable
\ No newline at end of file
=====================================
hadrian/hadrian.cabal
=====================================
@@ -152,7 +152,7 @@ executable hadrian
, TypeOperators
other-extensions: MultiParamTypeClasses
, TypeFamilies
- build-depends: Cabal >= 3.10 && < 3.11
+ build-depends: Cabal (>= 3.10 && < 3.11) || (>= 3.12.1 && < 3.13)
, base >= 4.11 && < 5
, bytestring >= 0.10 && < 0.13
, containers >= 0.5 && < 0.8
=====================================
hadrian/src/Context.hs
=====================================
@@ -9,7 +9,7 @@ module Context (
contextDir, buildPath, buildDir, pkgInplaceConfig, pkgSetupConfigFile, pkgSetupConfigDir,
pkgHaddockFile, pkgRegisteredLibraryFile, pkgRegisteredLibraryFileName,
pkgLibraryFile, pkgGhciLibraryFile,
- pkgConfFile, pkgStampFile, resourcePath, objectPath, contextPath, getContextPath, libPath, distDir,
+ pkgConfFile, pkgStampFile, resourcePath, objectPath, contextPath, getContextPath, libPath, distDir, distDynDir,
haddockStatsFilesDir
) where
@@ -20,7 +20,8 @@ import Hadrian.Expression
import Hadrian.Haskell.Cabal
import Oracles.Setting
import GHC.Toolchain.Target (Target(..))
-import GHC.Platform.ArchOS
+import Hadrian.Oracles.Cabal
+import Hadrian.Haskell.Cabal.Type
-- | Most targets are built only one way, hence the notion of 'vanillaContext'.
vanillaContext :: Stage -> Package -> Context
@@ -62,12 +63,15 @@ libPath Context {..} = buildRoot <&> (-/- (stageString stage -/- "lib"))
--
-- We preform some renaming to accommodate Cabal's slightly different naming
-- conventions (see 'cabalOsString' and 'cabalArchString').
-distDir :: Stage -> Action FilePath
-distDir st = do
- version <- ghcVersionStage st
- targetOs <- cabalOsString . stringEncodeOS . archOS_OS . tgtArchOs <$> targetStage st
- targetArch <- cabalArchString . stringEncodeArch . archOS_arch . tgtArchOs <$> targetStage st
- return $ targetArch ++ "-" ++ targetOs ++ "-ghc-" ++ version
+distDir :: Context -> Action FilePath
+distDir c = do
+ cd <- readContextData c
+ return (contextLibdir cd)
+
+distDynDir :: Context -> Action FilePath
+distDynDir c = do
+ cd <- readContextData c
+ return (contextDynLibdir cd)
pkgFileName :: Context -> Package -> String -> String -> Action FilePath
pkgFileName context package prefix suffix = do
@@ -104,13 +108,12 @@ pkgHaddockFile Context {..} = do
-- @_build/stage1/lib/x86_64-linux-ghc-8.9.0/array-0.5.1.0/libHSarray-0.5.4.0.a@
pkgRegisteredLibraryFile :: Context -> Action FilePath
pkgRegisteredLibraryFile context@Context {..} = do
- libDir <- libPath context
- pkgId <- pkgUnitId stage package
fileName <- pkgRegisteredLibraryFileName context
- distDir <- distDir stage
+ distDir <- distDir context
+ distDynDir <- distDynDir context
return $ if Dynamic `wayUnit` way
- then libDir -/- distDir -/- fileName
- else libDir -/- distDir -/- pkgId -/- fileName
+ then distDynDir -/- fileName
+ else distDir -/- fileName
-- | Just the final filename portion of pkgRegisteredLibraryFile
pkgRegisteredLibraryFileName :: Context -> Action FilePath
=====================================
hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
=====================================
@@ -254,6 +254,7 @@ resolveContextData context@Context {..} = do
pdi <- liftIO $ getHookedBuildInfo [pkgPath package, cPath -/- "build"]
let pd' = C.updatePackageDescription pdi (C.localPkgDescr lbi)
lbi' = lbi { C.localPkgDescr = pd' }
+ pkgDbPath <- packageDbPath (PackageDbLoc stage iplace)
-- TODO: Get rid of deprecated 'externalPackageDeps' and drop -Wno-deprecations
-- See: https://github.com/snowleopard/hadrian/issues/548
@@ -302,6 +303,8 @@ resolveContextData context@Context {..} = do
| takeExtension fp `elem` [".cpp", ".cxx", ".c++"]= CppMain
| otherwise = CMain
+ install_dirs = absoluteInstallDirs pd' lbi' (CopyToDb pkgDbPath)
+
main_src = fmap (first C.display) mainIs
cdata = ContextData
{ dependencies = deps
@@ -343,7 +346,10 @@ resolveContextData context@Context {..} = do
, depLdOpts = forDeps Installed.ldOptions
, buildGhciLib = C.withGHCiLib lbi'
, frameworks = C.frameworks buildInfo
- , packageDescription = pd' }
+ , packageDescription = pd'
+ , contextLibdir = libdir install_dirs
+ , contextDynLibdir = dynlibdir install_dirs
+ }
in return cdata
=====================================
hadrian/src/Hadrian/Haskell/Cabal/Type.hs
=====================================
@@ -70,6 +70,10 @@ data ContextData = ContextData
, buildGhciLib :: Bool
, frameworks :: [String]
, packageDescription :: PackageDescription
+ -- The location where normal library files go
+ , contextLibdir :: FilePath
+ -- The location where dynamic libraries go
+ , contextDynLibdir :: FilePath
} deriving (Eq, Generic, Show, Typeable)
instance Binary PackageData
=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -146,7 +146,7 @@ bindistRules = do
phony "binary-dist-dir" $ do
version <- setting ProjectVersion
targetPlatform <- setting TargetPlatformFull
- distDir <- Context.distDir Stage1
+ distDir <- Context.distDir (vanillaContext Stage1 rts)
rtsDir <- pkgUnitId Stage1 rts
-- let rtsDir = "rts"
=====================================
hadrian/src/Rules/CabalReinstall.hs
=====================================
@@ -53,13 +53,10 @@ cabalBuildRules = do
iserv_targets <- if cross then pure [] else iservBins
need (lib_targets ++ (map (\(_, p) -> p) (bin_targets ++ iserv_targets)))
- distDir <- Context.distDir Stage1
- rtsDir <- pkgUnitId Stage1 rts
+ distDir <- Context.distDir (vanillaContext Stage1 rts)
-- let rtsDir = "rts"
- let ghcBuildDir = root -/- stageString Stage1
- rtsIncludeDir = ghcBuildDir -/- "lib" -/- distDir -/- rtsDir
- -/- "include"
+ let rtsIncludeDir = distDir -/- "include"
libdir <- liftIO . IO.makeAbsolute =<< stageLibPath Stage1
work_dir <- liftIO $ IO.makeAbsolute $ root -/- "stage-cabal"
=====================================
hadrian/src/Rules/Register.hs
=====================================
@@ -182,11 +182,12 @@ buildConfFinal rs context@Context {..} _conf = do
--
-- so that if any change ends up modifying a library (but not its .conf
-- file), we still rebuild things that depend on it.
- dir <- (-/-) <$> libPath context <*> distDir stage
+ dir <- distDir context
+ dyndir <- distDynDir context
pkgid <- pkgUnitId stage package
files <- liftIO $
- (++) <$> getDirectoryFilesIO "." [dir -/- "*libHS"++pkgid++"*"]
- <*> getDirectoryFilesIO "." [dir -/- pkgid -/- "**"]
+ (++) <$> getDirectoryFilesIO "." [dyndir -/- "*libHS"++pkgid++"*"]
+ <*> getDirectoryFilesIO "." [dir -/- "**"]
produces files
buildConfInplace :: [(Resource, Int)] -> Context -> FilePath -> Action ()
=====================================
hadrian/src/Rules/Rts.hs
=====================================
@@ -154,10 +154,9 @@ needRtsSymLinks :: Stage -> Set.Set Way -> Action ()
needRtsSymLinks stage rtsWays
= forM_ (Set.filter (wayUnit Dynamic) rtsWays) $ \ way -> do
let ctx = Context stage rts way Final
- libPath <- libPath ctx
- distDir <- distDir stage
+ distDir <- distDynDir ctx
rtsLibFile <- takeFileName <$> pkgLibraryFile ctx
- need [removeRtsDummyVersion (libPath </> distDir </> rtsLibFile)]
+ need [removeRtsDummyVersion (distDir </> rtsLibFile)]
prefix, versionlessPrefix :: String
versionlessPrefix = "libHSrts"
=====================================
hadrian/src/Settings/Builders/Ghc.hs
=====================================
@@ -98,9 +98,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
-- Relative path from the output (rpath $ORIGIN).
originPath <- dropFileName <$> getOutput
context <- getContext
- libPath' <- expr (libPath context)
- st <- getStage
- distDir <- expr (Context.distDir st)
+ distPath <- expr (Context.distDynDir context)
useSystemFfi <- expr (flag UseSystemFfi)
buildPath <- getBuildPath
@@ -112,7 +110,6 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
let
dynamic = Dynamic `wayUnit` way
- distPath = libPath' -/- distDir
originToLibsDir = makeRelativeNoSysLink originPath distPath
rpath
-- Programs will end up in the bin dir ($ORIGIN) and will link to
=====================================
testsuite/tests/plugins/plugins10.stdout
=====================================
@@ -7,6 +7,8 @@ interfacePlugin: GHC.Internal.Float
interfacePlugin: GHC.Prim.Ext
interfacePlugin: Language.Haskell.TH.Syntax
typeCheckPlugin (rn)
+interfacePlugin: GHC.Internal.Stack.Types
+interfacePlugin: GHC.Internal.Exception.Context
typeCheckPlugin (tc)
parsePlugin(a)
typeCheckPlugin (rn)
=====================================
testsuite/tests/plugins/static-plugins.stdout
=====================================
@@ -8,6 +8,8 @@ interfacePlugin: GHC.Internal.System.IO
interfacePlugin: GHC.Types
interfacePlugin: GHC.Internal.Show
typeCheckPlugin (rn)
+interfacePlugin: GHC.Internal.Stack.Types
+interfacePlugin: GHC.Internal.Exception.Context
interfacePlugin: GHC.Internal.TopHandler
typeCheckPlugin (tc)
interfacePlugin: GHC.CString
=====================================
testsuite/tests/typecheck/should_run/T25529.hs
=====================================
@@ -0,0 +1,33 @@
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE ImplicitParams #-}
+
+module Main where
+
+import GHC.Stack (HasCallStack, CallStack, SrcLoc(srcLocStartLine, srcLocStartCol), callStack, getCallStack)
+
+main :: IO ()
+main =
+ let ?myImplicitParam = ()
+ in run action
+
+type MyConstraints = (HasCallStack, ?myImplicitParam :: ())
+
+action :: MyConstraints => IO ()
+action = run $ pure ()
+
+-- | Print the current call stack and then run an action.
+run ::
+ MyConstraints =>
+ IO a ->
+ IO a
+run action = do
+ let prettyCallStack = unlines $ map prettyCallStackEntry $ getCallStack callStack
+ prettyCallStackEntry (name, loc) =
+ name
+ <> ", called at "
+ <> show (srcLocStartLine loc)
+ <> ":"
+ <> show (srcLocStartCol loc)
+ putStrLn "============================================================"
+ putStrLn prettyCallStack
+ action
=====================================
testsuite/tests/typecheck/should_run/T25529.stdout
=====================================
@@ -0,0 +1,7 @@
+============================================================
+run, called at 11:7
+
+============================================================
+run, called at 16:10
+action, called at 11:11
+
=====================================
testsuite/tests/typecheck/should_run/all.T
=====================================
@@ -170,6 +170,7 @@ test('T22510', normal, compile_and_run, [''])
test('T21973a', [exit_code(1)], compile_and_run, [''])
test('T21973b', normal, compile_and_run, [''])
test('T23761', normal, compile_and_run, [''])
+test('T25529', normal, compile_and_run, [''])
test('T23761b', normal, compile_and_run, [''])
test('T17594e', normal, compile_and_run, [''])
test('T25998', normal, compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a2398ad0dc9b6eaff0743156117488…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a2398ad0dc9b6eaff0743156117488…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/9.10.3-backports] 4 commits: 9.10 hadrian can build with Cabal-3.12.1
by Zubin (@wz1000) 24 Jul '25
by Zubin (@wz1000) 24 Jul '25
24 Jul '25
Zubin pushed to branch wip/9.10.3-backports at Glasgow Haskell Compiler / GHC
Commits:
6e25fe9e by Jens Petersen at 2025-07-24T06:01:42+05:30
9.10 hadrian can build with Cabal-3.12.1
fixes #25605
(cherry picked from commit 07f17b6ed1bb0ba7134ee8dfd992036e97552c94)
- - - - -
7d52147f by sheaf at 2025-07-24T06:01:42+05:30
Don't cache solved [W] HasCallStack constraints
This commit ensures we do not add solved Wanted constraints that mention
HasCallStack or HasExceptionContext constraints to the set of solved
Wanted dictionary constraints: caching them is invalid, because re-using
such cached dictionaries means using an old call-stack instead of
constructing a new one, as was reported in #25529.
Fixes #25529.
(cherry picked from commit 256ac29c8df4f17a1d50ea243408d506ebf395d6)
- - - - -
e373cfb5 by Zubin Duggal at 2025-07-24T06:01:42+05:30
In commit "Don't cache solved [W] HasCallStack constraints" (256ac29c8df4f17a1d50ea243408d506ebf395d6),
we attempt to use `tryM` to avoid errors when looking up certain known-key names like CallStack while
compiling ghc-prim and ghc-internal.
Unfortunately, `tryM` doesn't catch module lookup errors. This manifests as a failure to build ghc-prim
in `--make` mode on the GHC 9.10 branch.
Instead, we explicitly avoid doing lookups when we are compiling ghc-prim or ghc-internal instead of
relying on catching the exception.
- - - - -
a2398ad0 by Zubin Duggal at 2025-07-24T06:01:42+05:30
Prepare 9.10.3 prerelease
- - - - -
20 changed files:
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Types.hs
- configure.ac
- + docs/users_guide/9.10.3-notes.rst
- hadrian/hadrian.cabal
- hadrian/src/Context.hs
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Hadrian/Haskell/Cabal/Type.hs
- hadrian/src/Rules/BinaryDist.hs
- hadrian/src/Rules/CabalReinstall.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Rules/Rts.hs
- hadrian/src/Settings/Builders/Ghc.hs
- testsuite/tests/plugins/plugins10.stdout
- testsuite/tests/plugins/static-plugins.stdout
- + testsuite/tests/typecheck/should_run/T25529.hs
- + testsuite/tests/typecheck/should_run/T25529.stdout
- testsuite/tests/typecheck/should_run/all.T
Changes:
=====================================
compiler/GHC/Core/Predicate.hs
=====================================
@@ -27,7 +27,7 @@ module GHC.Core.Predicate (
-- Implicit parameters
isIPLikePred, mentionsIP, isIPTyCon, isIPClass,
isCallStackTy, isCallStackPred, isCallStackPredTy,
- isExceptionContextPred,
+ isExceptionContextPred, isExceptionContextTy,
isIPPred_maybe,
-- Evidence variables
@@ -39,7 +39,6 @@ import GHC.Prelude
import GHC.Core.Type
import GHC.Core.Class
-import GHC.Core.TyCo.Compare( eqType )
import GHC.Core.TyCon
import GHC.Core.TyCon.RecWalk
import GHC.Types.Var
@@ -292,7 +291,7 @@ isExceptionContextPred cls tys
| otherwise
= Nothing
--- | Is a type a 'CallStack'?
+-- | Is a type an 'ExceptionContext'?
isExceptionContextTy :: Type -> Bool
isExceptionContextTy ty
| Just tc <- tyConAppTyCon_maybe ty
@@ -338,31 +337,38 @@ isCallStackTy ty
isIPLikePred :: Type -> Bool
-- Is `pred`, or any of its superclasses, an implicit parameter?
-- See Note [Local implicit parameters]
-isIPLikePred pred = mentions_ip_pred initIPRecTc Nothing pred
-
-mentionsIP :: Type -> Class -> [Type] -> Bool
--- Is (cls tys) an implicit parameter with key `str_ty`, or
--- is any of its superclasses such at thing.
+isIPLikePred pred =
+ mentions_ip_pred initIPRecTc (const True) (const True) pred
+
+mentionsIP :: (Type -> Bool) -- ^ predicate on the string
+ -> (Type -> Bool) -- ^ predicate on the type
+ -> Class
+ -> [Type] -> Bool
+-- ^ @'mentionsIP' str_cond ty_cond cls tys@ returns @True@ if:
+--
+-- - @cls tys@ is of the form @IP str ty@, where @str_cond str@ and @ty_cond ty@
+-- are both @True@,
+-- - or any superclass of @cls tys@ has this property.
+--
-- See Note [Local implicit parameters]
-mentionsIP str_ty cls tys = mentions_ip initIPRecTc (Just str_ty) cls tys
-
-mentions_ip :: RecTcChecker -> Maybe Type -> Class -> [Type] -> Bool
-mentions_ip rec_clss mb_str_ty cls tys
- | Just (str_ty', _) <- isIPPred_maybe cls tys
- = case mb_str_ty of
- Nothing -> True
- Just str_ty -> str_ty `eqType` str_ty'
+mentionsIP = mentions_ip initIPRecTc
+
+mentions_ip :: RecTcChecker -> (Type -> Bool) -> (Type -> Bool) -> Class -> [Type] -> Bool
+mentions_ip rec_clss str_cond ty_cond cls tys
+ | Just (str_ty, ty) <- isIPPred_maybe cls tys
+ = str_cond str_ty && ty_cond ty
| otherwise
- = or [ mentions_ip_pred rec_clss mb_str_ty (classMethodInstTy sc_sel_id tys)
+ = or [ mentions_ip_pred rec_clss str_cond ty_cond (classMethodInstTy sc_sel_id tys)
| sc_sel_id <- classSCSelIds cls ]
-mentions_ip_pred :: RecTcChecker -> Maybe Type -> Type -> Bool
-mentions_ip_pred rec_clss mb_str_ty ty
+
+mentions_ip_pred :: RecTcChecker -> (Type -> Bool) -> (Type -> Bool) -> Type -> Bool
+mentions_ip_pred rec_clss str_cond ty_cond ty
| Just (cls, tys) <- getClassPredTys_maybe ty
, let tc = classTyCon cls
, Just rec_clss' <- if isTupleTyCon tc then Just rec_clss
else checkRecTc rec_clss tc
- = mentions_ip rec_clss' mb_str_ty cls tys
+ = mentions_ip rec_clss' str_cond ty_cond cls tys
| otherwise
= False -- Includes things like (D []) where D is
-- a Constraint-ranged family; #7785
@@ -429,7 +435,38 @@ Small worries (Sept 20):
* The superclass hunt stops when it encounters the same class again,
but in principle we could have the same class, differently instantiated,
and the second time it could have an implicit parameter
-I'm going to treat these as problems for another day. They are all exotic. -}
+I'm going to treat these as problems for another day. They are all exotic.
+
+Note [Using typesAreApart when calling mentionsIP]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We call 'mentionsIP' in two situations:
+
+ (1) to check that a predicate does not contain any implicit parameters
+ IP str ty, for a fixed literal str and any type ty,
+ (2) to check that a predicate does not contain any HasCallStack or
+ HasExceptionContext constraints.
+
+In both of these cases, we want to be sure, so we should be conservative:
+
+ For (1), the predicate might contain an implicit parameter IP Str a, where
+ Str is a type family such as:
+
+ type family MyStr where MyStr = "abc"
+
+ To safeguard against this (niche) situation, instead of doing a simple
+ type equality check, we use 'typesAreApart'. This allows us to recognise
+ that 'IP MyStr a' contains an implicit parameter of the form 'IP "abc" ty'.
+
+ For (2), we similarly might have
+
+ type family MyCallStack where MyCallStack = CallStack
+
+ Again, here we use 'typesAreApart'. This allows us to see that
+
+ (?foo :: MyCallStack)
+
+ is indeed a CallStack constraint, hidden under a type family.
+-}
{- *********************************************************************
* *
=====================================
compiler/GHC/Tc/Solver/Dict.hs
=====================================
@@ -32,7 +32,7 @@ import GHC.Core.InstEnv ( DFunInstType )
import GHC.Core.Class
import GHC.Core.Predicate
import GHC.Core.Multiplicity ( scaledThing )
-import GHC.Core.Unify ( ruleMatchTyKiX )
+import GHC.Core.Unify ( ruleMatchTyKiX , typesAreApart )
import GHC.Types.Name
import GHC.Types.Name.Set
@@ -105,21 +105,25 @@ updInertDicts :: DictCt -> TcS ()
updInertDicts dict_ct@(DictCt { di_cls = cls, di_ev = ev, di_tys = tys })
= do { traceTcS "Adding inert dict" (ppr dict_ct $$ ppr cls <+> ppr tys)
- ; if | isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys
+ ; if | isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys
-> -- See (SIP1) and (SIP2) in Note [Shadowing of implicit parameters]
-- Update /both/ inert_cans /and/ inert_solved_dicts.
updInertSet $ \ inerts@(IS { inert_cans = ics, inert_solved_dicts = solved }) ->
- inerts { inert_cans = updDicts (filterDicts (not_ip_for str_ty)) ics
- , inert_solved_dicts = filterDicts (not_ip_for str_ty) solved }
- | otherwise
+ inerts { inert_cans = updDicts (filterDicts (does_not_mention_ip_for str_ty)) ics
+ , inert_solved_dicts = filterDicts (does_not_mention_ip_for str_ty) solved }
+ | otherwise
-> return ()
-- Add the new constraint to the inert set
; updInertCans (updDicts (addDict dict_ct)) }
where
- not_ip_for :: Type -> DictCt -> Bool
- not_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys })
- = not (mentionsIP str_ty cls tys)
+ -- Does this class constraint or any of its superclasses mention
+ -- an implicit parameter (?str :: ty) for the given 'str' and any type 'ty'?
+ does_not_mention_ip_for :: Type -> DictCt -> Bool
+ does_not_mention_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys })
+ = not $ mentionsIP (not . typesAreApart str_ty) (const True) cls tys
+ -- See Note [Using typesAreApart when calling mentionsIP]
+ -- in GHC.Core.Predicate
canDictCt :: CtEvidence -> Class -> [Type] -> SolverStage DictCt
-- Once-only processing of Dict constraints:
@@ -201,7 +205,7 @@ in two places:
* In `GHC.Tc.Solver.InertSet.solveOneFromTheOther`, be careful when we have
(?x :: ty) in the inert set and an identical (?x :: ty) as the work item.
-* In `updInertDicts` in this module, when adding [G] (?x :: ty), remove any
+* In `updInertDicts`, in this module, when adding [G] (?x :: ty), remove any
existing [G] (?x :: ty'), regardless of ty'.
* Wrinkle (SIP1): we must be careful of superclasses. Consider
@@ -221,7 +225,7 @@ in two places:
An important special case is constraint tuples like [G] (% ?x::ty, Eq a %).
But it could happen for `class xx => D xx where ...` and the constraint D
(?x :: int). This corner (constraint-kinded variables instantiated with
- implicit parameter constraints) is not well explorered.
+ implicit parameter constraints) is not well explored.
Example in #14218, and #23761
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -158,7 +158,7 @@ import GHC.Tc.Types.Origin
import GHC.Tc.Types.Constraint
import GHC.Tc.Utils.Unify
-import GHC.Builtin.Names ( unsatisfiableClassNameKey )
+import GHC.Builtin.Names ( unsatisfiableClassNameKey, callStackTyConName, exceptionContextTyConName )
import GHC.Core.Type
import GHC.Core.TyCo.Rep as Rep
@@ -168,6 +168,7 @@ import GHC.Core.Predicate
import GHC.Core.Reduction
import GHC.Core.Class
import GHC.Core.TyCon
+import GHC.Core.Unify (typesAreApart)
import GHC.Types.Name
import GHC.Types.TyThing
@@ -177,13 +178,13 @@ import GHC.Types.Var.Set
import GHC.Types.Unique.Supply
import GHC.Types.Unique.Set( elementOfUniqSet )
-import GHC.Unit.Module ( HasModule, getModule, extractModule )
+import GHC.Unit.Module ( HasModule, getModule, extractModule, primUnit, moduleUnit, ghcInternalUnit)
import qualified GHC.Rename.Env as TcM
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Logger
-import GHC.Utils.Misc (HasDebugCallStack)
+import GHC.Utils.Misc (HasDebugCallStack, (<||>))
import GHC.Data.Bag as Bag
import GHC.Data.Pair
@@ -478,14 +479,92 @@ getSafeOverlapFailures
updSolvedDicts :: InstanceWhat -> DictCt -> TcS ()
-- Conditionally add a new item in the solved set of the monad
-- See Note [Solved dictionaries] in GHC.Tc.Solver.InertSet
-updSolvedDicts what dict_ct@(DictCt { di_ev = ev })
+updSolvedDicts what dict_ct@(DictCt { di_cls = cls, di_tys = tys, di_ev = ev })
| isWanted ev
, instanceReturnsDictCon what
- = do { traceTcS "updSolvedDicts:" $ ppr dict_ct
+ = do { is_callstack <- is_tyConTy isCallStackTy callStackTyConName
+ ; is_exceptionCtx <- is_tyConTy isExceptionContextTy exceptionContextTyConName
+ ; let contains_callstack_or_exceptionCtx =
+ mentionsIP
+ (const True)
+ -- NB: the name of the call-stack IP is irrelevant
+ -- e.g (?foo :: CallStack) counts!
+ (is_callstack <||> is_exceptionCtx)
+ cls tys
+ -- See Note [Don't add HasCallStack constraints to the solved set]
+ ; unless contains_callstack_or_exceptionCtx $
+ do { traceTcS "updSolvedDicts:" $ ppr dict_ct
; updInertSet $ \ ics ->
- ics { inert_solved_dicts = addSolvedDict dict_ct (inert_solved_dicts ics) } }
+ ics { inert_solved_dicts = addSolvedDict dict_ct (inert_solved_dicts ics) }
+ } }
| otherwise
= return ()
+ where
+
+ -- Return a predicate that decides whether a type is CallStack
+ -- or ExceptionContext, accounting for e.g. type family reduction, as
+ -- per Note [Using typesAreApart when calling mentionsIP].
+ --
+ -- See Note [Using isCallStackTy in mentionsIP].
+ is_tyConTy :: (Type -> Bool) -> Name -> TcS (Type -> Bool)
+ is_tyConTy is_eq tc_name
+ = do { mb_tc <- wrapTcS $ do
+ mod <- tcg_mod <$> TcM.getGblEnv
+ if moduleUnit mod `elem` [primUnit, ghcInternalUnit]
+ then return Nothing
+ else Just <$> TcM.tcLookupTyCon tc_name
+ ; case mb_tc of
+ Just tc ->
+ return $ \ ty -> not (typesAreApart ty (mkTyConTy tc))
+ Nothing ->
+ return is_eq
+ }
+
+{- Note [Don't add HasCallStack constraints to the solved set]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We must not add solved Wanted dictionaries that mention HasCallStack constraints
+to the solved set, or we might fail to accumulate the proper call stack, as was
+reported in #25529.
+
+Recall that HasCallStack constraints (and the related HasExceptionContext
+constraints) are implicit parameter constraints, and are accumulated as per
+Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence.
+
+When we solve a Wanted that contains a HasCallStack constraint, we don't want
+to cache the result, because re-using that solution means re-using the call-stack
+in a different context!
+
+See also Note [Shadowing of implicit parameters], which deals with a similar
+problem with Given implicit parameter constraints.
+
+Note [Using isCallStackTy in mentionsIP]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+To implement Note [Don't add HasCallStack constraints to the solved set],
+we need to check whether a constraint contains a HasCallStack or HasExceptionContext
+constraint. We do this using the 'mentionsIP' function, but as per
+Note [Using typesAreApart when calling mentionsIP] we don't want to simply do:
+
+ mentionsIP
+ (const True) -- (ignore the implicit parameter string)
+ (isCallStackTy <||> isExceptionContextTy)
+
+because this does not account for e.g. a type family that reduces to CallStack.
+The predicate we want to use instead is:
+
+ \ ty -> not (typesAreApart ty callStackTy && typesAreApart ty exceptionContextTy)
+
+However, this is made difficult by the fact that CallStack and ExceptionContext
+are not wired-in types; they are only known-key. This means we must look them
+up using 'tcLookupTyCon'. However, this might fail, e.g. if we are in the middle
+of typechecking ghc-internal and these data-types have not been typechecked yet!
+
+In that case, we simply fall back to the naive 'isCallStackTy'/'isExceptionContextTy'
+logic.
+
+Note that it would be somewhat painful to wire-in ExceptionContext: at the time
+of writing (March 2025), this would require wiring in the ExceptionAnnotation
+class, as well as SomeExceptionAnnotation, which is a data type with existentials.
+-}
getSolvedDicts :: TcS (DictMap DictCt)
getSolvedDicts = do { ics <- getInertSet; return (inert_solved_dicts ics) }
=====================================
compiler/GHC/Tc/Solver/Types.hs
=====================================
@@ -166,7 +166,7 @@ Suppose f :: HasCallStack => blah. Then
IP "callStack" CallStack
See Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence
-* We cannonicalise such constraints, in GHC.Tc.Solver.Dict.canDictNC, by
+* We canonicalise such constraints, in GHC.Tc.Solver.Dict.canDictNC, by
pushing the call-site info on the stack, and changing the CtOrigin
to record that has been done.
Bind: s1 = pushCallStack <site-info> s2
=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.10.2], [glasgow-ha
AC_CONFIG_MACRO_DIRS([m4])
# Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
# The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
# above. If this is not a released version, then we will append the
=====================================
docs/users_guide/9.10.3-notes.rst
=====================================
@@ -0,0 +1,165 @@
+.. _release-9-10-3:
+
+Version 9.10.3
+===============
+The significant changes to the various parts of the compiler are listed in the
+following sections. See the `migration guide
+<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.10>`_ on the GHC Wiki
+for specific guidance on migrating programs to this release.
+
+
+Compiler
+~~~~~~~~
+
+- Don't cache solved [W] HasCallStack constraints to avoid re-using old
+ call-stacks instead of constructing new ones. (:ghc-ticket:`25529`)
+
+- Fix EmptyCase panic in tcMatches when \case{} is checked against a function
+ type preceded by invisible forall. (:ghc-ticket:`25960`)
+
+- Fix panic triggered by combination of \case{} and forall t ->. (:ghc-ticket:`25004`)
+
+- Fix GHC.SysTools.Ar archive member size writing logic that was emitting wrong
+ archive member sizes in headers. (:ghc-ticket:`26120`, :ghc-ticket:`22586`)
+
+- Fix multiple bugs in name resolution of subordinate import lists related to
+ type namespace specifiers and hiding clauses. (:ghc-ticket:`22581`, :ghc-ticket:`25983`, :ghc-ticket:`25984`, :ghc-ticket:`25991`)
+
+- Use mkTrAppChecked in ds_ev_typeable to avoid false negatives for type
+ equality involving function types. (:ghc-ticket:`25998`)
+
+- Fix bytecode generation for ``tagToEnum# <LITERAL>``. (:ghc-ticket:`25975`)
+
+- Don't report used duplicate record fields as unused. (:ghc-ticket:`24035`)
+
+- Propagate long distance info to guarded let binds for better pattern-match
+ checking warnings. (:ghc-ticket:`25749`)
+
+- Prevent incorrect unpacking optimizations for GADTs with multiple constructors. (:ghc-ticket:`25672`)
+
+- Introduce a separate argument limit for forced specs via SPEC argument with
+ warning when limit is exceeded. (:ghc-ticket:`25197`)
+
+Build system and packaging
+~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+- 9.10 hadrian can build with Cabal-3.12.1. (:ghc-ticket:`25605`)
+
+- GHC settings: always unescape escaped spaces to fix handling of spaces in
+ executable paths. (:ghc-ticket:`25204`)
+
+Native code generator backend
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+- x86 NCG: Fix code generation of bswap64 on i386. (:ghc-ticket:`25601`)
+
+- AArch64 NCG: Fix sub-word arithmetic right shift by zero-extending sub-word
+ values. (:ghc-ticket:`26061`)
+
+- NCG: AArch64 - Add -finter-module-far-jumps flag for modules with far jumps
+ outside the current module. (:ghc-ticket:`24648`)
+
+LLVM backend
+~~~~~~~~~~~~
+
+- LLVM: fix typo in padLiveArgs that was incorrectly computing too many padding
+ registers causing segfaults. (:ghc-ticket:`25770`, :ghc-ticket:`25773`)
+
+- llvmGen: Fix linkage of built-in arrays to use Appending linkage instead of
+ Internal. (:ghc-ticket:`25769`)
+
+- llvmGen: Fix built-in variable predicate to check for `@llvm` rather than
+ `$llvm`.
+
+WebAssembly backend
+~~~~~~~~~~~~~~~~~~~
+
+- wasm: use primitive opcodes for fabs and sqrt operations.
+
+Runtime system
+~~~~~~~~~~~~~~
+
+- rts: Implement WEAK EXTERNAL undef redirection by target symbol name.
+
+- rts: Handle API set symbol versioning conflicts.
+
+- rts: fix rts_clearMemory logic when sanity checks are enabled. (:ghc-ticket:`26011`)
+
+- rts/linker: Improve efficiency of proddable blocks structure by using binary
+ search instead of linked lists for better performance with split sections. (:ghc-ticket:`26009`)
+
+- rts/linker/PEi386: Don't repeatedly load DLLs by maintaining a hash-set of
+ loaded DLL names. (:ghc-ticket:`26009`, :ghc-ticket:`26052`)
+
+- rts/linker: Don't fail due to RTLD_NOW by attempting eager binding first,
+ then reverting to lazy binding on failure. (:ghc-ticket:`25943`)
+
+``base`` library
+~~~~~~~~~~~~~~~~
+
+- base: Expose Backtraces constructor and fields. (:ghc-ticket:`26049`)
+
+- base: Note strictness changes made in 4.16.0.0. (:ghc-ticket:`25886`)
+
+- Fix bugs in ``integerRecipMod`` and ``integerPowMod`` return values. (:ghc-ticket:`26017`)
+
+``ghc`` library
+~~~~~~~~~~~~~~~
+
+- perf: Replace uses of genericLength with strictGenericLength to reduce time
+ spent in 'assembleBCOs' and allocations. (:ghc-ticket:`25706`)
+
+Build tools
+~~~~~~~~~~~
+
+- configure: Drop probing of ld.gold since `gold` has been dropped from
+ binutils-2.44. (:ghc-ticket:`25716`)
+
+- get-win32-tarballs.py: List tarball files to be downloaded if we cannot find
+ them. (:ghc-ticket:`25929`)
+
+- hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc.
+
+Included libraries
+~~~~~~~~~~~~~~~~~~
+
+The package database provided with this distribution also contains a number of
+packages other than GHC itself. See the changelogs provided with these packages
+for further change information.
+
+.. ghc-package-list::
+
+ libraries/array/array.cabal: Dependency of ``ghc`` library
+ libraries/base/base.cabal: Core library
+ libraries/binary/binary.cabal: Dependency of ``ghc`` library
+ libraries/bytestring/bytestring.cabal: Dependency of ``ghc`` library
+ libraries/Cabal/Cabal/Cabal.cabal: Dependency of ``ghc-pkg`` utility
+ libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal: Dependency of ``ghc-pkg`` utility
+ libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
+ libraries/deepseq/deepseq.cabal: Dependency of ``ghc`` library
+ libraries/directory/directory.cabal: Dependency of ``ghc`` library
+ libraries/exceptions/exceptions.cabal: Dependency of ``ghc`` and ``haskeline`` library
+ libraries/filepath/filepath.cabal: Dependency of ``ghc`` library
+ compiler/ghc.cabal: The compiler itself
+ libraries/ghci/ghci.cabal: The REPL interface
+ libraries/ghc-boot/ghc-boot.cabal: Internal compiler library
+ libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
+ libraries/ghc-compact/ghc-compact.cabal: Core library
+ libraries/ghc-heap/ghc-heap.cabal: GHC heap-walking library
+ libraries/ghc-prim/ghc-prim.cabal: Core library
+ libraries/haskeline/haskeline.cabal: Dependency of ``ghci`` executable
+ libraries/hpc/hpc.cabal: Dependency of ``hpc`` executable
+ libraries/integer-gmp/integer-gmp.cabal: Core library
+ libraries/mtl/mtl.cabal: Dependency of ``Cabal`` library
+ libraries/parsec/parsec.cabal: Dependency of ``Cabal`` library
+ libraries/pretty/pretty.cabal: Dependency of ``ghc`` library
+ libraries/process/process.cabal: Dependency of ``ghc`` library
+ libraries/stm/stm.cabal: Dependency of ``haskeline`` library
+ libraries/template-haskell/template-haskell.cabal: Core library
+ libraries/terminfo/terminfo.cabal: Dependency of ``haskeline`` library
+ libraries/text/text.cabal: Dependency of ``Cabal`` library
+ libraries/time/time.cabal: Dependency of ``ghc`` library
+ libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
+ libraries/unix/unix.cabal: Dependency of ``ghc`` library
+ libraries/Win32/Win32.cabal: Dependency of ``ghc`` library
+ libraries/xhtml/xhtml.cabal: Dependency of ``haddock`` executable
\ No newline at end of file
=====================================
hadrian/hadrian.cabal
=====================================
@@ -152,7 +152,7 @@ executable hadrian
, TypeOperators
other-extensions: MultiParamTypeClasses
, TypeFamilies
- build-depends: Cabal >= 3.10 && < 3.11
+ build-depends: Cabal (>= 3.10 && < 3.11) || (>= 3.12.1 && < 3.13)
, base >= 4.11 && < 5
, bytestring >= 0.10 && < 0.13
, containers >= 0.5 && < 0.8
=====================================
hadrian/src/Context.hs
=====================================
@@ -9,7 +9,7 @@ module Context (
contextDir, buildPath, buildDir, pkgInplaceConfig, pkgSetupConfigFile, pkgSetupConfigDir,
pkgHaddockFile, pkgRegisteredLibraryFile, pkgRegisteredLibraryFileName,
pkgLibraryFile, pkgGhciLibraryFile,
- pkgConfFile, pkgStampFile, resourcePath, objectPath, contextPath, getContextPath, libPath, distDir,
+ pkgConfFile, pkgStampFile, resourcePath, objectPath, contextPath, getContextPath, libPath, distDir, distDynDir,
haddockStatsFilesDir
) where
@@ -20,7 +20,8 @@ import Hadrian.Expression
import Hadrian.Haskell.Cabal
import Oracles.Setting
import GHC.Toolchain.Target (Target(..))
-import GHC.Platform.ArchOS
+import Hadrian.Oracles.Cabal
+import Hadrian.Haskell.Cabal.Type
-- | Most targets are built only one way, hence the notion of 'vanillaContext'.
vanillaContext :: Stage -> Package -> Context
@@ -62,12 +63,15 @@ libPath Context {..} = buildRoot <&> (-/- (stageString stage -/- "lib"))
--
-- We preform some renaming to accommodate Cabal's slightly different naming
-- conventions (see 'cabalOsString' and 'cabalArchString').
-distDir :: Stage -> Action FilePath
-distDir st = do
- version <- ghcVersionStage st
- targetOs <- cabalOsString . stringEncodeOS . archOS_OS . tgtArchOs <$> targetStage st
- targetArch <- cabalArchString . stringEncodeArch . archOS_arch . tgtArchOs <$> targetStage st
- return $ targetArch ++ "-" ++ targetOs ++ "-ghc-" ++ version
+distDir :: Context -> Action FilePath
+distDir c = do
+ cd <- readContextData c
+ return (contextLibdir cd)
+
+distDynDir :: Context -> Action FilePath
+distDynDir c = do
+ cd <- readContextData c
+ return (contextDynLibdir cd)
pkgFileName :: Context -> Package -> String -> String -> Action FilePath
pkgFileName context package prefix suffix = do
@@ -104,13 +108,12 @@ pkgHaddockFile Context {..} = do
-- @_build/stage1/lib/x86_64-linux-ghc-8.9.0/array-0.5.1.0/libHSarray-0.5.4.0.a@
pkgRegisteredLibraryFile :: Context -> Action FilePath
pkgRegisteredLibraryFile context@Context {..} = do
- libDir <- libPath context
- pkgId <- pkgUnitId stage package
fileName <- pkgRegisteredLibraryFileName context
- distDir <- distDir stage
+ distDir <- distDir context
+ distDynDir <- distDynDir context
return $ if Dynamic `wayUnit` way
- then libDir -/- distDir -/- fileName
- else libDir -/- distDir -/- pkgId -/- fileName
+ then distDynDir -/- fileName
+ else distDir -/- fileName
-- | Just the final filename portion of pkgRegisteredLibraryFile
pkgRegisteredLibraryFileName :: Context -> Action FilePath
=====================================
hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
=====================================
@@ -254,6 +254,7 @@ resolveContextData context@Context {..} = do
pdi <- liftIO $ getHookedBuildInfo [pkgPath package, cPath -/- "build"]
let pd' = C.updatePackageDescription pdi (C.localPkgDescr lbi)
lbi' = lbi { C.localPkgDescr = pd' }
+ pkgDbPath <- packageDbPath (PackageDbLoc stage iplace)
-- TODO: Get rid of deprecated 'externalPackageDeps' and drop -Wno-deprecations
-- See: https://github.com/snowleopard/hadrian/issues/548
@@ -302,6 +303,8 @@ resolveContextData context@Context {..} = do
| takeExtension fp `elem` [".cpp", ".cxx", ".c++"]= CppMain
| otherwise = CMain
+ install_dirs = absoluteInstallDirs pd' lbi' (CopyToDb pkgDbPath)
+
main_src = fmap (first C.display) mainIs
cdata = ContextData
{ dependencies = deps
@@ -343,7 +346,10 @@ resolveContextData context@Context {..} = do
, depLdOpts = forDeps Installed.ldOptions
, buildGhciLib = C.withGHCiLib lbi'
, frameworks = C.frameworks buildInfo
- , packageDescription = pd' }
+ , packageDescription = pd'
+ , contextLibdir = libdir install_dirs
+ , contextDynLibdir = dynlibdir install_dirs
+ }
in return cdata
=====================================
hadrian/src/Hadrian/Haskell/Cabal/Type.hs
=====================================
@@ -70,6 +70,10 @@ data ContextData = ContextData
, buildGhciLib :: Bool
, frameworks :: [String]
, packageDescription :: PackageDescription
+ -- The location where normal library files go
+ , contextLibdir :: FilePath
+ -- The location where dynamic libraries go
+ , contextDynLibdir :: FilePath
} deriving (Eq, Generic, Show, Typeable)
instance Binary PackageData
=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -146,7 +146,7 @@ bindistRules = do
phony "binary-dist-dir" $ do
version <- setting ProjectVersion
targetPlatform <- setting TargetPlatformFull
- distDir <- Context.distDir Stage1
+ distDir <- Context.distDir (vanillaContext Stage1 rts)
rtsDir <- pkgUnitId Stage1 rts
-- let rtsDir = "rts"
=====================================
hadrian/src/Rules/CabalReinstall.hs
=====================================
@@ -53,13 +53,11 @@ cabalBuildRules = do
iserv_targets <- if cross then pure [] else iservBins
need (lib_targets ++ (map (\(_, p) -> p) (bin_targets ++ iserv_targets)))
- distDir <- Context.distDir Stage1
+ distDir <- Context.distDir (vanillaContext Stage1 rts)
rtsDir <- pkgUnitId Stage1 rts
-- let rtsDir = "rts"
- let ghcBuildDir = root -/- stageString Stage1
- rtsIncludeDir = ghcBuildDir -/- "lib" -/- distDir -/- rtsDir
- -/- "include"
+ let rtsIncludeDir = distDir -/- "include"
libdir <- liftIO . IO.makeAbsolute =<< stageLibPath Stage1
work_dir <- liftIO $ IO.makeAbsolute $ root -/- "stage-cabal"
=====================================
hadrian/src/Rules/Register.hs
=====================================
@@ -182,11 +182,12 @@ buildConfFinal rs context@Context {..} _conf = do
--
-- so that if any change ends up modifying a library (but not its .conf
-- file), we still rebuild things that depend on it.
- dir <- (-/-) <$> libPath context <*> distDir stage
+ dir <- distDir context
+ dyndir <- distDynDir context
pkgid <- pkgUnitId stage package
files <- liftIO $
- (++) <$> getDirectoryFilesIO "." [dir -/- "*libHS"++pkgid++"*"]
- <*> getDirectoryFilesIO "." [dir -/- pkgid -/- "**"]
+ (++) <$> getDirectoryFilesIO "." [dyndir -/- "*libHS"++pkgid++"*"]
+ <*> getDirectoryFilesIO "." [dir -/- "**"]
produces files
buildConfInplace :: [(Resource, Int)] -> Context -> FilePath -> Action ()
=====================================
hadrian/src/Rules/Rts.hs
=====================================
@@ -154,10 +154,9 @@ needRtsSymLinks :: Stage -> Set.Set Way -> Action ()
needRtsSymLinks stage rtsWays
= forM_ (Set.filter (wayUnit Dynamic) rtsWays) $ \ way -> do
let ctx = Context stage rts way Final
- libPath <- libPath ctx
- distDir <- distDir stage
+ distDir <- distDynDir ctx
rtsLibFile <- takeFileName <$> pkgLibraryFile ctx
- need [removeRtsDummyVersion (libPath </> distDir </> rtsLibFile)]
+ need [removeRtsDummyVersion (distDir </> rtsLibFile)]
prefix, versionlessPrefix :: String
versionlessPrefix = "libHSrts"
=====================================
hadrian/src/Settings/Builders/Ghc.hs
=====================================
@@ -99,8 +99,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
originPath <- dropFileName <$> getOutput
context <- getContext
libPath' <- expr (libPath context)
- st <- getStage
- distDir <- expr (Context.distDir st)
+ distPath <- expr (Context.distDynDir context)
useSystemFfi <- expr (flag UseSystemFfi)
buildPath <- getBuildPath
@@ -112,7 +111,6 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
let
dynamic = Dynamic `wayUnit` way
- distPath = libPath' -/- distDir
originToLibsDir = makeRelativeNoSysLink originPath distPath
rpath
-- Programs will end up in the bin dir ($ORIGIN) and will link to
=====================================
testsuite/tests/plugins/plugins10.stdout
=====================================
@@ -7,6 +7,8 @@ interfacePlugin: GHC.Internal.Float
interfacePlugin: GHC.Prim.Ext
interfacePlugin: Language.Haskell.TH.Syntax
typeCheckPlugin (rn)
+interfacePlugin: GHC.Internal.Stack.Types
+interfacePlugin: GHC.Internal.Exception.Context
typeCheckPlugin (tc)
parsePlugin(a)
typeCheckPlugin (rn)
=====================================
testsuite/tests/plugins/static-plugins.stdout
=====================================
@@ -8,6 +8,8 @@ interfacePlugin: GHC.Internal.System.IO
interfacePlugin: GHC.Types
interfacePlugin: GHC.Internal.Show
typeCheckPlugin (rn)
+interfacePlugin: GHC.Internal.Stack.Types
+interfacePlugin: GHC.Internal.Exception.Context
interfacePlugin: GHC.Internal.TopHandler
typeCheckPlugin (tc)
interfacePlugin: GHC.CString
=====================================
testsuite/tests/typecheck/should_run/T25529.hs
=====================================
@@ -0,0 +1,33 @@
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE ImplicitParams #-}
+
+module Main where
+
+import GHC.Stack (HasCallStack, CallStack, SrcLoc(srcLocStartLine, srcLocStartCol), callStack, getCallStack)
+
+main :: IO ()
+main =
+ let ?myImplicitParam = ()
+ in run action
+
+type MyConstraints = (HasCallStack, ?myImplicitParam :: ())
+
+action :: MyConstraints => IO ()
+action = run $ pure ()
+
+-- | Print the current call stack and then run an action.
+run ::
+ MyConstraints =>
+ IO a ->
+ IO a
+run action = do
+ let prettyCallStack = unlines $ map prettyCallStackEntry $ getCallStack callStack
+ prettyCallStackEntry (name, loc) =
+ name
+ <> ", called at "
+ <> show (srcLocStartLine loc)
+ <> ":"
+ <> show (srcLocStartCol loc)
+ putStrLn "============================================================"
+ putStrLn prettyCallStack
+ action
=====================================
testsuite/tests/typecheck/should_run/T25529.stdout
=====================================
@@ -0,0 +1,7 @@
+============================================================
+run, called at 11:7
+
+============================================================
+run, called at 16:10
+action, called at 11:11
+
=====================================
testsuite/tests/typecheck/should_run/all.T
=====================================
@@ -170,6 +170,7 @@ test('T22510', normal, compile_and_run, [''])
test('T21973a', [exit_code(1)], compile_and_run, [''])
test('T21973b', normal, compile_and_run, [''])
test('T23761', normal, compile_and_run, [''])
+test('T25529', normal, compile_and_run, [''])
test('T23761b', normal, compile_and_run, [''])
test('T17594e', normal, compile_and_run, [''])
test('T25998', normal, compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/72e5c618bd6386ce03018537ad447d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/72e5c618bd6386ce03018537ad447d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
24 Jul '25
Zubin pushed to branch wip/9.10.3-backports at Glasgow Haskell Compiler / GHC
Commits:
72e5c618 by Zubin Duggal at 2025-07-24T05:38:10+05:30
Prepare 9.10.3 prerelease
- - - - -
2 changed files:
- configure.ac
- + docs/users_guide/9.10.3-notes.rst
Changes:
=====================================
configure.ac
=====================================
@@ -22,7 +22,7 @@ AC_INIT([The Glorious Glasgow Haskell Compilation System], [9.10.2], [glasgow-ha
AC_CONFIG_MACRO_DIRS([m4])
# Set this to YES for a released version, otherwise NO
-: ${RELEASE=YES}
+: ${RELEASE=NO}
# The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
# above. If this is not a released version, then we will append the
=====================================
docs/users_guide/9.10.3-notes.rst
=====================================
@@ -0,0 +1,165 @@
+.. _release-9-10-3:
+
+Version 9.10.3
+===============
+The significant changes to the various parts of the compiler are listed in the
+following sections. See the `migration guide
+<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.10>`_ on the GHC Wiki
+for specific guidance on migrating programs to this release.
+
+
+Compiler
+~~~~~~~~
+
+- Don't cache solved [W] HasCallStack constraints to avoid re-using old
+ call-stacks instead of constructing new ones. (:ghc-ticket:`25529`)
+
+- Fix EmptyCase panic in tcMatches when \case{} is checked against a function
+ type preceded by invisible forall. (:ghc-ticket:`25960`)
+
+- Fix panic triggered by combination of \case{} and forall t ->. (:ghc-ticket:`25004`)
+
+- Fix GHC.SysTools.Ar archive member size writing logic that was emitting wrong
+ archive member sizes in headers. (:ghc-ticket:`26120`, :ghc-ticket:`22586`)
+
+- Fix multiple bugs in name resolution of subordinate import lists related to
+ type namespace specifiers and hiding clauses. (:ghc-ticket:`22581`, :ghc-ticket:`25983`, :ghc-ticket:`25984`, :ghc-ticket:`25991`)
+
+- Use mkTrAppChecked in ds_ev_typeable to avoid false negatives for type
+ equality involving function types. (:ghc-ticket:`25998`)
+
+- Fix bytecode generation for ``tagToEnum# <LITERAL>``. (:ghc-ticket:`25975`)
+
+- Don't report used duplicate record fields as unused. (:ghc-ticket:`24035`)
+
+- Propagate long distance info to guarded let binds for better pattern-match
+ checking warnings. (:ghc-ticket:`25749`)
+
+- Prevent incorrect unpacking optimizations for GADTs with multiple constructors. (:ghc-ticket:`25672`)
+
+- Introduce a separate argument limit for forced specs via SPEC argument with
+ warning when limit is exceeded. (:ghc-ticket:`25197`)
+
+Build system and packaging
+~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+- 9.10 hadrian can build with Cabal-3.12.1. (:ghc-ticket:`25605`)
+
+- GHC settings: always unescape escaped spaces to fix handling of spaces in
+ executable paths. (:ghc-ticket:`25204`)
+
+Native code generator backend
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+- x86 NCG: Fix code generation of bswap64 on i386. (:ghc-ticket:`25601`)
+
+- AArch64 NCG: Fix sub-word arithmetic right shift by zero-extending sub-word
+ values. (:ghc-ticket:`26061`)
+
+- NCG: AArch64 - Add -finter-module-far-jumps flag for modules with far jumps
+ outside the current module. (:ghc-ticket:`24648`)
+
+LLVM backend
+~~~~~~~~~~~~
+
+- LLVM: fix typo in padLiveArgs that was incorrectly computing too many padding
+ registers causing segfaults. (:ghc-ticket:`25770`, :ghc-ticket:`25773`)
+
+- llvmGen: Fix linkage of built-in arrays to use Appending linkage instead of
+ Internal. (:ghc-ticket:`25769`)
+
+- llvmGen: Fix built-in variable predicate to check for `@llvm` rather than
+ `$llvm`.
+
+WebAssembly backend
+~~~~~~~~~~~~~~~~~~~
+
+- wasm: use primitive opcodes for fabs and sqrt operations.
+
+Runtime system
+~~~~~~~~~~~~~~
+
+- rts: Implement WEAK EXTERNAL undef redirection by target symbol name.
+
+- rts: Handle API set symbol versioning conflicts.
+
+- rts: fix rts_clearMemory logic when sanity checks are enabled. (:ghc-ticket:`26011`)
+
+- rts/linker: Improve efficiency of proddable blocks structure by using binary
+ search instead of linked lists for better performance with split sections. (:ghc-ticket:`26009`)
+
+- rts/linker/PEi386: Don't repeatedly load DLLs by maintaining a hash-set of
+ loaded DLL names. (:ghc-ticket:`26009`, :ghc-ticket:`26052`)
+
+- rts/linker: Don't fail due to RTLD_NOW by attempting eager binding first,
+ then reverting to lazy binding on failure. (:ghc-ticket:`25943`)
+
+``base`` library
+~~~~~~~~~~~~~~~~
+
+- base: Expose Backtraces constructor and fields. (:ghc-ticket:`26049`)
+
+- base: Note strictness changes made in 4.16.0.0. (:ghc-ticket:`25886`)
+
+- Fix bugs in ``integerRecipMod`` and ``integerPowMod`` return values. (:ghc-ticket:`26017`)
+
+``ghc`` library
+~~~~~~~~~~~~~~~
+
+- perf: Replace uses of genericLength with strictGenericLength to reduce time
+ spent in 'assembleBCOs' and allocations. (:ghc-ticket:`25706`)
+
+Build tools
+~~~~~~~~~~~
+
+- configure: Drop probing of ld.gold since `gold` has been dropped from
+ binutils-2.44. (:ghc-ticket:`25716`)
+
+- get-win32-tarballs.py: List tarball files to be downloaded if we cannot find
+ them. (:ghc-ticket:`25929`)
+
+- hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc.
+
+Included libraries
+~~~~~~~~~~~~~~~~~~
+
+The package database provided with this distribution also contains a number of
+packages other than GHC itself. See the changelogs provided with these packages
+for further change information.
+
+.. ghc-package-list::
+
+ libraries/array/array.cabal: Dependency of ``ghc`` library
+ libraries/base/base.cabal: Core library
+ libraries/binary/binary.cabal: Dependency of ``ghc`` library
+ libraries/bytestring/bytestring.cabal: Dependency of ``ghc`` library
+ libraries/Cabal/Cabal/Cabal.cabal: Dependency of ``ghc-pkg`` utility
+ libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal: Dependency of ``ghc-pkg`` utility
+ libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
+ libraries/deepseq/deepseq.cabal: Dependency of ``ghc`` library
+ libraries/directory/directory.cabal: Dependency of ``ghc`` library
+ libraries/exceptions/exceptions.cabal: Dependency of ``ghc`` and ``haskeline`` library
+ libraries/filepath/filepath.cabal: Dependency of ``ghc`` library
+ compiler/ghc.cabal: The compiler itself
+ libraries/ghci/ghci.cabal: The REPL interface
+ libraries/ghc-boot/ghc-boot.cabal: Internal compiler library
+ libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
+ libraries/ghc-compact/ghc-compact.cabal: Core library
+ libraries/ghc-heap/ghc-heap.cabal: GHC heap-walking library
+ libraries/ghc-prim/ghc-prim.cabal: Core library
+ libraries/haskeline/haskeline.cabal: Dependency of ``ghci`` executable
+ libraries/hpc/hpc.cabal: Dependency of ``hpc`` executable
+ libraries/integer-gmp/integer-gmp.cabal: Core library
+ libraries/mtl/mtl.cabal: Dependency of ``Cabal`` library
+ libraries/parsec/parsec.cabal: Dependency of ``Cabal`` library
+ libraries/pretty/pretty.cabal: Dependency of ``ghc`` library
+ libraries/process/process.cabal: Dependency of ``ghc`` library
+ libraries/stm/stm.cabal: Dependency of ``haskeline`` library
+ libraries/template-haskell/template-haskell.cabal: Core library
+ libraries/terminfo/terminfo.cabal: Dependency of ``haskeline`` library
+ libraries/text/text.cabal: Dependency of ``Cabal`` library
+ libraries/time/time.cabal: Dependency of ``ghc`` library
+ libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
+ libraries/unix/unix.cabal: Dependency of ``ghc`` library
+ libraries/Win32/Win32.cabal: Dependency of ``ghc`` library
+ libraries/xhtml/xhtml.cabal: Dependency of ``haddock`` executable
\ No newline at end of file
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/72e5c618bd6386ce03018537ad447d7…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/72e5c618bd6386ce03018537ad447d7…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T23162-spj] 2 commits: Work in progress [skip ci]
by Simon Peyton Jones (@simonpj) 23 Jul '25
by Simon Peyton Jones (@simonpj) 23 Jul '25
23 Jul '25
Simon Peyton Jones pushed to branch wip/T23162-spj at Glasgow Haskell Compiler / GHC
Commits:
b071f3c5 by Simon Peyton Jones at 2025-07-23T23:37:49+01:00
Work in progress [skip ci]
- - - - -
23570d20 by Simon Peyton Jones at 2025-07-23T23:38:25+01:00
Add hs-boot file [skip ci]
- - - - -
4 changed files:
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/FunDeps.hs
- compiler/GHC/Tc/Solver/Monad.hs
- + compiler/GHC/Tc/Solver/Solve.hs-boot
Changes:
=====================================
compiler/GHC/Tc/Solver/Dict.hs
=====================================
@@ -86,14 +86,15 @@ solveDict dict_ct@(DictCt { di_ev = ev, di_cls = cls, di_tys = tys })
= assertPpr (ctEvRewriteRole ev == Nominal) (ppr ev $$ ppr cls $$ ppr tys) $
do { simpleStage $ traceTcS "solveDict" (ppr dict_ct)
+ -- Look in the inert dictionaries
; tryInertDicts dict_ct
+
+ -- Try top-level instances
; tryInstances dict_ct
-- Try fundeps /after/ tryInstances:
-- see (DFL2) in Note [Do fundeps last]
--- ; doLocalFunDepImprovement dict_ct
- -- doLocalFunDepImprovement does StartAgain if there
- -- are any fundeps: see (DFL1) in Note [Do fundeps last]
+ ; doDictFunDepImprovement dict_ct
; simpleStage (updInertDicts dict_ct)
; stopWithStage (dictCtEvidence dict_ct) "Kept inert DictCt" }
=====================================
compiler/GHC/Tc/Solver/FunDeps.hs
=====================================
@@ -10,6 +10,8 @@ module GHC.Tc.Solver.FunDeps (
import GHC.Prelude
+import {-# SOURCE #-} GHC.Tc.Solver.Solve( solveSimpleWanteds )
+
import GHC.Tc.Instance.FunDeps
import GHC.Tc.Types.Evidence
import GHC.Tc.Types.Constraint
@@ -295,7 +297,7 @@ as the fundeps.
#7875 is a case in point.
-}
-doDictFunDepImprovement :: DictCt -> SolverStage Void
+doDictFunDepImprovement :: DictCt -> SolverStage ()
-- (doDictFunDepImprovement inst_envs cts)
-- * Generate the fundeps from interacting the
-- top-level `inst_envs` with the constraints `cts`
@@ -306,13 +308,26 @@ doDictFunDepImprovement :: DictCt -> SolverStage Void
-- are any fundeps: see (DFL1) in Note [Do fundeps last]
doDictFunDepImprovement dict_ct
- = do { inst_envs <- getInstEnvs
- ; imp_res1 <- do_dict_local_fds dict_ct
- ; if noImprovement imp_res1
- then do { imp_res2 <- do_one_top inst_envs dict_ct
- ; return (imp_res `plusImprovements` imp_res2) }
- else return (imp_res `plusImprovements` imp_res1) }
+ = Stage $
+ -- Local dictionaries
+ do { inst_envs <- getInstEnvs
+ ; imp1 <- solveFunDeps (do_dict_local_fds dict_ct)
+ ; if imp1 then start_again else
+ -- Top-level instances dictionaries
+ do { imp2 <- solveFunDeps (do_one_top inst_envs dict_ct)
+ ; if imp2 then start_again
+ else continueWith () } }
+ where
+ start_again = startAgainWith (CDictCan dict_ct)
+solveFunDeps :: TcS ImprovementResult -> TcS Bool
+solveFunDeps generate_eqs
+ = do { (eqs, imp1) <- generate_eqs
+ ; if isEmptyBag eqs
+ then return imp1
+ else do { imp2 <- nestFunDepsTcS $
+ solveWanteds eqs
+ ; return (imp1 || imp2) } }
do_one_top :: InstEnvs -> DictCt -> TcS ImprovementResult
do_one_top inst_envs (DictCt { di_ev = ev, di_cls = cls, di_tys = xis })
@@ -340,7 +355,6 @@ do_dict_local_fds :: DictCt -> TcS ImprovementResult
-- Using functional dependencies, interact the DictCt with the
-- inert Givens and Wanteds, to produce new equalities
do_dict_local_fds dict_ct@(DictCt { di_cls = cls, di_ev = wanted_ev })
- -- locals contains all the Givens and earlier Wanteds
= do { inerts <- getInertCans
; foldM do_interaction noopImprovement $
findDictsByClass locals cls }
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -1353,6 +1353,30 @@ nestTcS (TcS thing_inside)
; return res }
+nestFunDepsTcS :: TcS a -> TcS Bool
+nestFunDepsTcS (TcS thing_inside)
+ = TcS $ \ env@(TcSEnv { tcs_inerts = inerts_var
+ , tcs_unif_lvl = unif_lvl_var }) ->
+ do { inerts <- TcM.readTcRef inerts_var
+ ; new_inert_var <- TcM.newTcRef inerts
+ ; new_wl_var <- TcM.newTcRef emptyWorkList
+ ; new_unif_lvl_var <- TcM.newTcRef Nothing
+ ; let nest_env = env { tcs_inerts = new_inert_var
+ , tcs_worklist = new_wl_var
+ , tcs_unif_lvl = new_unif_lvl_var }
+
+ ; (inner_lvl, res) <- TcM.pushTcLevelM $
+ thing_inside nest_env
+
+ ; mb_lvl <- TcM.readTcRef new_unif_lvl_var
+ ; case mb_lvl of
+ Just lvl | lvl < inner_lvl
+ -> do { setUnificationFlag lvl
+ ; return True }
+ _ -> return False -- No unifications (except of vars
+ -- generated in the fundep stuff itself)
+ }
+
emitImplicationTcS :: TcLevel -> SkolemInfoAnon
-> [TcTyVar] -- Skolems
-> [EvVar] -- Givens
=====================================
compiler/GHC/Tc/Solver/Solve.hs-boot
=====================================
@@ -0,0 +1,6 @@
+module GHC.Tc.Solver.Solve where
+
+import GHC.Tc.Solver.Monad
+import GHC.Tc.Types.Constraint
+
+solveSimpleWanteds :: Cts -> TcS WantedConstraints
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c9a428316d587d88158f56fc016125…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c9a428316d587d88158f56fc016125…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: Respect `-fdiagnostics-as-json` for error messages from pre-processors
by Marge Bot (@marge-bot) 23 Jul '25
by Marge Bot (@marge-bot) 23 Jul '25
23 Jul '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
84711c39 by Simon Hengel at 2025-07-23T18:27:34+07:00
Respect `-fdiagnostics-as-json` for error messages from pre-processors
(fixes #25480)
- - - - -
affcef9e by Simon Hengel at 2025-07-23T17:35:25-04:00
Include the rendered message in -fdiagnostics-as-json output
This implements #26173.
- - - - -
0c5588c5 by Ben Gamari at 2025-07-23T17:35:26-04:00
rts/Interpreter: Factor out ctoi tuple info tables into data
Instead of a massive case let's put this into data which we can reuse
elsewhere.
- - - - -
11 changed files:
- compiler/GHC/Driver/Errors.hs
- compiler/GHC/SysTools/Process.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Utils/Logger.hs
- docs/users_guide/9.14.1-notes.rst
- + docs/users_guide/diagnostics-as-json-schema-1_2.json
- docs/users_guide/using.rst
- ghc/GHCi/UI.hs
- rts/Interpreter.c
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json_warn.stderr
Changes:
=====================================
compiler/GHC/Driver/Errors.hs
=====================================
@@ -1,7 +1,9 @@
{-# LANGUAGE ScopedTypeVariables #-}
module GHC.Driver.Errors (
- printOrThrowDiagnostics
+ reportError
+ , reportDiagnostic
, printMessages
+ , printOrThrowDiagnostics
, mkDriverPsHeaderMessage
) where
@@ -10,10 +12,33 @@ import GHC.Prelude
import GHC.Types.SrcLoc
import GHC.Types.SourceError
import GHC.Types.Error
+import GHC.Utils.Json
import GHC.Utils.Error
import GHC.Utils.Outputable
import GHC.Utils.Logger
+reportError :: Logger -> NamePprCtx -> DiagOpts -> SrcSpan -> SDoc -> IO ()
+reportError logger nameContext opts span doc = do
+ let
+ message :: MsgEnvelope DiagnosticMessage
+ message = mkErrorMsgEnvelope span nameContext DiagnosticMessage {
+ diagMessage = mkDecorated [doc]
+ , diagReason = ErrorWithoutFlag
+ , diagHints = []
+ }
+ printMessage logger NoDiagnosticOpts opts message
+
+reportDiagnostic :: Logger -> NamePprCtx -> DiagOpts -> SrcSpan -> DiagnosticReason -> SDoc -> IO ()
+reportDiagnostic logger nameContext opts span reason doc = do
+ let
+ message :: MsgEnvelope DiagnosticMessage
+ message = mkMsgEnvelope opts span nameContext DiagnosticMessage {
+ diagMessage = mkDecorated [doc]
+ , diagReason = reason
+ , diagHints = []
+ }
+ printMessage logger NoDiagnosticOpts opts message
+
printMessages :: forall a. (Diagnostic a) => Logger -> DiagnosticOpts a -> DiagOpts -> Messages a -> IO ()
printMessages logger msg_opts opts = mapM_ (printMessage logger msg_opts opts) . sortMessages
where
@@ -22,9 +47,22 @@ printMessages logger msg_opts opts = mapM_ (printMessage logger msg_opts opts) .
printMessage :: forall a. (Diagnostic a) => Logger -> DiagnosticOpts a -> DiagOpts -> MsgEnvelope a -> IO ()
printMessage logger msg_opts opts message
- | log_diags_as_json = logJsonMsg logger messageClass message
+ | log_diags_as_json = do
+ decorated <- decorateDiagnostic logflags messageClass location doc
+ let
+ rendered :: String
+ rendered = renderWithContext (log_default_user_context logflags) decorated
+
+ jsonMessage :: JsonDoc
+ jsonMessage = jsonDiagnostic rendered message
+
+ logJsonMsg logger messageClass jsonMessage
+
| otherwise = logMsg logger messageClass location doc
where
+ logflags :: LogFlags
+ logflags = logFlags logger
+
doc :: SDoc
doc = updSDocContext (\_ -> ctx) (messageWithHints diagnostic)
=====================================
compiler/GHC/SysTools/Process.hs
=====================================
@@ -26,6 +26,8 @@ import GHC.Utils.Logger
import GHC.Utils.TmpFs
import GHC.Utils.CliOption
+import GHC.Driver.Errors (reportError)
+
import GHC.Types.SrcLoc ( SrcLoc, mkSrcLoc, mkSrcSpan )
import GHC.Data.FastString
@@ -286,8 +288,7 @@ builderMainLoop logger filter_fn pgm real_args mb_cwd mb_env = withPipe $ \ (rea
BuildMsg msg -> do
logInfo logger $ withPprStyle defaultUserStyle msg
BuildError loc msg -> do
- logMsg logger errorDiagnostic (mkSrcSpan loc loc)
- $ withPprStyle defaultUserStyle msg
+ reportError logger neverQualify emptyDiagOpts (mkSrcSpan loc loc) msg
parseBuildMessages :: [String] -> [BuildMessage]
parseBuildMessages str = loop str Nothing
=====================================
compiler/GHC/Types/Error.hs
=====================================
@@ -73,6 +73,9 @@ module GHC.Types.Error
, mkLocMessage
, mkLocMessageWarningGroups
, getCaretDiagnostic
+
+ , jsonDiagnostic
+
-- * Queries
, isIntrinsicErrorMessage
, isExtrinsicErrorMessage
@@ -109,7 +112,7 @@ import GHC.Utils.Panic
import GHC.Version (cProjectVersion)
import Data.Bifunctor
-import Data.Foldable ( fold, toList )
+import Data.Foldable
import Data.List.NonEmpty ( NonEmpty (..) )
import qualified Data.List.NonEmpty as NE
import Data.List ( intercalate )
@@ -171,9 +174,6 @@ instance Diagnostic e => Outputable (Messages e) where
pprDiagnostic (errMsgDiagnostic envelope)
]
-instance (Diagnostic e) => ToJson (Messages e) where
- json msgs = JSArray . toList $ json <$> getMessages msgs
-
{- Note [Discarding Messages]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -573,7 +573,7 @@ instance ToJson DiagnosticCode where
{- Note [Diagnostic Message JSON Schema]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The below instance of ToJson must conform to the JSON schema
-specified in docs/users_guide/diagnostics-as-json-schema-1_1.json.
+specified in docs/users_guide/diagnostics-as-json-schema-1_2.json.
When the schema is altered, please bump the version.
If the content is altered in a backwards compatible way,
update the minor version (e.g. 1.3 ~> 1.4).
@@ -586,15 +586,17 @@ https://json-schema.org
-}
schemaVersion :: String
-schemaVersion = "1.1"
+schemaVersion = "1.2"
+
-- See Note [Diagnostic Message JSON Schema] before editing!
-instance Diagnostic e => ToJson (MsgEnvelope e) where
- json m = JSObject $ [
+jsonDiagnostic :: forall e. Diagnostic e => String -> MsgEnvelope e -> JsonDoc
+jsonDiagnostic rendered m = JSObject $ [
("version", JSString schemaVersion),
("ghcVersion", JSString $ "ghc-" ++ cProjectVersion),
("span", json $ errMsgSpan m),
("severity", json $ errMsgSeverity m),
("code", maybe JSNull json (diagnosticCode diag)),
+ ("rendered", JSString rendered),
("message", JSArray $ map renderToJSString diagMsg),
("hints", JSArray $ map (renderToJSString . ppr) (diagnosticHints diag) ) ]
++ [ ("reason", reasonJson)
=====================================
compiler/GHC/Utils/Logger.hs
=====================================
@@ -62,6 +62,8 @@ module GHC.Utils.Logger
, logJsonMsg
, logDumpMsg
+ , decorateDiagnostic
+
-- * Dumping
, defaultDumpAction
, putDumpFile
@@ -419,26 +421,62 @@ defaultLogActionWithHandles out err logflags msg_class srcSpan msg
MCInfo -> printErrs msg
MCFatal -> printErrs msg
MCDiagnostic SevIgnore _ _ -> pure () -- suppress the message
- MCDiagnostic _sev _rea _code -> printDiagnostics
+ MCDiagnostic _sev _rea _code -> decorateDiagnostic logflags msg_class srcSpan msg >>= printErrs
where
printOut = defaultLogActionHPrintDoc logflags False out
printErrs = defaultLogActionHPrintDoc logflags False err
putStrSDoc = defaultLogActionHPutStrDoc logflags False out
+
+-- This function is used by `defaultLogActionWithHandles` for non-JSON output,
+-- and also by `GHC.Driver.Errors.printMessages` to produce the `rendered`
+-- message on `-fdiagnostics-as-json`.
+--
+-- We would want to eventually consolidate this. However, this is currently
+-- not feasible for the following reasons:
+--
+-- 1. Some parts of the compiler sidestep `printMessages`, for that reason we
+-- can not decorate the message in `printMessages`.
+--
+-- 2. GHC uses two different code paths for JSON and non-JSON diagnostics. For
+-- that reason we can not decorate the message in `defaultLogActionWithHandles`.
+--
+-- See also Note [JSON Error Messages]:
+--
+-- `jsonLogAction` should be removed along with -ddump-json
+--
+-- Also note that (1) is the reason why some parts of the compiler produce
+-- diagnostics that don't respect `-fdiagnostics-as-json`.
+--
+-- The plan as I see it is as follows:
+--
+-- 1. Refactor all places in the compiler that report diagnostics to go
+-- through `GHC.Driver.Errors.printMessages`.
+--
+-- (It's easy to find all those places by looking for who creates
+-- MCDiagnostic, either directly or via `mkMCDiagnostic` or
+-- `errorDiagnostic`.)
+--
+-- 2. Get rid of `-ddump-json`, `jsonLogAction` and consolidate message
+-- decoration at one place (either `printMessages` or
+-- `defaultLogActionWithHandles`)
+--
+-- This story is tracked by #24113.
+decorateDiagnostic :: LogFlags -> MessageClass -> SrcSpan -> SDoc -> IO SDoc
+decorateDiagnostic logflags msg_class srcSpan msg = addCaret
+ where
-- Pretty print the warning flag, if any (#10752)
+ message :: SDoc
message = mkLocMessageWarningGroups (log_show_warn_groups logflags) msg_class srcSpan msg
- printDiagnostics = do
+ addCaret :: IO SDoc
+ addCaret = do
caretDiagnostic <-
if log_show_caret logflags
then getCaretDiagnostic msg_class srcSpan
else pure empty
- printErrs $ getPprStyle $ \style ->
+ return $ getPprStyle $ \style ->
withPprStyle (setStyleColoured True style)
(message $+$ caretDiagnostic $+$ blankLine)
- -- careful (#2302): printErrs prints in UTF-8,
- -- whereas converting to string first and using
- -- hPutStr would just emit the low 8 bits of
- -- each unicode char.
-- | Like 'defaultLogActionHPutStrDoc' but appends an extra newline.
defaultLogActionHPrintDoc :: LogFlags -> Bool -> Handle -> SDoc -> IO ()
@@ -603,8 +641,8 @@ defaultTraceAction logflags title doc x =
logMsg :: Logger -> MessageClass -> SrcSpan -> SDoc -> IO ()
logMsg logger mc loc msg = putLogMsg logger (logFlags logger) mc loc msg
-logJsonMsg :: ToJson a => Logger -> MessageClass -> a -> IO ()
-logJsonMsg logger mc d = putJsonLogMsg logger (logFlags logger) mc (json d)
+logJsonMsg :: Logger -> MessageClass -> JsonDoc -> IO ()
+logJsonMsg logger mc = putJsonLogMsg logger (logFlags logger) mc
-- | Dump something
logDumpFile :: Logger -> PprStyle -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -147,6 +147,11 @@ Compiler
integer operations. Also, ``shuffleFloatX4#`` and ``shuffleDoubleX2#`` no longer
require ``-mavx``.
+- JSON diagnostics produced with (:ghc-flag:`-fdiagnostics-as-json`) now
+ include the `rendered` diagnostics message, in the exact same format as what
+ GHC would have produced without -fdiagnostics-as-json (including ANSI escape
+ sequences).
+
GHCi
~~~~
=====================================
docs/users_guide/diagnostics-as-json-schema-1_2.json
=====================================
@@ -0,0 +1,144 @@
+{
+ "$schema": "https://json-schema.org/draft/2020-12/schema",
+ "title": "JSON Diagnostic Schema",
+ "description": "A Schema for specifying GHC diagnostics output as JSON",
+ "type": "object",
+ "properties": {
+ "version": {
+ "description": "The current JSON schema version this object conforms to",
+ "type": "string"
+ },
+ "ghcVersion": {
+ "description": "The GHC version",
+ "type": "string"
+ },
+ "span": {
+ "oneOf": [
+ { "$ref": "#/$defs/span" },
+ { "type": "null" }
+ ]
+ },
+ "severity": {
+ "description": "The diagnostic severity",
+ "type": "string",
+ "enum": [
+ "Warning",
+ "Error"
+ ]
+ },
+ "code": {
+ "description": "The diagnostic code (if it exists)",
+ "type": [
+ "integer",
+ "null"
+ ]
+ },
+ "rendered": {
+ "description": "The rendered diagnostics message, in the exact same format as what GHC would have produced without -fdiagnostics-as-json (including ANSI escape sequences)",
+ "type": "string"
+ },
+ "message": {
+ "description": "The string output of the diagnostic message by GHC",
+ "type": "array",
+ "items": {
+ "type": "string"
+ }
+ },
+ "hints": {
+ "description": "The suggested fixes",
+ "type": "array",
+ "items": {
+ "type": "string"
+ }
+ },
+ "reason" : {
+ "description": "The GHC flag that was responsible for the emission of the diagnostic message",
+ "oneOf": [
+ {
+ "type": "object",
+ "description": "The diagnostic message was controlled by one or more GHC flags",
+ "properties": {
+ "flags": {
+ "type": "array",
+ "items": {
+ "description": "The name of a GHC flag controlling the diagnostic message",
+ "type": "string"
+ },
+ "minItems": 1
+ }
+ },
+ "required": ["flags"]
+ },
+ {
+ "type": "object",
+ "description": "The diagnostic message was controlled by a GHC diagnostic message category",
+ "properties": {
+ "category": {
+ "description": "The name of the GHC diagnostic message category controlling the diagnostic message",
+ "type": "string"
+ }
+ },
+ "required": ["category"]
+ }
+ ]
+ }
+ },
+
+ "$comment": "NOTE: \"rendered\" is not a required field so that the schema is backward compatible with version 1.1. If you bump the schema version to 2.0 the please also add \"rendered\" to the \"required\" fields.",
+ "required": [
+ "version",
+ "ghcVersion",
+ "span",
+ "severity",
+ "code",
+ "message",
+ "hints"
+ ],
+
+ "additionalProperties": false,
+ "$defs": {
+ "span": {
+ "description": "The span of the diagnostic",
+ "type": "object",
+ "properties": {
+ "file": {
+ "description": "The file in which the diagnostic occurs",
+ "type": "string"
+ },
+ "start": {
+ "description": "The start location of the diagnostic",
+ "$ref": "#/$defs/location"
+ },
+ "end": {
+ "description": "The end location of the diagnostic",
+ "$ref": "#/$defs/location"
+ }
+ },
+ "required": [
+ "file",
+ "start",
+ "end"
+ ],
+ "additionalProperties": false
+ },
+ "location": {
+ "description": "A location in a text file",
+ "type": "object",
+ "properties": {
+ "line": {
+ "description": "The line number",
+ "type": "integer"
+ },
+ "column": {
+ "description": "The column number",
+ "type": "integer"
+ }
+ },
+ "required": [
+ "line",
+ "column"
+ ],
+ "additionalProperties": false
+ }
+ }
+}
=====================================
docs/users_guide/using.rst
=====================================
@@ -1428,7 +1428,7 @@ messages and in GHCi:
a new line.
The structure of the output is described by a `JSON Schema <https://json-schema.org/>`_.
- The schema can be downloaded :download:`here <diagnostics-as-json-schema-1_1.json>`.
+ The schema can be downloaded :download:`here <diagnostics-as-json-schema-1_2.json>`.
.. ghc-flag:: -fdiagnostics-color=⟨always|auto|never⟩
:shortdesc: Use colors in error messages
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -53,7 +53,7 @@ import GHC.Core.DataCon
import GHC.Core.ConLike
import GHC.Core.PatSyn
import GHC.Driver.Flags
-import GHC.Driver.Errors
+import GHC.Driver.Errors (printOrThrowDiagnostics)
import GHC.Driver.Errors.Types
import GHC.Driver.Phases
import GHC.Driver.Session as DynFlags
=====================================
rts/Interpreter.c
=====================================
@@ -473,6 +473,72 @@ void interp_shutdown( void ){
#endif
+const StgPtr ctoi_tuple_infos[] = {
+ (StgPtr) &stg_ctoi_t0_info,
+ (StgPtr) &stg_ctoi_t1_info,
+ (StgPtr) &stg_ctoi_t2_info,
+ (StgPtr) &stg_ctoi_t3_info,
+ (StgPtr) &stg_ctoi_t4_info,
+ (StgPtr) &stg_ctoi_t5_info,
+ (StgPtr) &stg_ctoi_t6_info,
+ (StgPtr) &stg_ctoi_t7_info,
+ (StgPtr) &stg_ctoi_t8_info,
+ (StgPtr) &stg_ctoi_t9_info,
+ (StgPtr) &stg_ctoi_t10_info,
+ (StgPtr) &stg_ctoi_t11_info,
+ (StgPtr) &stg_ctoi_t12_info,
+ (StgPtr) &stg_ctoi_t13_info,
+ (StgPtr) &stg_ctoi_t14_info,
+ (StgPtr) &stg_ctoi_t15_info,
+ (StgPtr) &stg_ctoi_t16_info,
+ (StgPtr) &stg_ctoi_t17_info,
+ (StgPtr) &stg_ctoi_t18_info,
+ (StgPtr) &stg_ctoi_t19_info,
+ (StgPtr) &stg_ctoi_t20_info,
+ (StgPtr) &stg_ctoi_t21_info,
+ (StgPtr) &stg_ctoi_t22_info,
+ (StgPtr) &stg_ctoi_t23_info,
+ (StgPtr) &stg_ctoi_t24_info,
+ (StgPtr) &stg_ctoi_t25_info,
+ (StgPtr) &stg_ctoi_t26_info,
+ (StgPtr) &stg_ctoi_t27_info,
+ (StgPtr) &stg_ctoi_t28_info,
+ (StgPtr) &stg_ctoi_t29_info,
+ (StgPtr) &stg_ctoi_t30_info,
+ (StgPtr) &stg_ctoi_t31_info,
+ (StgPtr) &stg_ctoi_t32_info,
+ (StgPtr) &stg_ctoi_t33_info,
+ (StgPtr) &stg_ctoi_t34_info,
+ (StgPtr) &stg_ctoi_t35_info,
+ (StgPtr) &stg_ctoi_t36_info,
+ (StgPtr) &stg_ctoi_t37_info,
+ (StgPtr) &stg_ctoi_t38_info,
+ (StgPtr) &stg_ctoi_t39_info,
+ (StgPtr) &stg_ctoi_t40_info,
+ (StgPtr) &stg_ctoi_t41_info,
+ (StgPtr) &stg_ctoi_t42_info,
+ (StgPtr) &stg_ctoi_t43_info,
+ (StgPtr) &stg_ctoi_t44_info,
+ (StgPtr) &stg_ctoi_t45_info,
+ (StgPtr) &stg_ctoi_t46_info,
+ (StgPtr) &stg_ctoi_t47_info,
+ (StgPtr) &stg_ctoi_t48_info,
+ (StgPtr) &stg_ctoi_t49_info,
+ (StgPtr) &stg_ctoi_t50_info,
+ (StgPtr) &stg_ctoi_t51_info,
+ (StgPtr) &stg_ctoi_t52_info,
+ (StgPtr) &stg_ctoi_t53_info,
+ (StgPtr) &stg_ctoi_t54_info,
+ (StgPtr) &stg_ctoi_t55_info,
+ (StgPtr) &stg_ctoi_t56_info,
+ (StgPtr) &stg_ctoi_t57_info,
+ (StgPtr) &stg_ctoi_t58_info,
+ (StgPtr) &stg_ctoi_t59_info,
+ (StgPtr) &stg_ctoi_t60_info,
+ (StgPtr) &stg_ctoi_t61_info,
+ (StgPtr) &stg_ctoi_t62_info,
+};
+
#if defined(PROFILING)
//
@@ -1828,82 +1894,11 @@ run_BCO:
SpW(-1) = BCO_PTR(o_tuple_bco);
SpW(-2) = tuple_info;
SpW(-3) = BCO_PTR(o_bco);
- W_ ctoi_t_offset;
int tuple_stack_words = (tuple_info >> 24) & 0xff;
- switch(tuple_stack_words) {
- case 0: ctoi_t_offset = (W_)&stg_ctoi_t0_info; break;
- case 1: ctoi_t_offset = (W_)&stg_ctoi_t1_info; break;
- case 2: ctoi_t_offset = (W_)&stg_ctoi_t2_info; break;
- case 3: ctoi_t_offset = (W_)&stg_ctoi_t3_info; break;
- case 4: ctoi_t_offset = (W_)&stg_ctoi_t4_info; break;
- case 5: ctoi_t_offset = (W_)&stg_ctoi_t5_info; break;
- case 6: ctoi_t_offset = (W_)&stg_ctoi_t6_info; break;
- case 7: ctoi_t_offset = (W_)&stg_ctoi_t7_info; break;
- case 8: ctoi_t_offset = (W_)&stg_ctoi_t8_info; break;
- case 9: ctoi_t_offset = (W_)&stg_ctoi_t9_info; break;
-
- case 10: ctoi_t_offset = (W_)&stg_ctoi_t10_info; break;
- case 11: ctoi_t_offset = (W_)&stg_ctoi_t11_info; break;
- case 12: ctoi_t_offset = (W_)&stg_ctoi_t12_info; break;
- case 13: ctoi_t_offset = (W_)&stg_ctoi_t13_info; break;
- case 14: ctoi_t_offset = (W_)&stg_ctoi_t14_info; break;
- case 15: ctoi_t_offset = (W_)&stg_ctoi_t15_info; break;
- case 16: ctoi_t_offset = (W_)&stg_ctoi_t16_info; break;
- case 17: ctoi_t_offset = (W_)&stg_ctoi_t17_info; break;
- case 18: ctoi_t_offset = (W_)&stg_ctoi_t18_info; break;
- case 19: ctoi_t_offset = (W_)&stg_ctoi_t19_info; break;
-
- case 20: ctoi_t_offset = (W_)&stg_ctoi_t20_info; break;
- case 21: ctoi_t_offset = (W_)&stg_ctoi_t21_info; break;
- case 22: ctoi_t_offset = (W_)&stg_ctoi_t22_info; break;
- case 23: ctoi_t_offset = (W_)&stg_ctoi_t23_info; break;
- case 24: ctoi_t_offset = (W_)&stg_ctoi_t24_info; break;
- case 25: ctoi_t_offset = (W_)&stg_ctoi_t25_info; break;
- case 26: ctoi_t_offset = (W_)&stg_ctoi_t26_info; break;
- case 27: ctoi_t_offset = (W_)&stg_ctoi_t27_info; break;
- case 28: ctoi_t_offset = (W_)&stg_ctoi_t28_info; break;
- case 29: ctoi_t_offset = (W_)&stg_ctoi_t29_info; break;
-
- case 30: ctoi_t_offset = (W_)&stg_ctoi_t30_info; break;
- case 31: ctoi_t_offset = (W_)&stg_ctoi_t31_info; break;
- case 32: ctoi_t_offset = (W_)&stg_ctoi_t32_info; break;
- case 33: ctoi_t_offset = (W_)&stg_ctoi_t33_info; break;
- case 34: ctoi_t_offset = (W_)&stg_ctoi_t34_info; break;
- case 35: ctoi_t_offset = (W_)&stg_ctoi_t35_info; break;
- case 36: ctoi_t_offset = (W_)&stg_ctoi_t36_info; break;
- case 37: ctoi_t_offset = (W_)&stg_ctoi_t37_info; break;
- case 38: ctoi_t_offset = (W_)&stg_ctoi_t38_info; break;
- case 39: ctoi_t_offset = (W_)&stg_ctoi_t39_info; break;
-
- case 40: ctoi_t_offset = (W_)&stg_ctoi_t40_info; break;
- case 41: ctoi_t_offset = (W_)&stg_ctoi_t41_info; break;
- case 42: ctoi_t_offset = (W_)&stg_ctoi_t42_info; break;
- case 43: ctoi_t_offset = (W_)&stg_ctoi_t43_info; break;
- case 44: ctoi_t_offset = (W_)&stg_ctoi_t44_info; break;
- case 45: ctoi_t_offset = (W_)&stg_ctoi_t45_info; break;
- case 46: ctoi_t_offset = (W_)&stg_ctoi_t46_info; break;
- case 47: ctoi_t_offset = (W_)&stg_ctoi_t47_info; break;
- case 48: ctoi_t_offset = (W_)&stg_ctoi_t48_info; break;
- case 49: ctoi_t_offset = (W_)&stg_ctoi_t49_info; break;
-
- case 50: ctoi_t_offset = (W_)&stg_ctoi_t50_info; break;
- case 51: ctoi_t_offset = (W_)&stg_ctoi_t51_info; break;
- case 52: ctoi_t_offset = (W_)&stg_ctoi_t52_info; break;
- case 53: ctoi_t_offset = (W_)&stg_ctoi_t53_info; break;
- case 54: ctoi_t_offset = (W_)&stg_ctoi_t54_info; break;
- case 55: ctoi_t_offset = (W_)&stg_ctoi_t55_info; break;
- case 56: ctoi_t_offset = (W_)&stg_ctoi_t56_info; break;
- case 57: ctoi_t_offset = (W_)&stg_ctoi_t57_info; break;
- case 58: ctoi_t_offset = (W_)&stg_ctoi_t58_info; break;
- case 59: ctoi_t_offset = (W_)&stg_ctoi_t59_info; break;
-
- case 60: ctoi_t_offset = (W_)&stg_ctoi_t60_info; break;
- case 61: ctoi_t_offset = (W_)&stg_ctoi_t61_info; break;
- case 62: ctoi_t_offset = (W_)&stg_ctoi_t62_info; break;
-
- default: barf("unsupported tuple size %d", tuple_stack_words);
+ if (tuple_stack_words > 62) {
+ barf("unsupported tuple size %d", tuple_stack_words);
}
-
+ W_ ctoi_t_offset = (W_) ctoi_tuple_infos[tuple_stack_words];
SpW(-4) = ctoi_t_offset;
Sp_subW(4);
goto nextInsn;
=====================================
testsuite/tests/driver/json.stderr
=====================================
@@ -1 +1 @@
-{"version":"1.1","ghcVersion":"ghc-9.13.20250529","span":{"file":"json.hs","start":{"line":9,"column":11},"end":{"line":9,"column":21}},"severity":"Error","code":48010,"message":["Empty list of alternatives in case expression"],"hints":["Perhaps you intended to use the \u2018EmptyCase\u2019 extension"]}
+{"version":"1.2","ghcVersion":"ghc-9.13.20250627","span":{"file":"json.hs","start":{"line":9,"column":11},"end":{"line":9,"column":21}},"severity":"Error","code":48010,"rendered":"json.hs:9:11: error: [GHC-48010]\n Empty list of alternatives in case expression\n Suggested fix:\n Perhaps you intended to use the \u2018EmptyCase\u2019 extension\n","message":["Empty list of alternatives in case expression"],"hints":["Perhaps you intended to use the \u2018EmptyCase\u2019 extension"]}
=====================================
testsuite/tests/driver/json_warn.stderr
=====================================
@@ -1,2 +1,2 @@
-{"version":"1.1","ghcVersion":"ghc-9.13.20250529","span":{"file":"json_warn.hs","start":{"line":4,"column":3},"end":{"line":4,"column":4}},"severity":"Warning","code":40910,"message":["Defined but not used: \u2018x\u2019"],"hints":[],"reason":{"flags":["unused-matches"]}}
-{"version":"1.1","ghcVersion":"ghc-9.13.20250529","span":{"file":"json_warn.hs","start":{"line":7,"column":5},"end":{"line":7,"column":9}},"severity":"Warning","code":63394,"message":["In the use of \u2018head\u2019\n(imported from Prelude, but defined in GHC.Internal.List):\n\"This is a partial function, it throws an error on empty lists. Use pattern matching, 'Data.List.uncons' or 'Data.Maybe.listToMaybe' instead. Consider refactoring to use \"Data.List.NonEmpty\".\""],"hints":[],"reason":{"category":"x-partial"}}
+{"version":"1.2","ghcVersion":"ghc-9.13.20250627","span":{"file":"json_warn.hs","start":{"line":4,"column":3},"end":{"line":4,"column":4}},"severity":"Warning","code":40910,"rendered":"json_warn.hs:4:3: warning: [GHC-40910] [-Wunused-matches (in -Wextra)]\n Defined but not used: \u2018x\u2019\n","message":["Defined but not used: \u2018x\u2019"],"hints":[],"reason":{"flags":["unused-matches"]}}
+{"version":"1.2","ghcVersion":"ghc-9.13.20250627","span":{"file":"json_warn.hs","start":{"line":7,"column":5},"end":{"line":7,"column":9}},"severity":"Warning","code":63394,"rendered":"json_warn.hs:7:5: warning: [GHC-63394] [-Wx-partial (in -Wextended-warnings)]\n In the use of \u2018head\u2019\n (imported from Prelude, but defined in GHC.Internal.List):\n \"This is a partial function, it throws an error on empty lists. Use pattern matching, 'Data.List.uncons' or 'Data.Maybe.listToMaybe' instead. Consider refactoring to use \"Data.List.NonEmpty\".\"\n","message":["In the use of \u2018head\u2019\n(imported from Prelude, but defined in GHC.Internal.List):\n\"This is a partial function, it throws an error on empty lists. Use pattern matching, 'Data.List.uncons' or 'Data.Maybe.listToMaybe' instead. Consider refactoring to use \"Data.List.NonEmpty\".\""],"hints":[],"reason":{"category":"x-partial"}}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46d49146f1c449641db3bb346e58d1…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46d49146f1c449641db3bb346e58d1…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/amg/castz] 2 commits: Accept output change for ghci024
by Adam Gundry (@adamgundry) 23 Jul '25
by Adam Gundry (@adamgundry) 23 Jul '25
23 Jul '25
Adam Gundry pushed to branch wip/amg/castz at Glasgow Haskell Compiler / GHC
Commits:
e7c9343f by Adam Gundry at 2025-07-23T20:53:56+01:00
Accept output change for ghci024
- - - - -
79d86db2 by Adam Gundry at 2025-07-23T20:53:56+01:00
Attempt to move cast zapping to the zonker
- - - - -
6 changed files:
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Zonk/Type.hs
- testsuite/tests/ghci/scripts/ghci024.stdout
Changes:
=====================================
compiler/GHC/HsToCore/Binds.hs
=====================================
@@ -1783,6 +1783,7 @@ dsEvBind (EvBind { eb_lhs = v, eb_rhs = r, eb_info = info }) = do
dsEvTerm :: EvTerm -> DsM CoreExpr
dsEvTerm (EvExpr e) = return e
+dsEvTerm (EvCastExpr e co _) = return (Cast e co)
dsEvTerm (EvTypeable ty ev) = dsEvTypeable ty ev
dsEvTerm (EvFun { et_tvs = tvs, et_given = given
, et_binds = ev_binds, et_body = wanted_id })
=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -30,6 +30,7 @@ import GHC.Types.Avail ( Avails )
import GHC.Data.Bag ( Bag, bagToList )
import GHC.Types.Basic
import GHC.Data.BooleanFormula
+import GHC.Core ( Expr(Cast) )
import GHC.Core.Class ( className, classSCSelIds )
import GHC.Core.ConLike ( conLikeName )
import GHC.Core.FVs
@@ -674,6 +675,7 @@ instance ToHie (Context (Located (WithUserRdr Name))) where
evVarsOfTermList :: EvTerm -> [EvId]
evVarsOfTermList (EvExpr e) = exprSomeFreeVarsList isEvVar e
+evVarsOfTermList (EvCastExpr e co _ty) = exprSomeFreeVarsList isEvVar (Cast e co) -- TODO really
evVarsOfTermList (EvTypeable _ ev) =
case ev of
EvTypeableTyCon _ e -> concatMap evVarsOfTermList e
=====================================
compiler/GHC/Tc/Solver/Solve.hs
=====================================
@@ -36,8 +36,8 @@ import GHC.Core.Predicate
import GHC.Core.Reduction
import GHC.Core.Coercion
import GHC.Core.Class( classHasSCs )
-import GHC.Core.TyCo.FVs
-import GHC.Core.TyCo.Rep (Coercion(..))
+-- import GHC.Core.TyCo.FVs
+-- import GHC.Core.TyCo.Rep (Coercion(..))
import GHC.Types.Id( idType )
import GHC.Types.Var( EvVar, tyVarKind )
@@ -52,7 +52,7 @@ import GHC.Utils.Panic
import GHC.Utils.Misc
import GHC.Driver.Session
-import GHC.Driver.DynFlags ( hasZapCasts )
+-- import GHC.Driver.DynFlags ( hasZapCasts )
import Data.List( deleteFirstsBy )
@@ -1457,12 +1457,12 @@ finish_rewrite
(Reduction co new_pred)
rewriters
= assert (isEmptyRewriterSet rewriters) $ -- this is a Given, not a wanted
- do { zap_casts <- hasZapCasts <$> getDynFlags
+ do { -- zap_casts <- hasZapCasts <$> getDynFlags
; let loc = ctEvLoc ev
-- mkEvCast optimises ReflCo
ev_rw_role = ctEvRewriteRole ev
new_tm = assert (coercionRole co == ev_rw_role)
- evCastCo (evId old_evar) (mkCastCoercion zap_casts new_pred (downgradeRole Representational ev_rw_role co))
+ evCastCo (evId old_evar) (downgradeRole Representational ev_rw_role co) new_pred
; new_ev <- newGivenEvVar loc (new_pred, new_tm)
; continueWith $ CtGiven new_ev }
@@ -1470,14 +1470,14 @@ finish_rewrite
ev@(CtWanted (WantedCt { ctev_pred = old_pred, ctev_rewriters = rewriters, ctev_dest = dest }))
(Reduction co new_pred)
new_rewriters
- = do { zap_casts <- hasZapCasts <$> getDynFlags
+ = do { -- zap_casts <- hasZapCasts <$> getDynFlags
; let loc = ctEvLoc ev
rewriters' = rewriters S.<> new_rewriters
ev_rw_role = ctEvRewriteRole ev
; mb_new_ev <- newWanted loc rewriters' new_pred
; massert (coercionRole co == ev_rw_role)
; setWantedEvTerm dest EvCanonical $
- evCastCo (getEvExpr mb_new_ev) (mkCastCoercion zap_casts old_pred (downgradeRole Representational ev_rw_role (mkSymCo co)))
+ evCastCo (getEvExpr mb_new_ev) (downgradeRole Representational ev_rw_role (mkSymCo co)) old_pred
; case mb_new_ev of
Fresh new_ev -> continueWith $ CtWanted new_ev
Cached _ -> stopWith ev "Cached wanted" }
@@ -1492,10 +1492,10 @@ finish_rewrite
--
-- See Note [Zapped casts] in GHC.Core.TyCo.Rep.
--
-mkCastCoercion :: Bool -> Type -> Coercion -> CastCoercion
-mkCastCoercion zap_casts lhs_ty co
- | isSmallCo co || not zap_casts = CCoercion co
- | otherwise = ZCoercion lhs_ty (shallowCoVarsOfCo co)
+-- mkCastCoercion :: Bool -> Type -> Coercion -> CastCoercion
+-- mkCastCoercion zap_casts lhs_ty co
+-- | isSmallCo co || not zap_casts = CCoercion co
+-- | otherwise = ZCoercion lhs_ty (shallowCoVarsOfCo co)
-- | Is this coercion probably smaller than its type? This is a rough heuristic,
-- but crucially we treat axioms (perhaps wrapped in Sym/Sub/etc.) as small
@@ -1505,24 +1505,24 @@ mkCastCoercion zap_casts lhs_ty co
--
-- so we want to cast by `CCoercion (axF <Int>)` rather than `ZCoercion SomeVeryBigType []`.
--
-isSmallCo :: Coercion -> Bool
-isSmallCo Refl{} = True
-isSmallCo GRefl{} = True
-isSmallCo AxiomCo{} = True
-isSmallCo CoVarCo{} = True
-isSmallCo (SymCo co) = isSmallCo co
-isSmallCo (KindCo co) = isSmallCo co
-isSmallCo (SubCo co) = isSmallCo co
-isSmallCo TyConAppCo{} = False
-isSmallCo AppCo{} = False
-isSmallCo ForAllCo{} = False
-isSmallCo FunCo{} = False
-isSmallCo UnivCo{} = False
-isSmallCo TransCo{} = False
-isSmallCo SelCo{} = False
-isSmallCo LRCo{} = False
-isSmallCo InstCo{} = False
-isSmallCo HoleCo{} = False
+-- isSmallCo :: Coercion -> Bool
+-- isSmallCo Refl{} = True
+-- isSmallCo GRefl{} = True
+-- isSmallCo AxiomCo{} = True
+-- isSmallCo CoVarCo{} = True
+-- isSmallCo (SymCo co) = isSmallCo co
+-- isSmallCo (KindCo co) = isSmallCo co
+-- isSmallCo (SubCo co) = isSmallCo co
+-- isSmallCo TyConAppCo{} = False
+-- isSmallCo AppCo{} = False
+-- isSmallCo ForAllCo{} = False
+-- isSmallCo FunCo{} = False
+-- isSmallCo UnivCo{} = False
+-- isSmallCo TransCo{} = False
+-- isSmallCo SelCo{} = False
+-- isSmallCo LRCo{} = False
+-- isSmallCo InstCo{} = False
+-- isSmallCo HoleCo{} = False
{- *******************************************************************
=====================================
compiler/GHC/Tc/Types/Evidence.hs
=====================================
@@ -502,6 +502,8 @@ mkGivenEvBind ev tm = EvBind { eb_info = EvBindGiven, eb_lhs = ev, eb_rhs = tm }
data EvTerm
= EvExpr EvExpr
+ | EvCastExpr EvExpr TcCastCoercion TcType
+
| EvTypeable Type EvTypeable -- Dictionary for (Typeable ty)
| EvFun -- /\as \ds. let binds in v
@@ -530,10 +532,10 @@ evCoercion co = EvExpr (Coercion co)
-- | d |> co
evCast :: EvExpr -> TcCoercion -> EvTerm
evCast et tc | isReflCo tc = EvExpr et
- | otherwise = evCastCo et (CCoercion tc)
+ | otherwise = EvExpr (Cast et (CCoercion tc))
-evCastCo :: EvExpr -> TcCastCoercion -> EvTerm
-evCastCo et tc = EvExpr (Cast et tc)
+evCastCo :: EvExpr -> TcCoercion -> TcType -> EvTerm
+evCastCo et co co_res_ty = EvCastExpr et (CCoercion co) co_res_ty
-- Dictionary instance application
evDFunApp :: DFunId -> [Type] -> [EvExpr] -> EvTerm
@@ -889,6 +891,7 @@ findNeededEvVars ev_binds seeds
evVarsOfTerm :: EvTerm -> VarSet
evVarsOfTerm (EvExpr e) = exprSomeFreeVars isEvVar e
+evVarsOfTerm (EvCastExpr e co _ty) = exprSomeFreeVars isEvVar (Cast e co) -- TODO safe to ignore ty here?
evVarsOfTerm (EvTypeable _ ev) = evVarsOfTypeable ev
evVarsOfTerm (EvFun {}) = emptyVarSet -- See Note [Free vars of EvFun]
@@ -985,6 +988,7 @@ instance Outputable EvBind where
instance Outputable EvTerm where
ppr (EvExpr e) = ppr e
+ ppr (EvCastExpr e co ty) = text "EvCastExpr" <+> ppr e <+> ppr co <+> ppr ty
ppr (EvTypeable ty ev) = ppr ev <+> dcolon <+> text "Typeable" <+> ppr ty
ppr (EvFun { et_tvs = tvs, et_given = gs, et_binds = bs, et_body = w })
= hang (text "\\" <+> sep (map pprLamBndr (tvs ++ gs)) <+> arrow)
=====================================
compiler/GHC/Tc/Zonk/Type.hs
=====================================
@@ -59,6 +59,7 @@ import GHC.Tc.Zonk.TcType
( tcInitTidyEnv, tcInitOpenTidyEnv
, writeMetaTyVarRef
, checkCoercionHole
+ , unpackCoercionHole_maybe
, zonkCoVar )
import GHC.Core.Type
@@ -97,6 +98,9 @@ import Control.Monad
import Control.Monad.Trans.Class ( lift )
import Data.List.NonEmpty ( NonEmpty )
import Data.Foldable ( toList )
+import Data.Semigroup
+
+import GHC.Driver.DynFlags ( getDynFlags, hasZapCasts )
{- Note [What is zonking?]
~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -1762,9 +1766,49 @@ Wrinkles:
************************************************************************
-}
+zonkShallowCoVarsOfCo :: TcCoercion -> ZonkTcM CoVarSet
+zonkShallowCoVarsOfCo co
+ = unZCVSM $ go_co co
+ where
+ go_hole :: CoercionHole -> ZonkTcM CoVarSet
+ go_hole hole
+ = do { m_co <- lift $ liftZonkM $ unpackCoercionHole_maybe hole
+ ; case m_co of
+ Nothing -> return emptyVarSet -- Not filled (TODO emit log message?)
+ Just co -> unZCVSM (go_co co) } -- Filled: look inside
+
+ go_co :: Coercion -> ZonkCoVarSetMonoid
+ (_, _, go_co, _) = foldTyCo folder ()
+
+ folder :: TyCoFolder () ZonkCoVarSetMonoid
+ folder = TyCoFolder { tcf_view = noView
+ , tcf_tyvar = \ _ _ -> mempty
+ , tcf_covar = \ _ cv -> ZCVSM (pure (unitVarSet cv))
+ , tcf_hole = \ _ -> ZCVSM . go_hole
+ , tcf_tycobinder = \ _ _ _ -> () }
+
+newtype ZonkCoVarSetMonoid = ZCVSM { unZCVSM :: ZonkTcM CoVarSet }
+
+instance Semigroup ZonkCoVarSetMonoid where
+ ZCVSM l <> ZCVSM r = ZCVSM (unionVarSet <$> l <*> r)
+
+instance Monoid ZonkCoVarSetMonoid where
+ mempty = ZCVSM (return emptyVarSet)
+
+
+
zonkEvTerm :: EvTerm -> ZonkTcM EvTerm
zonkEvTerm (EvExpr e)
= EvExpr <$> zonkCoreExpr e
+zonkEvTerm (EvCastExpr e (CCoercion co) co_res_ty)
+ = do { zap_casts <- hasZapCasts <$> lift getDynFlags
+ ; co_res_ty' <- zonkTcTypeToTypeX co_res_ty
+ ; if zap_casts
+ then EvCastExpr <$> zonkCoreExpr e <*> (ZCoercion co_res_ty' <$> zonkShallowCoVarsOfCo co) <*> pure co_res_ty'
+ else EvExpr <$> zonkCoreExpr (Cast e (CCoercion co))
+ }
+zonkEvTerm ev@(EvCastExpr _ (ZCoercion{}) _)
+ = pprPanic "zonkEvTerm: ZCoercion" (ppr ev)
zonkEvTerm (EvTypeable ty ev)
= EvTypeable <$> zonkTcTypeToTypeX ty <*> zonkEvTypeable ev
zonkEvTerm (EvFun { et_tvs = tvs, et_given = evs
=====================================
testsuite/tests/ghci/scripts/ghci024.stdout
=====================================
@@ -15,6 +15,7 @@ other dynamic, non-language, flag settings:
-fshow-warning-groups
-fprefer-byte-code
-fbreak-points
+ -fno-zap-casts
warning settings:
-Wpattern-namespace-specifier
~~~~~~~~~~ Testing :set -a
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/32459579d089bd4a389a3c1b56ef6f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/32459579d089bd4a389a3c1b56ef6f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0