[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: [#26183] Associated Type Iface Fix
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 [#26183] Associated Type Iface Fix When determining "extras" for class decl interface entries, axioms for the associated types need to included so that dependent modules will be recompiled if those axioms change. resolves #26183 - - - - - ae1aeaab by Cheng Shao at 2026-01-01T03:06:32-05:00 testsuite: run numeric tests with optasm when available This patch adds the `optasm` extra way to nueric tests when NCG is available. Some numeric bugs only surface with optimization, omitting this can hide these bugs and even make them slip into release! (e.g. #26711) - - - - - 6213bb57 by maralorn at 2026-01-02T16:30:32+01:00 GHC.Internal.Exception.Context: Fix comment on addExceptionAnnotation - - - - - 7479a17e by Janis Voigtlaender at 2026-01-04T17:21:59-05:00 GHC.Internal.Control.Monad.replicateM: Fix comment - - - - - 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: ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -1782,10 +1782,12 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env complete_env decl IfaceClass{ifBody = IfConcreteClass { ifSigs=sigs, ifATs=ats }} -> IfaceClassExtras (fix_fn n) insts (ann_fn (AnnOccName n)) meths defms where - insts = (map ifDFun $ (concatMap at_extras ats) - ++ lookupOccEnvL inst_env n) - -- Include instances of the associated types - -- as well as instances of the class (#5147) + insts = + let (atFamInsts, atClsInsts) = foldMap at_extras ats + in (ifFamInstAxiom <$> atFamInsts) ++ (ifDFun <$> atClsInsts) + ++ (ifDFun <$> lookupOccEnvL inst_env n) + -- Include instances and axioms of the associated types + -- as well as instances of the class (#5147) (#26183) meths = [id_extras (getOccName op) | IfaceClassOp op _ _ <- sigs] -- Names of all the default methods (see Note [default method Name]) defms = [ dmName @@ -1802,7 +1804,10 @@ declExtras fix_fn ann_fn rule_env inst_env fi_env dm_env complete_env decl where n = getOccName decl id_extras occ = IdExtras (fix_fn occ) (lookupOccEnvL rule_env occ) (ann_fn (AnnOccName occ)) (lookup_complete_match occ) - at_extras (IfaceAT decl _) = lookupOccEnvL inst_env (getOccName decl) + at_extras (IfaceAT decl _) = + ( lookupOccEnvL fi_env (getOccName decl) -- Axioms + , lookupOccEnvL inst_env (getOccName decl) -- Class instances + ) lookup_complete_match occ = lookupOccEnvL complete_env occ ===================================== libraries/ghc-internal/src/GHC/Internal/Control/Monad.hs ===================================== @@ -314,7 +314,7 @@ Core: https://gitlab.haskell.org/ghc/ghc/issues/11795#note_118976 -- | @'replicateM' n act@ performs the action @act@ @n@ times, -- and then returns the list of results. -- --- @replicateM n (pure x) == 'replicate' n x@ +-- @replicateM n (pure x) == pure ('replicate' n x)@ -- -- ==== __Examples__ -- ===================================== libraries/ghc-internal/src/GHC/Internal/Exception/Context.hs ===================================== @@ -64,7 +64,7 @@ instance Monoid ExceptionContext where emptyExceptionContext :: ExceptionContext emptyExceptionContext = ExceptionContext [] --- | Construct a singleton 'ExceptionContext' from an 'ExceptionAnnotation'. +-- | Add an 'ExceptionAnnotation' to a given 'ExceptionContext'. -- -- @since base-4.20.0.0 addExceptionAnnotation :: ExceptionAnnotation a => a -> ExceptionContext -> ExceptionContext ===================================== testsuite/tests/driver/recomp26183/M.hs ===================================== @@ -0,0 +1,5 @@ +module M where +import M2 + +x :: AT () +x = True ===================================== testsuite/tests/driver/recomp26183/M2A.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE TypeFamilies #-} +module M2 where + +class C a where + type AT a + +instance C () where + type AT () = Bool ===================================== testsuite/tests/driver/recomp26183/M2B.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE TypeFamilies #-} +module M2 where + +class C a where + type AT a + +instance C () where + type AT () = Int ===================================== testsuite/tests/driver/recomp26183/Makefile ===================================== @@ -0,0 +1,13 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +# Recompilation tests + +recomp26183: + cp M2A.hs M2.hs + '$(TEST_HC)' $(TEST_HC_OPTS) --make M.hs + sleep 1 + cp M2B.hs M2.hs + # This should fail + if '$(TEST_HC)' $(TEST_HC_OPTS) --make M.hs; then false; fi ===================================== testsuite/tests/driver/recomp26183/all.T ===================================== @@ -0,0 +1,3 @@ +test('recomp26183', [extra_files(['M2A.hs', 'M.hs', 'M2B.hs']), + when(fast(), skip), ignore_stdout], + makefile_test, []) ===================================== testsuite/tests/driver/recomp26183/recomp26183.stderr ===================================== @@ -0,0 +1,7 @@ +M.hs:5:5: error: [GHC-83865] + • Couldn't match type ‘Bool’ with ‘Int’ + Expected: AT () + Actual: Bool + • In the expression: True + In an equation for ‘x’: x = True + ===================================== testsuite/tests/numeric/should_run/all.T ===================================== @@ -5,6 +5,10 @@ import random +# some bugs only surface with -O, omitting optasm may cause them to +# slip into releases! (e.g. #26711) +setTestOpts(when(have_ncg(), extra_ways(['optasm']))) + test('arith001', normal, compile_and_run, ['']) test('arith002', normal, compile_and_run, ['']) test('arith003', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/be4b173d024ddee98d8ef455582ed50... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/be4b173d024ddee98d8ef455582ed50... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)