Zubin pushed to branch wip/9.10.3-backports at Glasgow Haskell Compiler / GHC

Commits:

26 changed files:

Changes:

  • compiler/GHC/Core/Predicate.hs
    ... ... @@ -27,7 +27,7 @@ module GHC.Core.Predicate (
    27 27
       -- Implicit parameters
    
    28 28
       isIPLikePred, mentionsIP, isIPTyCon, isIPClass,
    
    29 29
       isCallStackTy, isCallStackPred, isCallStackPredTy,
    
    30
    -  isExceptionContextPred,
    
    30
    +  isExceptionContextPred, isExceptionContextTy,
    
    31 31
       isIPPred_maybe,
    
    32 32
     
    
    33 33
       -- Evidence variables
    
    ... ... @@ -39,7 +39,6 @@ import GHC.Prelude
    39 39
     
    
    40 40
     import GHC.Core.Type
    
    41 41
     import GHC.Core.Class
    
    42
    -import GHC.Core.TyCo.Compare( eqType )
    
    43 42
     import GHC.Core.TyCon
    
    44 43
     import GHC.Core.TyCon.RecWalk
    
    45 44
     import GHC.Types.Var
    
    ... ... @@ -292,7 +291,7 @@ isExceptionContextPred cls tys
    292 291
       | otherwise
    
    293 292
       = Nothing
    
    294 293
     
    
    295
    --- | Is a type a 'CallStack'?
    
    294
    +-- | Is a type an 'ExceptionContext'?
    
    296 295
     isExceptionContextTy :: Type -> Bool
    
    297 296
     isExceptionContextTy ty
    
    298 297
       | Just tc <- tyConAppTyCon_maybe ty
    
    ... ... @@ -338,31 +337,38 @@ isCallStackTy ty
    338 337
     isIPLikePred :: Type -> Bool
    
    339 338
     -- Is `pred`, or any of its superclasses, an implicit parameter?
    
    340 339
     -- See Note [Local implicit parameters]
    
    341
    -isIPLikePred pred = mentions_ip_pred initIPRecTc Nothing pred
    
    342
    -
    
    343
    -mentionsIP :: Type -> Class -> [Type] -> Bool
    
    344
    --- Is (cls tys) an implicit parameter with key `str_ty`, or
    
    345
    --- is any of its superclasses such at thing.
    
    340
    +isIPLikePred pred =
    
    341
    +  mentions_ip_pred initIPRecTc (const True) (const True) pred
    
    342
    +
    
    343
    +mentionsIP :: (Type -> Bool) -- ^ predicate on the string
    
    344
    +           -> (Type -> Bool) -- ^ predicate on the type
    
    345
    +           -> Class
    
    346
    +           -> [Type] -> Bool
    
    347
    +-- ^ @'mentionsIP' str_cond ty_cond cls tys@ returns @True@ if:
    
    348
    +--
    
    349
    +--    - @cls tys@ is of the form @IP str ty@, where @str_cond str@ and @ty_cond ty@
    
    350
    +--      are both @True@,
    
    351
    +--    - or any superclass of @cls tys@ has this property.
    
    352
    +--
    
    346 353
     -- See Note [Local implicit parameters]
    
    347
    -mentionsIP str_ty cls tys = mentions_ip initIPRecTc (Just str_ty) cls tys
    
    348
    -
    
    349
    -mentions_ip :: RecTcChecker -> Maybe Type -> Class -> [Type] -> Bool
    
    350
    -mentions_ip rec_clss mb_str_ty cls tys
    
    351
    -  | Just (str_ty', _) <- isIPPred_maybe cls tys
    
    352
    -  = case mb_str_ty of
    
    353
    -       Nothing -> True
    
    354
    -       Just str_ty -> str_ty `eqType` str_ty'
    
    354
    +mentionsIP = mentions_ip initIPRecTc
    
    355
    +
    
    356
    +mentions_ip :: RecTcChecker -> (Type -> Bool) -> (Type -> Bool) -> Class -> [Type] -> Bool
    
    357
    +mentions_ip rec_clss str_cond ty_cond cls tys
    
    358
    +  | Just (str_ty, ty) <- isIPPred_maybe cls tys
    
    359
    +  = str_cond str_ty && ty_cond ty
    
    355 360
       | otherwise
    
    356
    -  = or [ mentions_ip_pred rec_clss mb_str_ty (classMethodInstTy sc_sel_id tys)
    
    361
    +  = or [ mentions_ip_pred rec_clss str_cond ty_cond (classMethodInstTy sc_sel_id tys)
    
    357 362
            | sc_sel_id <- classSCSelIds cls ]
    
    358 363
     
    
    359
    -mentions_ip_pred :: RecTcChecker -> Maybe Type -> Type -> Bool
    
    360
    -mentions_ip_pred  rec_clss mb_str_ty ty
    
    364
    +
    
    365
    +mentions_ip_pred :: RecTcChecker -> (Type -> Bool) -> (Type -> Bool) -> Type -> Bool
    
    366
    +mentions_ip_pred rec_clss str_cond ty_cond ty
    
    361 367
       | Just (cls, tys) <- getClassPredTys_maybe ty
    
    362 368
       , let tc = classTyCon cls
    
    363 369
       , Just rec_clss' <- if isTupleTyCon tc then Just rec_clss
    
    364 370
                           else checkRecTc rec_clss tc
    
    365
    -  = mentions_ip rec_clss' mb_str_ty cls tys
    
    371
    +  = mentions_ip rec_clss' str_cond ty_cond cls tys
    
    366 372
       | otherwise
    
    367 373
       = False -- Includes things like (D []) where D is
    
    368 374
               -- a Constraint-ranged family; #7785
    
    ... ... @@ -429,7 +435,38 @@ Small worries (Sept 20):
    429 435
     * The superclass hunt stops when it encounters the same class again,
    
    430 436
       but in principle we could have the same class, differently instantiated,
    
    431 437
       and the second time it could have an implicit parameter
    
    432
    -I'm going to treat these as problems for another day. They are all exotic.  -}
    
    438
    +I'm going to treat these as problems for another day. They are all exotic.
    
    439
    +
    
    440
    +Note [Using typesAreApart when calling mentionsIP]
    
    441
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    442
    +We call 'mentionsIP' in two situations:
    
    443
    +
    
    444
    +  (1) to check that a predicate does not contain any implicit parameters
    
    445
    +      IP str ty, for a fixed literal str and any type ty,
    
    446
    +  (2) to check that a predicate does not contain any HasCallStack or
    
    447
    +      HasExceptionContext constraints.
    
    448
    +
    
    449
    +In both of these cases, we want to be sure, so we should be conservative:
    
    450
    +
    
    451
    +  For (1), the predicate might contain an implicit parameter IP Str a, where
    
    452
    +  Str is a type family such as:
    
    453
    +
    
    454
    +    type family MyStr where MyStr = "abc"
    
    455
    +
    
    456
    +  To safeguard against this (niche) situation, instead of doing a simple
    
    457
    +  type equality check, we use 'typesAreApart'. This allows us to recognise
    
    458
    +  that 'IP MyStr a' contains an implicit parameter of the form 'IP "abc" ty'.
    
    459
    +
    
    460
    +  For (2), we similarly might have
    
    461
    +
    
    462
    +    type family MyCallStack where MyCallStack = CallStack
    
    463
    +
    
    464
    +  Again, here we use 'typesAreApart'. This allows us to see that
    
    465
    +
    
    466
    +    (?foo :: MyCallStack)
    
    467
    +
    
    468
    +  is indeed a CallStack constraint, hidden under a type family.
    
    469
    +-}
    
    433 470
     
    
    434 471
     {- *********************************************************************
    
    435 472
     *                                                                      *
    

  • compiler/GHC/Core/TyCon.hs
    ... ... @@ -2659,6 +2659,7 @@ tyConStupidTheta :: TyCon -> [PredType]
    2659 2659
     tyConStupidTheta tc@(TyCon { tyConDetails = details })
    
    2660 2660
       | AlgTyCon {algTcStupidTheta = stupid} <- details = stupid
    
    2661 2661
       | PrimTyCon {} <- details                         = []
    
    2662
    +  | PromotedDataCon {} <- details                   = []
    
    2662 2663
       | otherwise = pprPanic "tyConStupidTheta" (ppr tc)
    
    2663 2664
     
    
    2664 2665
     -- | Extract the 'TyVar's bound by a vanilla type synonym
    

  • compiler/GHC/Tc/Solver/Dict.hs
    ... ... @@ -32,7 +32,7 @@ import GHC.Core.InstEnv ( DFunInstType )
    32 32
     import GHC.Core.Class
    
    33 33
     import GHC.Core.Predicate
    
    34 34
     import GHC.Core.Multiplicity ( scaledThing )
    
    35
    -import GHC.Core.Unify ( ruleMatchTyKiX )
    
    35
    +import GHC.Core.Unify ( ruleMatchTyKiX , typesAreApart )
    
    36 36
     
    
    37 37
     import GHC.Types.Name
    
    38 38
     import GHC.Types.Name.Set
    
    ... ... @@ -105,21 +105,25 @@ updInertDicts :: DictCt -> TcS ()
    105 105
     updInertDicts dict_ct@(DictCt { di_cls = cls, di_ev = ev, di_tys = tys })
    
    106 106
       = do { traceTcS "Adding inert dict" (ppr dict_ct $$ ppr cls  <+> ppr tys)
    
    107 107
     
    
    108
    -       ; if |  isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys
    
    108
    +       ; if | isGiven ev, Just (str_ty, _) <- isIPPred_maybe cls tys
    
    109 109
                 -> -- See (SIP1) and (SIP2) in Note [Shadowing of implicit parameters]
    
    110 110
                    -- Update /both/ inert_cans /and/ inert_solved_dicts.
    
    111 111
                    updInertSet $ \ inerts@(IS { inert_cans = ics, inert_solved_dicts = solved }) ->
    
    112
    -               inerts { inert_cans         = updDicts (filterDicts (not_ip_for str_ty)) ics
    
    113
    -                      , inert_solved_dicts = filterDicts (not_ip_for str_ty) solved }
    
    114
    -            |  otherwise
    
    112
    +               inerts { inert_cans         = updDicts (filterDicts (does_not_mention_ip_for str_ty)) ics
    
    113
    +                      , inert_solved_dicts = filterDicts (does_not_mention_ip_for str_ty) solved }
    
    114
    +            | otherwise
    
    115 115
                 -> return ()
    
    116 116
     
    
    117 117
            -- Add the new constraint to the inert set
    
    118 118
            ; updInertCans (updDicts (addDict dict_ct)) }
    
    119 119
       where
    
    120
    -    not_ip_for :: Type -> DictCt -> Bool
    
    121
    -    not_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys })
    
    122
    -      = not (mentionsIP str_ty cls tys)
    
    120
    +    -- Does this class constraint or any of its superclasses mention
    
    121
    +    -- an implicit parameter (?str :: ty) for the given 'str' and any type 'ty'?
    
    122
    +    does_not_mention_ip_for :: Type -> DictCt -> Bool
    
    123
    +    does_not_mention_ip_for str_ty (DictCt { di_cls = cls, di_tys = tys })
    
    124
    +      = not $ mentionsIP (not . typesAreApart str_ty) (const True) cls tys
    
    125
    +        -- See Note [Using typesAreApart when calling mentionsIP]
    
    126
    +        -- in GHC.Core.Predicate
    
    123 127
     
    
    124 128
     canDictCt :: CtEvidence -> Class -> [Type] -> SolverStage DictCt
    
    125 129
     -- Once-only processing of Dict constraints:
    
    ... ... @@ -201,7 +205,7 @@ in two places:
    201 205
     * In `GHC.Tc.Solver.InertSet.solveOneFromTheOther`, be careful when we have
    
    202 206
        (?x :: ty) in the inert set and an identical (?x :: ty) as the work item.
    
    203 207
     
    
    204
    -* In `updInertDicts` in this module, when adding [G] (?x :: ty), remove  any
    
    208
    +* In `updInertDicts`, in this module, when adding [G] (?x :: ty), remove any
    
    205 209
       existing [G] (?x :: ty'), regardless of ty'.
    
    206 210
     
    
    207 211
     * Wrinkle (SIP1): we must be careful of superclasses.  Consider
    
    ... ... @@ -221,7 +225,7 @@ in two places:
    221 225
       An important special case is constraint tuples like [G] (% ?x::ty, Eq a %).
    
    222 226
       But it could happen for `class xx => D xx where ...` and the constraint D
    
    223 227
       (?x :: int).  This corner (constraint-kinded variables instantiated with
    
    224
    -  implicit parameter constraints) is not well explorered.
    
    228
    +  implicit parameter constraints) is not well explored.
    
    225 229
     
    
    226 230
       Example in #14218, and #23761
    
    227 231
     
    

  • compiler/GHC/Tc/Solver/Monad.hs
    ... ... @@ -158,7 +158,7 @@ import GHC.Tc.Types.Origin
    158 158
     import GHC.Tc.Types.Constraint
    
    159 159
     import GHC.Tc.Utils.Unify
    
    160 160
     
    
    161
    -import GHC.Builtin.Names ( unsatisfiableClassNameKey )
    
    161
    +import GHC.Builtin.Names ( unsatisfiableClassNameKey, callStackTyConName, exceptionContextTyConName )
    
    162 162
     
    
    163 163
     import GHC.Core.Type
    
    164 164
     import GHC.Core.TyCo.Rep as Rep
    
    ... ... @@ -168,6 +168,7 @@ import GHC.Core.Predicate
    168 168
     import GHC.Core.Reduction
    
    169 169
     import GHC.Core.Class
    
    170 170
     import GHC.Core.TyCon
    
    171
    +import GHC.Core.Unify (typesAreApart)
    
    171 172
     
    
    172 173
     import GHC.Types.Name
    
    173 174
     import GHC.Types.TyThing
    
    ... ... @@ -177,13 +178,13 @@ import GHC.Types.Var.Set
    177 178
     import GHC.Types.Unique.Supply
    
    178 179
     import GHC.Types.Unique.Set( elementOfUniqSet )
    
    179 180
     
    
    180
    -import GHC.Unit.Module ( HasModule, getModule, extractModule )
    
    181
    +import GHC.Unit.Module ( HasModule, getModule, extractModule, primUnit, moduleUnit, ghcInternalUnit, bignumUnit)
    
    181 182
     import qualified GHC.Rename.Env as TcM
    
    182 183
     
    
    183 184
     import GHC.Utils.Outputable
    
    184 185
     import GHC.Utils.Panic
    
    185 186
     import GHC.Utils.Logger
    
    186
    -import GHC.Utils.Misc (HasDebugCallStack)
    
    187
    +import GHC.Utils.Misc (HasDebugCallStack, (<||>))
    
    187 188
     
    
    188 189
     import GHC.Data.Bag as Bag
    
    189 190
     import GHC.Data.Pair
    
    ... ... @@ -478,14 +479,92 @@ getSafeOverlapFailures
    478 479
     updSolvedDicts :: InstanceWhat -> DictCt -> TcS ()
    
    479 480
     -- Conditionally add a new item in the solved set of the monad
    
    480 481
     -- See Note [Solved dictionaries] in GHC.Tc.Solver.InertSet
    
    481
    -updSolvedDicts what dict_ct@(DictCt { di_ev = ev })
    
    482
    +updSolvedDicts what dict_ct@(DictCt { di_cls = cls, di_tys = tys, di_ev = ev })
    
    482 483
       | isWanted ev
    
    483 484
       , instanceReturnsDictCon what
    
    484
    -  = do { traceTcS "updSolvedDicts:" $ ppr dict_ct
    
    485
    +  = do { is_callstack    <- is_tyConTy isCallStackTy        callStackTyConName
    
    486
    +       ; is_exceptionCtx <- is_tyConTy isExceptionContextTy exceptionContextTyConName
    
    487
    +       ; let contains_callstack_or_exceptionCtx =
    
    488
    +               mentionsIP
    
    489
    +                 (const True)
    
    490
    +                    -- NB: the name of the call-stack IP is irrelevant
    
    491
    +                    -- e.g (?foo :: CallStack) counts!
    
    492
    +                 (is_callstack <||> is_exceptionCtx)
    
    493
    +                 cls tys
    
    494
    +       -- See Note [Don't add HasCallStack constraints to the solved set]
    
    495
    +       ; unless contains_callstack_or_exceptionCtx $
    
    496
    +    do { traceTcS "updSolvedDicts:" $ ppr dict_ct
    
    485 497
            ; updInertSet $ \ ics ->
    
    486
    -         ics { inert_solved_dicts = addSolvedDict dict_ct (inert_solved_dicts ics) } }
    
    498
    +           ics { inert_solved_dicts = addSolvedDict dict_ct (inert_solved_dicts ics) }
    
    499
    +       } }
    
    487 500
       | otherwise
    
    488 501
       = return ()
    
    502
    +  where
    
    503
    +
    
    504
    +    -- Return a predicate that decides whether a type is CallStack
    
    505
    +    -- or ExceptionContext, accounting for e.g. type family reduction, as
    
    506
    +    -- per Note [Using typesAreApart when calling mentionsIP].
    
    507
    +    --
    
    508
    +    -- See Note [Using isCallStackTy in mentionsIP].
    
    509
    +    is_tyConTy :: (Type -> Bool) -> Name -> TcS (Type -> Bool)
    
    510
    +    is_tyConTy is_eq tc_name
    
    511
    +      = do {  mb_tc <- wrapTcS $ do
    
    512
    +                mod <- tcg_mod <$> TcM.getGblEnv
    
    513
    +                if moduleUnit mod `elem` [primUnit, ghcInternalUnit, bignumUnit]
    
    514
    +                then return Nothing
    
    515
    +                else Just <$> TcM.tcLookupTyCon tc_name
    
    516
    +           ; case mb_tc of
    
    517
    +              Just tc ->
    
    518
    +                return $ \ ty -> not (typesAreApart ty (mkTyConTy tc))
    
    519
    +              Nothing ->
    
    520
    +                return is_eq
    
    521
    +           }
    
    522
    +
    
    523
    +{- Note [Don't add HasCallStack constraints to the solved set]
    
    524
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    525
    +We must not add solved Wanted dictionaries that mention HasCallStack constraints
    
    526
    +to the solved set, or we might fail to accumulate the proper call stack, as was
    
    527
    +reported in #25529.
    
    528
    +
    
    529
    +Recall that HasCallStack constraints (and the related HasExceptionContext
    
    530
    +constraints) are implicit parameter constraints, and are accumulated as per
    
    531
    +Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence.
    
    532
    +
    
    533
    +When we solve a Wanted that contains a HasCallStack constraint, we don't want
    
    534
    +to cache the result, because re-using that solution means re-using the call-stack
    
    535
    +in a different context!
    
    536
    +
    
    537
    +See also Note [Shadowing of implicit parameters], which deals with a similar
    
    538
    +problem with Given implicit parameter constraints.
    
    539
    +
    
    540
    +Note [Using isCallStackTy in mentionsIP]
    
    541
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    542
    +To implement Note [Don't add HasCallStack constraints to the solved set],
    
    543
    +we need to check whether a constraint contains a HasCallStack or HasExceptionContext
    
    544
    +constraint. We do this using the 'mentionsIP' function, but as per
    
    545
    +Note [Using typesAreApart when calling mentionsIP] we don't want to simply do:
    
    546
    +
    
    547
    +  mentionsIP
    
    548
    +    (const True) -- (ignore the implicit parameter string)
    
    549
    +    (isCallStackTy <||> isExceptionContextTy)
    
    550
    +
    
    551
    +because this does not account for e.g. a type family that reduces to CallStack.
    
    552
    +The predicate we want to use instead is:
    
    553
    +
    
    554
    +    \ ty -> not (typesAreApart ty callStackTy && typesAreApart ty exceptionContextTy)
    
    555
    +
    
    556
    +However, this is made difficult by the fact that CallStack and ExceptionContext
    
    557
    +are not wired-in types; they are only known-key. This means we must look them
    
    558
    +up using 'tcLookupTyCon'. However, this might fail, e.g. if we are in the middle
    
    559
    +of typechecking ghc-internal and these data-types have not been typechecked yet!
    
    560
    +
    
    561
    +In that case, we simply fall back to the naive 'isCallStackTy'/'isExceptionContextTy'
    
    562
    +logic.
    
    563
    +
    
    564
    +Note that it would be somewhat painful to wire-in ExceptionContext: at the time
    
    565
    +of writing (March 2025), this would require wiring in the ExceptionAnnotation
    
    566
    +class, as well as SomeExceptionAnnotation, which is a data type with existentials.
    
    567
    +-}
    
    489 568
     
    
    490 569
     getSolvedDicts :: TcS (DictMap DictCt)
    
    491 570
     getSolvedDicts = do { ics <- getInertSet; return (inert_solved_dicts ics) }
    

  • compiler/GHC/Tc/Solver/Types.hs
    ... ... @@ -166,7 +166,7 @@ Suppose f :: HasCallStack => blah. Then
    166 166
         IP "callStack" CallStack
    
    167 167
       See Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence
    
    168 168
     
    
    169
    -* We cannonicalise such constraints, in GHC.Tc.Solver.Dict.canDictNC, by
    
    169
    +* We canonicalise such constraints, in GHC.Tc.Solver.Dict.canDictNC, by
    
    170 170
       pushing the call-site info on the stack, and changing the CtOrigin
    
    171 171
       to record that has been done.
    
    172 172
        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
    22 22
     AC_CONFIG_MACRO_DIRS([m4])
    
    23 23
     
    
    24 24
     # Set this to YES for a released version, otherwise NO
    
    25
    -: ${RELEASE=YES}
    
    25
    +: ${RELEASE=NO}
    
    26 26
     
    
    27 27
     # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line
    
    28 28
     # above.  If this is not a released version, then we will append the
    

  • docs/users_guide/9.10.3-notes.rst
    1
    +.. _release-9-10-3:
    
    2
    +
    
    3
    +Version 9.10.3
    
    4
    +===============
    
    5
    +The significant changes to the various parts of the compiler are listed in the
    
    6
    +following sections. See the `migration guide
    
    7
    +<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.10>`_ on the GHC Wiki
    
    8
    +for specific guidance on migrating programs to this release.
    
    9
    +
    
    10
    +
    
    11
    +Compiler
    
    12
    +~~~~~~~~
    
    13
    +
    
    14
    +- Don't cache solved [W] HasCallStack constraints to avoid re-using old
    
    15
    +  call-stacks instead of constructing new ones. (:ghc-ticket:`25529`)
    
    16
    +
    
    17
    +- Fix EmptyCase panic in tcMatches when \case{} is checked against a function
    
    18
    +  type preceded by invisible forall. (:ghc-ticket:`25960`)
    
    19
    +
    
    20
    +- Fix panic triggered by combination of \case{} and forall t ->. (:ghc-ticket:`25004`)
    
    21
    +
    
    22
    +- Fix GHC.SysTools.Ar archive member size writing logic that was emitting wrong
    
    23
    +  archive member sizes in headers. (:ghc-ticket:`26120`, :ghc-ticket:`22586`)
    
    24
    +
    
    25
    +- Fix multiple bugs in name resolution of subordinate import lists related to
    
    26
    +  type namespace specifiers and hiding clauses. (:ghc-ticket:`22581`, :ghc-ticket:`25983`, :ghc-ticket:`25984`, :ghc-ticket:`25991`)
    
    27
    +
    
    28
    +- Use mkTrAppChecked in ds_ev_typeable to avoid false negatives for type
    
    29
    +  equality involving function types. (:ghc-ticket:`25998`)
    
    30
    +
    
    31
    +- Fix bytecode generation for ``tagToEnum# <LITERAL>``. (:ghc-ticket:`25975`)
    
    32
    +
    
    33
    +- Don't report used duplicate record fields as unused. (:ghc-ticket:`24035`)
    
    34
    +
    
    35
    +- Propagate long distance info to guarded let binds for better pattern-match
    
    36
    +  checking warnings. (:ghc-ticket:`25749`)
    
    37
    +
    
    38
    +- Prevent incorrect unpacking optimizations for GADTs with multiple constructors. (:ghc-ticket:`25672`)
    
    39
    +
    
    40
    +- Introduce a separate argument limit for forced specs via SPEC argument with
    
    41
    +  warning when limit is exceeded. (:ghc-ticket:`25197`)
    
    42
    +
    
    43
    +Build system and packaging
    
    44
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    45
    +
    
    46
    +- 9.10 hadrian can build with Cabal-3.12.1. (:ghc-ticket:`25605`)
    
    47
    +
    
    48
    +- GHC settings: always unescape escaped spaces to fix handling of spaces in
    
    49
    +  executable paths. (:ghc-ticket:`25204`)
    
    50
    +
    
    51
    +Native code generator backend
    
    52
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    53
    +
    
    54
    +- x86 NCG: Fix code generation of bswap64 on i386. (:ghc-ticket:`25601`)
    
    55
    +
    
    56
    +- AArch64 NCG: Fix sub-word arithmetic right shift by zero-extending sub-word
    
    57
    +  values. (:ghc-ticket:`26061`)
    
    58
    +
    
    59
    +- NCG: AArch64 - Add -finter-module-far-jumps flag for modules with far jumps
    
    60
    +  outside the current module. (:ghc-ticket:`24648`)
    
    61
    +
    
    62
    +LLVM backend
    
    63
    +~~~~~~~~~~~~
    
    64
    +
    
    65
    +- LLVM: fix typo in padLiveArgs that was incorrectly computing too many padding
    
    66
    +  registers causing segfaults. (:ghc-ticket:`25770`, :ghc-ticket:`25773`)
    
    67
    +
    
    68
    +- llvmGen: Fix linkage of built-in arrays to use Appending linkage instead of
    
    69
    +  Internal. (:ghc-ticket:`25769`)
    
    70
    +
    
    71
    +- llvmGen: Fix built-in variable predicate to check for `@llvm` rather than
    
    72
    +  `$llvm`.
    
    73
    +
    
    74
    +WebAssembly backend
    
    75
    +~~~~~~~~~~~~~~~~~~~
    
    76
    +
    
    77
    +- wasm: use primitive opcodes for fabs and sqrt operations.
    
    78
    +
    
    79
    +Runtime system
    
    80
    +~~~~~~~~~~~~~~
    
    81
    +
    
    82
    +- rts: Implement WEAK EXTERNAL undef redirection by target symbol name.
    
    83
    +
    
    84
    +- rts: Handle API set symbol versioning conflicts.
    
    85
    +
    
    86
    +- rts: fix rts_clearMemory logic when sanity checks are enabled. (:ghc-ticket:`26011`)
    
    87
    +
    
    88
    +- rts/linker: Improve efficiency of proddable blocks structure by using binary
    
    89
    +  search instead of linked lists for better performance with split sections. (:ghc-ticket:`26009`)
    
    90
    +
    
    91
    +- rts/linker/PEi386: Don't repeatedly load DLLs by maintaining a hash-set of
    
    92
    +  loaded DLL names. (:ghc-ticket:`26009`, :ghc-ticket:`26052`)
    
    93
    +
    
    94
    +- rts/linker: Don't fail due to RTLD_NOW by attempting eager binding first,
    
    95
    +  then reverting to lazy binding on failure. (:ghc-ticket:`25943`)
    
    96
    +
    
    97
    +``base`` library
    
    98
    +~~~~~~~~~~~~~~~~
    
    99
    +
    
    100
    +- base: Expose Backtraces constructor and fields. (:ghc-ticket:`26049`)
    
    101
    +
    
    102
    +- base: Note strictness changes made in 4.16.0.0. (:ghc-ticket:`25886`)
    
    103
    +
    
    104
    +- Fix bugs in ``integerRecipMod`` and ``integerPowMod`` return values. (:ghc-ticket:`26017`)
    
    105
    +
    
    106
    +``ghc`` library
    
    107
    +~~~~~~~~~~~~~~~
    
    108
    +
    
    109
    +- perf: Replace uses of genericLength with strictGenericLength to reduce time
    
    110
    +  spent in 'assembleBCOs' and allocations. (:ghc-ticket:`25706`)
    
    111
    +
    
    112
    +Build tools
    
    113
    +~~~~~~~~~~~
    
    114
    +
    
    115
    +- configure: Drop probing of ld.gold since `gold` has been dropped from
    
    116
    +  binutils-2.44. (:ghc-ticket:`25716`)
    
    117
    +
    
    118
    +- get-win32-tarballs.py: List tarball files to be downloaded if we cannot find
    
    119
    +  them. (:ghc-ticket:`25929`)
    
    120
    +
    
    121
    +- hp2ps Utilities.c: include stdlib.h instead of extern malloc and realloc.
    
    122
    +
    
    123
    +Included libraries
    
    124
    +~~~~~~~~~~~~~~~~~~
    
    125
    +
    
    126
    +The package database provided with this distribution also contains a number of
    
    127
    +packages other than GHC itself. See the changelogs provided with these packages
    
    128
    +for further change information.
    
    129
    +
    
    130
    +.. ghc-package-list::
    
    131
    +
    
    132
    +    libraries/array/array.cabal:             Dependency of ``ghc`` library
    
    133
    +    libraries/base/base.cabal:               Core library
    
    134
    +    libraries/binary/binary.cabal:           Dependency of ``ghc`` library
    
    135
    +    libraries/bytestring/bytestring.cabal:   Dependency of ``ghc`` library
    
    136
    +    libraries/Cabal/Cabal/Cabal.cabal:       Dependency of ``ghc-pkg`` utility
    
    137
    +    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:  Dependency of ``ghc-pkg`` utility
    
    138
    +    libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
    
    139
    +    libraries/deepseq/deepseq.cabal:         Dependency of ``ghc`` library
    
    140
    +    libraries/directory/directory.cabal:     Dependency of ``ghc`` library
    
    141
    +    libraries/exceptions/exceptions.cabal:   Dependency of ``ghc`` and ``haskeline`` library
    
    142
    +    libraries/filepath/filepath.cabal:       Dependency of ``ghc`` library
    
    143
    +    compiler/ghc.cabal:                      The compiler itself
    
    144
    +    libraries/ghci/ghci.cabal:               The REPL interface
    
    145
    +    libraries/ghc-boot/ghc-boot.cabal:       Internal compiler library
    
    146
    +    libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
    
    147
    +    libraries/ghc-compact/ghc-compact.cabal: Core library
    
    148
    +    libraries/ghc-heap/ghc-heap.cabal:       GHC heap-walking library
    
    149
    +    libraries/ghc-prim/ghc-prim.cabal:       Core library
    
    150
    +    libraries/haskeline/haskeline.cabal:     Dependency of ``ghci`` executable
    
    151
    +    libraries/hpc/hpc.cabal:                 Dependency of ``hpc`` executable
    
    152
    +    libraries/integer-gmp/integer-gmp.cabal: Core library
    
    153
    +    libraries/mtl/mtl.cabal:                 Dependency of ``Cabal`` library
    
    154
    +    libraries/parsec/parsec.cabal:           Dependency of ``Cabal`` library
    
    155
    +    libraries/pretty/pretty.cabal:           Dependency of ``ghc`` library
    
    156
    +    libraries/process/process.cabal:         Dependency of ``ghc`` library
    
    157
    +    libraries/stm/stm.cabal:                 Dependency of ``haskeline`` library
    
    158
    +    libraries/template-haskell/template-haskell.cabal: Core library
    
    159
    +    libraries/terminfo/terminfo.cabal:       Dependency of ``haskeline`` library
    
    160
    +    libraries/text/text.cabal:               Dependency of ``Cabal`` library
    
    161
    +    libraries/time/time.cabal:               Dependency of ``ghc`` library
    
    162
    +    libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
    
    163
    +    libraries/unix/unix.cabal:               Dependency of ``ghc`` library
    
    164
    +    libraries/Win32/Win32.cabal:             Dependency of ``ghc`` library
    
    165
    +    libraries/xhtml/xhtml.cabal:             Dependency of ``haddock`` executable
    \ No newline at end of file

  • hadrian/hadrian.cabal
    ... ... @@ -152,7 +152,7 @@ executable hadrian
    152 152
                            , TypeOperators
    
    153 153
         other-extensions:    MultiParamTypeClasses
    
    154 154
                            , TypeFamilies
    
    155
    -    build-depends:       Cabal                >= 3.10    && < 3.11
    
    155
    +    build-depends:       Cabal    (>= 3.10 && < 3.11) || (>= 3.12.1 && < 3.13)
    
    156 156
                            , base                 >= 4.11    && < 5
    
    157 157
                            , bytestring           >= 0.10    && < 0.13
    
    158 158
                            , containers           >= 0.5     && < 0.8
    

  • hadrian/src/Context.hs
    ... ... @@ -9,7 +9,7 @@ module Context (
    9 9
         contextDir, buildPath, buildDir, pkgInplaceConfig, pkgSetupConfigFile, pkgSetupConfigDir,
    
    10 10
         pkgHaddockFile, pkgRegisteredLibraryFile, pkgRegisteredLibraryFileName,
    
    11 11
         pkgLibraryFile, pkgGhciLibraryFile,
    
    12
    -    pkgConfFile, pkgStampFile, resourcePath, objectPath, contextPath, getContextPath, libPath, distDir,
    
    12
    +    pkgConfFile, pkgStampFile, resourcePath, objectPath, contextPath, getContextPath, libPath, distDir, distDynDir,
    
    13 13
         haddockStatsFilesDir
    
    14 14
         ) where
    
    15 15
     
    
    ... ... @@ -20,7 +20,8 @@ import Hadrian.Expression
    20 20
     import Hadrian.Haskell.Cabal
    
    21 21
     import Oracles.Setting
    
    22 22
     import GHC.Toolchain.Target (Target(..))
    
    23
    -import GHC.Platform.ArchOS
    
    23
    +import Hadrian.Oracles.Cabal
    
    24
    +import Hadrian.Haskell.Cabal.Type
    
    24 25
     
    
    25 26
     -- | Most targets are built only one way, hence the notion of 'vanillaContext'.
    
    26 27
     vanillaContext :: Stage -> Package -> Context
    
    ... ... @@ -62,12 +63,15 @@ libPath Context {..} = buildRoot <&> (-/- (stageString stage -/- "lib"))
    62 63
     --
    
    63 64
     -- We preform some renaming to accommodate Cabal's slightly different naming
    
    64 65
     -- conventions (see 'cabalOsString' and 'cabalArchString').
    
    65
    -distDir :: Stage -> Action FilePath
    
    66
    -distDir st = do
    
    67
    -    version        <- ghcVersionStage st
    
    68
    -    targetOs       <- cabalOsString   . stringEncodeOS   . archOS_OS   . tgtArchOs <$> targetStage st
    
    69
    -    targetArch     <- cabalArchString . stringEncodeArch . archOS_arch . tgtArchOs <$> targetStage st
    
    70
    -    return $ targetArch ++ "-" ++ targetOs ++ "-ghc-" ++ version
    
    66
    +distDir :: Context -> Action FilePath
    
    67
    +distDir c = do
    
    68
    +    cd <- readContextData c
    
    69
    +    return (contextLibdir cd)
    
    70
    +
    
    71
    +distDynDir :: Context -> Action FilePath
    
    72
    +distDynDir c = do
    
    73
    +    cd <- readContextData c
    
    74
    +    return (contextDynLibdir cd)
    
    71 75
     
    
    72 76
     pkgFileName :: Context -> Package -> String -> String -> Action FilePath
    
    73 77
     pkgFileName context package prefix suffix = do
    
    ... ... @@ -104,13 +108,12 @@ pkgHaddockFile Context {..} = do
    104 108
     -- @_build/stage1/lib/x86_64-linux-ghc-8.9.0/array-0.5.1.0/libHSarray-0.5.4.0.a@
    
    105 109
     pkgRegisteredLibraryFile :: Context -> Action FilePath
    
    106 110
     pkgRegisteredLibraryFile context@Context {..} = do
    
    107
    -    libDir    <- libPath context
    
    108
    -    pkgId     <- pkgUnitId stage package
    
    109 111
         fileName  <- pkgRegisteredLibraryFileName context
    
    110
    -    distDir   <- distDir stage
    
    112
    +    distDir   <- distDir context
    
    113
    +    distDynDir  <- distDynDir context
    
    111 114
         return $ if Dynamic `wayUnit` way
    
    112
    -        then libDir -/- distDir -/- fileName
    
    113
    -        else libDir -/- distDir -/- pkgId -/- fileName
    
    115
    +        then distDynDir -/- fileName
    
    116
    +        else distDir -/- fileName
    
    114 117
     
    
    115 118
     -- | Just the final filename portion of pkgRegisteredLibraryFile
    
    116 119
     pkgRegisteredLibraryFileName :: Context -> Action FilePath
    

  • hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
    ... ... @@ -254,6 +254,7 @@ resolveContextData context@Context {..} = do
    254 254
         pdi <- liftIO $ getHookedBuildInfo [pkgPath package, cPath -/- "build"]
    
    255 255
         let pd'  = C.updatePackageDescription pdi (C.localPkgDescr lbi)
    
    256 256
             lbi' = lbi { C.localPkgDescr = pd' }
    
    257
    +    pkgDbPath <- packageDbPath (PackageDbLoc stage iplace)
    
    257 258
     
    
    258 259
         -- TODO: Get rid of deprecated 'externalPackageDeps' and drop -Wno-deprecations
    
    259 260
         -- See: https://github.com/snowleopard/hadrian/issues/548
    
    ... ... @@ -302,6 +303,8 @@ resolveContextData context@Context {..} = do
    302 303
               | takeExtension fp `elem` [".cpp", ".cxx", ".c++"]= CppMain
    
    303 304
               | otherwise = CMain
    
    304 305
     
    
    306
    +        install_dirs = absoluteInstallDirs pd' lbi' (CopyToDb pkgDbPath)
    
    307
    +
    
    305 308
             main_src = fmap (first C.display) mainIs
    
    306 309
             cdata = ContextData
    
    307 310
               { dependencies    = deps
    
    ... ... @@ -343,7 +346,10 @@ resolveContextData context@Context {..} = do
    343 346
               , depLdOpts          = forDeps Installed.ldOptions
    
    344 347
               , buildGhciLib       = C.withGHCiLib lbi'
    
    345 348
               , frameworks         = C.frameworks buildInfo
    
    346
    -          , packageDescription = pd' }
    
    349
    +          , packageDescription = pd'
    
    350
    +          , contextLibdir      = libdir install_dirs
    
    351
    +          , contextDynLibdir   = dynlibdir install_dirs
    
    352
    +          }
    
    347 353
     
    
    348 354
           in return cdata
    
    349 355
     
    

  • hadrian/src/Hadrian/Haskell/Cabal/Type.hs
    ... ... @@ -70,6 +70,10 @@ data ContextData = ContextData
    70 70
         , buildGhciLib       :: Bool
    
    71 71
         , frameworks         :: [String]
    
    72 72
         , packageDescription :: PackageDescription
    
    73
    +    -- The location where normal library files go
    
    74
    +    , contextLibdir    :: FilePath
    
    75
    +    -- The location where dynamic libraries go
    
    76
    +    , contextDynLibdir :: FilePath
    
    73 77
         } deriving (Eq, Generic, Show, Typeable)
    
    74 78
     
    
    75 79
     instance Binary   PackageData
    

  • hadrian/src/Rules/BinaryDist.hs
    1 1
     {-# LANGUAGE TupleSections, MultiWayIf #-}
    
    2 2
     module Rules.BinaryDist where
    
    3 3
     
    
    4
    -import Hadrian.Haskell.Cabal
    
    5
    -
    
    6 4
     import CommandLine
    
    7 5
     import Context
    
    8 6
     import Expression
    
    ... ... @@ -146,15 +144,12 @@ bindistRules = do
    146 144
         phony "binary-dist-dir" $ do
    
    147 145
             version        <- setting ProjectVersion
    
    148 146
             targetPlatform <- setting TargetPlatformFull
    
    149
    -        distDir        <- Context.distDir Stage1
    
    150
    -        rtsDir         <- pkgUnitId Stage1 rts
    
    151
    -        -- let rtsDir  = "rts"
    
    147
    +        distDir        <- Context.distDir (vanillaContext Stage1 rts)
    
    152 148
     
    
    153 149
             let ghcBuildDir      = root -/- stageString Stage1
    
    154 150
                 bindistFilesDir  = root -/- "bindist" -/- ghcVersionPretty
    
    155 151
                 ghcVersionPretty = "ghc-" ++ version ++ "-" ++ targetPlatform
    
    156
    -            rtsIncludeDir    = ghcBuildDir -/- "lib" -/- distDir -/- rtsDir
    
    157
    -                               -/- "include"
    
    152
    +            rtsIncludeDir    = distDir -/- "include"
    
    158 153
     
    
    159 154
             -- We 'need' all binaries and libraries
    
    160 155
             all_pkgs <- stagePackages Stage1
    

  • hadrian/src/Rules/CabalReinstall.hs
    ... ... @@ -10,7 +10,6 @@ import Utilities
    10 10
     import qualified System.Directory.Extra as IO
    
    11 11
     import Data.Either
    
    12 12
     import Rules.BinaryDist
    
    13
    -import Hadrian.Haskell.Cabal (pkgUnitId)
    
    14 13
     import Oracles.Setting
    
    15 14
     
    
    16 15
     {-
    
    ... ... @@ -53,13 +52,10 @@ cabalBuildRules = do
    53 52
             iserv_targets <- if cross then pure [] else iservBins
    
    54 53
             need (lib_targets ++ (map (\(_, p) -> p) (bin_targets ++ iserv_targets)))
    
    55 54
     
    
    56
    -        distDir        <- Context.distDir Stage1
    
    57
    -        rtsDir         <- pkgUnitId Stage1 rts
    
    55
    +        distDir        <- Context.distDir (vanillaContext Stage1 rts)
    
    58 56
             -- let rtsDir = "rts"
    
    59 57
     
    
    60
    -        let ghcBuildDir      = root -/- stageString Stage1
    
    61
    -            rtsIncludeDir    = ghcBuildDir -/- "lib" -/- distDir -/- rtsDir
    
    62
    -                               -/- "include"
    
    58
    +        let rtsIncludeDir    = distDir -/- "include"
    
    63 59
     
    
    64 60
             libdir  <- liftIO . IO.makeAbsolute =<< stageLibPath Stage1
    
    65 61
             work_dir <- liftIO $ IO.makeAbsolute $ root -/- "stage-cabal"
    

  • hadrian/src/Rules/Register.hs
    ... ... @@ -182,11 +182,12 @@ buildConfFinal rs context@Context {..} _conf = do
    182 182
         --
    
    183 183
         -- so that if any change ends up modifying a library (but not its .conf
    
    184 184
         -- file), we still rebuild things that depend on it.
    
    185
    -    dir <- (-/-) <$> libPath context <*> distDir stage
    
    185
    +    dir <- distDir context
    
    186
    +    dyndir <- distDynDir context
    
    186 187
         pkgid <- pkgUnitId stage package
    
    187 188
         files <- liftIO $
    
    188
    -      (++) <$> getDirectoryFilesIO "." [dir -/- "*libHS"++pkgid++"*"]
    
    189
    -           <*> getDirectoryFilesIO "." [dir -/- pkgid -/- "**"]
    
    189
    +      (++) <$> getDirectoryFilesIO "." [dyndir -/- "*libHS"++pkgid++"*"]
    
    190
    +           <*> getDirectoryFilesIO "." [dir -/- "**"]
    
    190 191
         produces files
    
    191 192
     
    
    192 193
     buildConfInplace :: [(Resource, Int)] -> Context -> FilePath -> Action ()
    

  • hadrian/src/Rules/Rts.hs
    ... ... @@ -154,10 +154,9 @@ needRtsSymLinks :: Stage -> Set.Set Way -> Action ()
    154 154
     needRtsSymLinks stage rtsWays
    
    155 155
         = forM_ (Set.filter (wayUnit Dynamic) rtsWays) $ \ way -> do
    
    156 156
             let ctx = Context stage rts way Final
    
    157
    -        libPath     <- libPath ctx
    
    158
    -        distDir     <- distDir stage
    
    157
    +        distDir     <- distDynDir ctx
    
    159 158
             rtsLibFile  <- takeFileName <$> pkgLibraryFile ctx
    
    160
    -        need [removeRtsDummyVersion (libPath </> distDir </> rtsLibFile)]
    
    159
    +        need [removeRtsDummyVersion (distDir </> rtsLibFile)]
    
    161 160
     
    
    162 161
     prefix, versionlessPrefix :: String
    
    163 162
     versionlessPrefix = "libHSrts"
    

  • hadrian/src/Settings/Builders/Ghc.hs
    ... ... @@ -98,9 +98,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
    98 98
         -- Relative path from the output (rpath $ORIGIN).
    
    99 99
         originPath <- dropFileName <$> getOutput
    
    100 100
         context <- getContext
    
    101
    -    libPath' <- expr (libPath context)
    
    102
    -    st <- getStage
    
    103
    -    distDir <- expr (Context.distDir st)
    
    101
    +    distPath <- expr (Context.distDynDir context)
    
    104 102
     
    
    105 103
         useSystemFfi <- expr (flag UseSystemFfi)
    
    106 104
         buildPath <- getBuildPath
    
    ... ... @@ -112,7 +110,6 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
    112 110
     
    
    113 111
         let
    
    114 112
             dynamic = Dynamic `wayUnit` way
    
    115
    -        distPath = libPath' -/- distDir
    
    116 113
             originToLibsDir = makeRelativeNoSysLink originPath distPath
    
    117 114
             rpath
    
    118 115
                 -- Programs will end up in the bin dir ($ORIGIN) and will link to
    

  • testsuite/driver/testlib.py
    ... ... @@ -1493,7 +1493,7 @@ async def do_test(name: TestName,
    1493 1493
             dst_makefile = in_testdir('Makefile')
    
    1494 1494
             if src_makefile.exists():
    
    1495 1495
                 makefile = src_makefile.read_text(encoding='UTF-8')
    
    1496
    -            makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, 1)
    
    1496
    +            makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, count=1)
    
    1497 1497
                 dst_makefile.write_text(makefile, encoding='UTF-8')
    
    1498 1498
     
    
    1499 1499
         if opts.pre_cmd:
    

  • testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout
    ... ... @@ -13,13 +13,13 @@ Building library 'q' instantiated with
    13 13
     for bkpcabal08-0.1.0.0...
    
    14 14
     [2 of 4] Compiling B[sig]           ( q/B.hsig, nothing )
    
    15 15
     [3 of 4] Compiling M                ( q/M.hs, nothing ) [A changed]
    
    16
    -[4 of 4] Instantiating bkpcabal08-0.1.0.0-5O1mUtZZLBeDZEqqtwJcCj-p
    
    16
    +[4 of 4] Instantiating bkpcabal08-0.1.0.0-Asivy2QkF0WEbGENiw5nyj-p
    
    17 17
     Preprocessing library 'q' for bkpcabal08-0.1.0.0...
    
    18 18
     Building library 'q' instantiated with
    
    19
    -  A = bkpcabal08-0.1.0.0-DlVb5PcmUolGCHYbfTL7EP-impl:A
    
    20
    -  B = bkpcabal08-0.1.0.0-DlVb5PcmUolGCHYbfTL7EP-impl:B
    
    19
    +  A = bkpcabal08-0.1.0.0-BznDTmYyvWf7fdEdPEncB4-impl:A
    
    20
    +  B = bkpcabal08-0.1.0.0-BznDTmYyvWf7fdEdPEncB4-impl:B
    
    21 21
     for bkpcabal08-0.1.0.0...
    
    22
    -[1 of 3] Compiling A[sig]           ( q/A.hsig, dist/build/bkpcabal08-0.1.0.0-LFiTKyjPqyn9yyuysCoVKg-q+5IA1jA4bEzCFcXtraqAC38/A.o ) [Prelude package changed]
    
    23
    -[2 of 3] Compiling B[sig]           ( q/B.hsig, dist/build/bkpcabal08-0.1.0.0-LFiTKyjPqyn9yyuysCoVKg-q+5IA1jA4bEzCFcXtraqAC38/B.o ) [Prelude package changed]
    
    22
    +[1 of 3] Compiling A[sig]           ( q/A.hsig, dist/build/bkpcabal08-0.1.0.0-BOgmYfE3t0l9LsOUH0dl5H-q+sLNLgjkt61DMZK9wGbx81/A.o ) [Prelude package changed]
    
    23
    +[2 of 3] Compiling B[sig]           ( q/B.hsig, dist/build/bkpcabal08-0.1.0.0-BOgmYfE3t0l9LsOUH0dl5H-q+sLNLgjkt61DMZK9wGbx81/B.o ) [Prelude package changed]
    
    24 24
     Preprocessing library 'r' for bkpcabal08-0.1.0.0...
    
    25 25
     Building library 'r' for bkpcabal08-0.1.0.0...

  • testsuite/tests/driver/T20604/T20604.stdout
    1 1
     A1
    
    2 2
     A
    
    3
    -addDependentFile "/home/ben/ghc/ghc-compare-2/_build/stage1/lib/../lib/x86_64-linux-ghc-9.9.20230815/libHSghc-prim-0.10.0-inplace-ghc9.9.20230815.so" 1403aed32fb9af243c4cc949007c846c
    
    4
    -addDependentFile "/home/ben/ghc/ghc-compare-2/_build/stage1/lib/../lib/x86_64-linux-ghc-9.9.20230815/libHSghc-bignum-1.3-inplace-ghc9.9.20230815.so" 54293f8faab737bac998f6e1a1248db8
    
    5
    -addDependentFile "/home/ben/ghc/ghc-compare-2/_build/stage1/lib/../lib/x86_64-linux-ghc-9.9.20230815/libHSghc-internal-0.1.0.0-inplace-ghc9.9.20230815.so" a5c0e962d84d9044d44df4698becddcc
    
    6
    -addDependentFile "/home/ben/ghc/ghc-compare-2/_build/stage1/lib/../lib/x86_64-linux-ghc-9.9.20230815/libHSbase-4.19.0.0-inplace-ghc9.9.20230815.so" 4a90ed136fe0f89e5d0360daded517bd
    
    7
    -addDependentFile "/home/ben/ghc/ghc-compare-2/_build/stage1/lib/../lib/x86_64-linux-ghc-9.9.20230815/libHSghc-boot-th-9.9-inplace-ghc9.9.20230815.so" e338655f71b1d37fdfdd2504b7de6e76
    
    8
    -addDependentFile "/home/ben/ghc/ghc-compare-2/_build/stage1/lib/../lib/x86_64-linux-ghc-9.9.20230815/libHSarray-0.5.6.0-inplace-ghc9.9.20230815.so" 6943478e8adaa043abf7a2b38dd435a2
    
    9
    -addDependentFile "/home/ben/ghc/ghc-compare-2/_build/stage1/lib/../lib/x86_64-linux-ghc-9.9.20230815/libHSdeepseq-1.5.0.0-inplace-ghc9.9.20230815.so" 9974eb196694990ac6bb3c2591405de0
    
    10
    -addDependentFile "/home/ben/ghc/ghc-compare-2/_build/stage1/lib/../lib/x86_64-linux-ghc-9.9.20230815/libHSpretty-1.1.3.6-inplace-ghc9.9.20230815.so" 1eefc21514f5584086f62b70aa554b7d
    
    11
    -addDependentFile "/home/ben/ghc/ghc-compare-2/_build/stage1/lib/../lib/x86_64-linux-ghc-9.9.20230815/libHStemplate-haskell-2.21.0.0-inplace-ghc9.9.20230815.so" f85c86eb94dcce1eacd739b6e991ba2d
    3
    +addDependentFile "/home/zubin/ghcs/unicode-lex/_build_/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250724/libHSghc-prim-0.12.0-inplace-ghc9.10.2.20250724.so" 0b7cbf5659e1fd221ea306e2da08c7d3
    
    4
    +addDependentFile "/home/zubin/ghcs/unicode-lex/_build_/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250724/libHSghc-bignum-1.3-inplace-ghc9.10.2.20250724.so" 1c29a409bcfbc31a3cfc2ded7c1d5530
    
    5
    +addDependentFile "/home/zubin/ghcs/unicode-lex/_build_/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250724/libHSghc-internal-9.1002.0-inplace-ghc9.10.2.20250724.so" 9606aee1cbbee934848aa85568563754
    
    6
    +addDependentFile "/home/zubin/ghcs/unicode-lex/_build_/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250724/libHSbase-4.20.1.0-inplace-ghc9.10.2.20250724.so" 5d1ab384becff6d4b20bae121d55fbc8
    
    7
    +addDependentFile "/home/zubin/ghcs/unicode-lex/_build_/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250724/libHSghc-boot-th-9.10.2.20250724-inplace-ghc9.10.2.20250724.so" 930b5206ff48d75ba522e582262695a8
    
    8
    +addDependentFile "/home/zubin/ghcs/unicode-lex/_build_/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250724/libHSdeepseq-1.5.2.0-inplace-ghc9.10.2.20250724.so" db23e7880c9a9fee0d494b48294c3487
    
    9
    +addDependentFile "/home/zubin/ghcs/unicode-lex/_build_/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250724/libHSpretty-1.1.3.6-inplace-ghc9.10.2.20250724.so" ad484cfb103f02509b1be6abcf2a402f
    
    10
    +addDependentFile "/home/zubin/ghcs/unicode-lex/_build_/stage1/lib/../lib/x86_64-linux-ghc-9.10.2.20250724/libHStemplate-haskell-2.22.0.0-inplace-ghc9.10.2.20250724.so" 50b2cb166e6e5293c24be374ffac2ade

  • testsuite/tests/ghci/scripts/ghci064.stdout
    ... ... @@ -27,12 +27,12 @@ instance [safe] Eq w => Eq (Maybe w)
    27 27
       -- Defined in ‘GHC.Internal.Maybe’
    
    28 28
     instance GHC.Internal.Generics.Generic [w]
    
    29 29
       -- Defined in ‘GHC.Internal.Generics’
    
    30
    -instance Monoid [w] -- Defined in ‘GHC.Internal.Base’
    
    31
    -instance Semigroup [w] -- Defined in ‘GHC.Internal.Base’
    
    32 30
     instance Read w => Read [w] -- Defined in ‘GHC.Internal.Read’
    
    33 31
     instance Eq w => Eq [w] -- Defined in ‘GHC.Classes’
    
    34 32
     instance Ord w => Ord [w] -- Defined in ‘GHC.Classes’
    
    35 33
     instance Show w => Show [w] -- Defined in ‘GHC.Internal.Show’
    
    34
    +instance Monoid [w] -- Defined in ‘GHC.Internal.Base’
    
    35
    +instance Semigroup [w] -- Defined in ‘GHC.Internal.Base’
    
    36 36
     instance [safe] MyShow w => MyShow [w]
    
    37 37
       -- Defined at ghci064.hs:8:10
    
    38 38
     instance GHC.Internal.Generics.Generic [T]
    

  • testsuite/tests/plugins/plugins10.stdout
    ... ... @@ -7,6 +7,8 @@ interfacePlugin: GHC.Internal.Float
    7 7
     interfacePlugin: GHC.Prim.Ext
    
    8 8
     interfacePlugin: Language.Haskell.TH.Syntax
    
    9 9
     typeCheckPlugin (rn)
    
    10
    +interfacePlugin: GHC.Internal.Stack.Types
    
    11
    +interfacePlugin: GHC.Internal.Exception.Context
    
    10 12
     typeCheckPlugin (tc)
    
    11 13
     parsePlugin(a)
    
    12 14
     typeCheckPlugin (rn)
    

  • testsuite/tests/plugins/static-plugins.stdout
    ... ... @@ -8,6 +8,8 @@ interfacePlugin: GHC.Internal.System.IO
    8 8
     interfacePlugin: GHC.Types
    
    9 9
     interfacePlugin: GHC.Internal.Show
    
    10 10
     typeCheckPlugin (rn)
    
    11
    +interfacePlugin: GHC.Internal.Stack.Types
    
    12
    +interfacePlugin: GHC.Internal.Exception.Context
    
    11 13
     interfacePlugin: GHC.Internal.TopHandler
    
    12 14
     typeCheckPlugin (tc)
    
    13 15
     interfacePlugin: GHC.CString
    

  • testsuite/tests/typecheck/should_run/T25529.hs
    1
    +{-# LANGUAGE ConstraintKinds #-}
    
    2
    +{-# LANGUAGE ImplicitParams #-}
    
    3
    +
    
    4
    +module Main where
    
    5
    +
    
    6
    +import GHC.Stack (HasCallStack, CallStack, SrcLoc(srcLocStartLine, srcLocStartCol), callStack, getCallStack)
    
    7
    +
    
    8
    +main :: IO ()
    
    9
    +main =
    
    10
    +  let ?myImplicitParam = ()
    
    11
    +   in run action
    
    12
    +
    
    13
    +type MyConstraints = (HasCallStack, ?myImplicitParam :: ())
    
    14
    +
    
    15
    +action :: MyConstraints => IO ()
    
    16
    +action = run $ pure ()
    
    17
    +
    
    18
    +-- | Print the current call stack and then run an action.
    
    19
    +run ::
    
    20
    +  MyConstraints =>
    
    21
    +  IO a ->
    
    22
    +  IO a
    
    23
    +run action = do
    
    24
    +  let prettyCallStack = unlines $ map prettyCallStackEntry $ getCallStack callStack
    
    25
    +      prettyCallStackEntry (name, loc) =
    
    26
    +        name
    
    27
    +        <> ", called at "
    
    28
    +        <> show (srcLocStartLine loc)
    
    29
    +        <> ":"
    
    30
    +        <> show (srcLocStartCol loc)
    
    31
    +  putStrLn "============================================================"
    
    32
    +  putStrLn prettyCallStack
    
    33
    +  action

  • testsuite/tests/typecheck/should_run/T25529.stdout
    1
    +============================================================
    
    2
    +run, called at 11:7
    
    3
    +
    
    4
    +============================================================
    
    5
    +run, called at 16:10
    
    6
    +action, called at 11:11
    
    7
    +

  • testsuite/tests/typecheck/should_run/all.T
    ... ... @@ -170,6 +170,7 @@ test('T22510', normal, compile_and_run, [''])
    170 170
     test('T21973a', [exit_code(1)], compile_and_run, [''])
    
    171 171
     test('T21973b', normal, compile_and_run, [''])
    
    172 172
     test('T23761', normal, compile_and_run, [''])
    
    173
    +test('T25529', normal, compile_and_run, [''])
    
    173 174
     test('T23761b', normal, compile_and_run, [''])
    
    174 175
     test('T17594e', normal, compile_and_run, [''])
    
    175 176
     test('T25998', normal, compile_and_run, [''])
    

  • utils/haddock
    1
    -Subproject commit f6116257ff838bb0b9def2c49d2f629756527ad2
    1
    +Subproject commit 00ac9eec76037ebf4e9b0b84f50675449edc5f51