Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
-
8a317b6f
by Aaron Allen at 2026-01-01T03:05:15-05:00
-
ae1aeaab
by Cheng Shao at 2026-01-01T03:06:32-05:00
-
6213bb57
by maralorn at 2026-01-02T16:30:32+01:00
-
7479a17e
by Janis Voigtlaender at 2026-01-04T17:21:59-05:00
10 changed files:
- compiler/GHC/Iface/Recomp.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs
- + testsuite/tests/driver/recomp26183/M.hs
- + testsuite/tests/driver/recomp26183/M2A.hs
- + testsuite/tests/driver/recomp26183/M2B.hs
- + testsuite/tests/driver/recomp26183/Makefile
- + testsuite/tests/driver/recomp26183/all.T
- + testsuite/tests/driver/recomp26183/recomp26183.stderr
- testsuite/tests/numeric/should_run/all.T
Changes:
| ... | ... | @@ -1782,10 +1782,12 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env complete_env decl |
| 1782 | 1782 | IfaceClass{ifBody = IfConcreteClass { ifSigs=sigs, ifATs=ats }} ->
|
| 1783 | 1783 | IfaceClassExtras (fix_fn n) insts (ann_fn (AnnOccName n)) meths defms
|
| 1784 | 1784 | where
|
| 1785 | - insts = (map ifDFun $ (concatMap at_extras ats)
|
|
| 1786 | - ++ lookupOccEnvL inst_env n)
|
|
| 1787 | - -- Include instances of the associated types
|
|
| 1788 | - -- as well as instances of the class (#5147)
|
|
| 1785 | + insts =
|
|
| 1786 | + let (atFamInsts, atClsInsts) = foldMap at_extras ats
|
|
| 1787 | + in (ifFamInstAxiom <$> atFamInsts) ++ (ifDFun <$> atClsInsts)
|
|
| 1788 | + ++ (ifDFun <$> lookupOccEnvL inst_env n)
|
|
| 1789 | + -- Include instances and axioms of the associated types
|
|
| 1790 | + -- as well as instances of the class (#5147) (#26183)
|
|
| 1789 | 1791 | meths = [id_extras (getOccName op) | IfaceClassOp op _ _ <- sigs]
|
| 1790 | 1792 | -- Names of all the default methods (see Note [default method Name])
|
| 1791 | 1793 | defms = [ dmName
|
| ... | ... | @@ -1802,7 +1804,10 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env complete_env decl |
| 1802 | 1804 | where
|
| 1803 | 1805 | n = getOccName decl
|
| 1804 | 1806 | id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn (AnnOccName occ)) (lookup_complete_match occ)
|
| 1805 | - at_extras (IfaceAT decl _) = lookupOccEnvL inst_env (getOccName decl)
|
|
| 1807 | + at_extras (IfaceAT decl _) =
|
|
| 1808 | + ( lookupOccEnvL fi_env (getOccName decl) -- Axioms
|
|
| 1809 | + , lookupOccEnvL inst_env (getOccName decl) -- Class instances
|
|
| 1810 | + )
|
|
| 1806 | 1811 | |
| 1807 | 1812 | lookup_complete_match occ = lookupOccEnvL complete_env occ
|
| 1808 | 1813 |
| ... | ... | @@ -314,7 +314,7 @@ Core: https://gitlab.haskell.org/ghc/ghc/issues/11795#note_118976 |
| 314 | 314 | -- | @'replicateM' n act@ performs the action @act@ @n@ times,
|
| 315 | 315 | -- and then returns the list of results.
|
| 316 | 316 | --
|
| 317 | --- @replicateM n (pure x) == 'replicate' n x@
|
|
| 317 | +-- @replicateM n (pure x) == pure ('replicate' n x)@
|
|
| 318 | 318 | --
|
| 319 | 319 | -- ==== __Examples__
|
| 320 | 320 | --
|
| ... | ... | @@ -64,7 +64,7 @@ instance Monoid ExceptionContext where |
| 64 | 64 | emptyExceptionContext :: ExceptionContext
|
| 65 | 65 | emptyExceptionContext = ExceptionContext []
|
| 66 | 66 | |
| 67 | --- | Construct a singleton 'ExceptionContext' from an 'ExceptionAnnotation'.
|
|
| 67 | +-- | Add an 'ExceptionAnnotation' to a given 'ExceptionContext'.
|
|
| 68 | 68 | --
|
| 69 | 69 | -- @since base-4.20.0.0
|
| 70 | 70 | addExceptionAnnotation :: ExceptionAnnotation a => a -> ExceptionContext -> ExceptionContext
|
| 1 | +module M where
|
|
| 2 | +import M2
|
|
| 3 | + |
|
| 4 | +x :: AT ()
|
|
| 5 | +x = True |
| 1 | +{-# LANGUAGE TypeFamilies #-}
|
|
| 2 | +module M2 where
|
|
| 3 | + |
|
| 4 | +class C a where
|
|
| 5 | + type AT a
|
|
| 6 | + |
|
| 7 | +instance C () where
|
|
| 8 | + type AT () = Bool |
| 1 | +{-# LANGUAGE TypeFamilies #-}
|
|
| 2 | +module M2 where
|
|
| 3 | + |
|
| 4 | +class C a where
|
|
| 5 | + type AT a
|
|
| 6 | + |
|
| 7 | +instance C () where
|
|
| 8 | + type AT () = Int |
| 1 | +TOP=../../..
|
|
| 2 | +include $(TOP)/mk/boilerplate.mk
|
|
| 3 | +include $(TOP)/mk/test.mk
|
|
| 4 | + |
|
| 5 | +# Recompilation tests
|
|
| 6 | + |
|
| 7 | +recomp26183:
|
|
| 8 | + cp M2A.hs M2.hs
|
|
| 9 | + '$(TEST_HC)' $(TEST_HC_OPTS) --make M.hs
|
|
| 10 | + sleep 1
|
|
| 11 | + cp M2B.hs M2.hs
|
|
| 12 | + # This should fail
|
|
| 13 | + if '$(TEST_HC)' $(TEST_HC_OPTS) --make M.hs; then false; fi |
| 1 | +test('recomp26183', [extra_files(['M2A.hs', 'M.hs', 'M2B.hs']),
|
|
| 2 | + when(fast(), skip), ignore_stdout],
|
|
| 3 | + makefile_test, []) |
| 1 | +M.hs:5:5: error: [GHC-83865]
|
|
| 2 | + • Couldn't match type ‘Bool’ with ‘Int’
|
|
| 3 | + Expected: AT ()
|
|
| 4 | + Actual: Bool
|
|
| 5 | + • In the expression: True
|
|
| 6 | + In an equation for ‘x’: x = True
|
|
| 7 | + |
| ... | ... | @@ -5,6 +5,10 @@ |
| 5 | 5 | |
| 6 | 6 | import random
|
| 7 | 7 | |
| 8 | +# some bugs only surface with -O, omitting optasm may cause them to
|
|
| 9 | +# slip into releases! (e.g. #26711)
|
|
| 10 | +setTestOpts(when(have_ncg(), extra_ways(['optasm'])))
|
|
| 11 | + |
|
| 8 | 12 | test('arith001', normal, compile_and_run, [''])
|
| 9 | 13 | test('arith002', normal, compile_and_run, [''])
|
| 10 | 14 | test('arith003', normal, compile_and_run, [''])
|