
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 03555ed8 by Sylvain Henry at 2025-08-10T22:20:57-04:00 Handle non-fractional CmmFloats in Cmm's CBE (#26229) Since f8d9d016305be355f518c141f6c6d4826f2de9a2, toRational for Float and Double converts float's infinity and NaN into Rational's infinity and NaN (respectively 1%0 and 0%0). Cmm CommonBlockEliminator hashing function needs to take these values into account as they can appear as literals now. See added testcase. - - - - - 6c956af3 by J. Ryan Stinnett at 2025-08-10T22:21:42-04:00 Fix extensions list in `DoAndIfThenElse` docs - - - - - 6dc420b1 by J. Ryan Stinnett at 2025-08-10T22:21:42-04:00 Document status of `RelaxedPolyRec` extension This adds a brief extension page explaining the status of the `RelaxedPolyRec` extension. The behaviour of this mode is already explained elsewhere, so this page is mainly for completeness so that various lists of extensions have somewhere to point to for this flag. Fixes #18630 - - - - - 0927bda0 by Simon Peyton Jones at 2025-08-11T03:30:50-04:00 Take more care in zonkEqTypes on AppTy/AppTy This patch fixes #26256. See Note [zonkEqTypes and the PKTI] in GHC.Tc.Solver.Equality - - - - - e7755f73 by Zubin Duggal at 2025-08-11T03:30:51-04:00 ci: upgrade bootstrap compiler on windows to 9.10.1 - - - - - 16 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - compiler/GHC/Cmm/CommonBlockElim.hs - compiler/GHC/Tc/Solver/Equality.hs - docs/users_guide/conf.py - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/exts/doandifthenelse.rst - + docs/users_guide/exts/relaxed_poly_rec.rst - docs/users_guide/exts/types.rst - + testsuite/tests/numeric/should_compile/T26229.hs - testsuite/tests/numeric/should_compile/all.T - + testsuite/tests/partial-sigs/should_compile/T26256.hs - + testsuite/tests/partial-sigs/should_compile/T26256.stderr - testsuite/tests/partial-sigs/should_compile/all.T - + testsuite/tests/typecheck/should_compile/T26256a.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== .gitlab/generate-ci/gen_ci.hs ===================================== @@ -478,7 +478,7 @@ opsysVariables _ (Windows {}) = mconcat , "LANG" =: "en_US.UTF-8" , "CABAL_INSTALL_VERSION" =: "3.10.2.0" , "HADRIAN_ARGS" =: "--docs=no-sphinx-pdfs" - , "GHC_VERSION" =: "9.6.4" + , "GHC_VERSION" =: "9.10.1" ] opsysVariables _ _ = mempty ===================================== .gitlab/jobs.yaml ===================================== @@ -3698,7 +3698,7 @@ "BUILD_FLAVOUR": "validate", "CABAL_INSTALL_VERSION": "3.10.2.0", "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "GHC_VERSION": "9.6.4", + "GHC_VERSION": "9.10.1", "HADRIAN_ARGS": "--docs=no-sphinx-pdfs", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", "LANG": "en_US.UTF-8", @@ -3761,7 +3761,7 @@ "BUILD_FLAVOUR": "validate", "CABAL_INSTALL_VERSION": "3.10.2.0", "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "GHC_VERSION": "9.6.4", + "GHC_VERSION": "9.10.1", "HADRIAN_ARGS": "--docs=no-sphinx-pdfs", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", "LANG": "en_US.UTF-8", @@ -5579,7 +5579,7 @@ "BUILD_FLAVOUR": "release", "CABAL_INSTALL_VERSION": "3.10.2.0", "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "GHC_VERSION": "9.6.4", + "GHC_VERSION": "9.10.1", "HADRIAN_ARGS": "--docs=no-sphinx-pdfs", "IGNORE_PERF_FAILURES": "all", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", @@ -5643,7 +5643,7 @@ "BUILD_FLAVOUR": "release", "CABAL_INSTALL_VERSION": "3.10.2.0", "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "GHC_VERSION": "9.6.4", + "GHC_VERSION": "9.10.1", "HADRIAN_ARGS": "--docs=no-sphinx-pdfs", "IGNORE_PERF_FAILURES": "all", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", @@ -7982,7 +7982,7 @@ "BUILD_FLAVOUR": "validate", "CABAL_INSTALL_VERSION": "3.10.2.0", "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "GHC_VERSION": "9.6.4", + "GHC_VERSION": "9.10.1", "HADRIAN_ARGS": "--docs=no-sphinx-pdfs", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", "LANG": "en_US.UTF-8", @@ -8044,7 +8044,7 @@ "BUILD_FLAVOUR": "validate", "CABAL_INSTALL_VERSION": "3.10.2.0", "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", - "GHC_VERSION": "9.6.4", + "GHC_VERSION": "9.10.1", "HADRIAN_ARGS": "--docs=no-sphinx-pdfs", "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check", "LANG": "en_US.UTF-8", ===================================== compiler/GHC/Cmm/CommonBlockElim.hs ===================================== @@ -29,6 +29,7 @@ import GHC.Utils.Word64 (truncateWord64ToWord32) import Control.Arrow (first, second) import Data.List.NonEmpty (NonEmpty (..)) import qualified Data.List.NonEmpty as NE +import GHC.Real (infinity,notANumber) -- ----------------------------------------------------------------------------- -- Eliminate common blocks @@ -167,7 +168,12 @@ hash_block block = hash_lit :: CmmLit -> Word32 hash_lit (CmmInt i _) = fromInteger i - hash_lit (CmmFloat r _) = truncate r + hash_lit (CmmFloat r _) + -- handle these special cases as `truncate` fails on non-fractional numbers (#26229) + | r == infinity = 9999999 + | r == -infinity = 9999998 + | r == notANumber = 6666666 + | otherwise = truncate r hash_lit (CmmVec ls) = hash_list hash_lit ls hash_lit (CmmLabel _) = 119 -- ugh hash_lit (CmmLabelOff _ i) = cvt $ 199 + i ===================================== compiler/GHC/Tc/Solver/Equality.hs ===================================== @@ -197,12 +197,8 @@ zonkEqTypes ev eq_rel ty1 ty2 then tycon tc1 tys1 tys2 else bale_out ty1 ty2 - go ty1 ty2 - | Just (ty1a, ty1b) <- tcSplitAppTyNoView_maybe ty1 - , Just (ty2a, ty2b) <- tcSplitAppTyNoView_maybe ty2 - = do { res_a <- go ty1a ty2a - ; res_b <- go ty1b ty2b - ; return $ combine_rev mkAppTy res_b res_a } + -- If you are temppted to add a case for AppTy/AppTy, be careful + -- See Note [zonkEqTypes and the PKTI] go ty1@(LitTy lit1) (LitTy lit2) | lit1 == lit2 @@ -278,6 +274,32 @@ zonkEqTypes ev eq_rel ty1 ty2 combine_rev f (Right tys) (Right ty) = Right (f ty tys) +{- Note [zonkEqTypes and the PKTI] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Because `zonkEqTypes` does /partial/ zonking, we need to be very careful +to maintain the Purely Kinded Type Invariant: see GHC.Tc.Gen/HsType +HsNote [The Purely Kinded Type Invariant (PKTI)]. + +In #26256 we try to solve this equality constraint: + Int :-> Maybe Char ~# k0 Int (m0 Char) +where m0 and k0 are unification variables, and + m0 :: Type -> Type +It happens that m0 was already unified + m0 := (w0 :: kappa) +where kappa is another unification variable that is also already unified: + kappa := Type->Type. +So the original type satisifed the PKTI, but a partially-zonked form + k0 Int (w0 Char) +does not!! (This a bit reminiscent of Note [mkAppTyM].) + +The solution I have adopted is simply to make `zonkEqTypes` bale out on `AppTy`. +After all, it's only supposed to be a quick hack to see if two types are already +equal; if we bale out we'll just get into the "proper" canonicaliser. + +The only tricky thing about this approach is that it relies on /omitting/ +code -- for the AppTy/AppTy case! Hence this Note +-} + {- ********************************************************************* * * * canonicaliseEquality ===================================== docs/users_guide/conf.py ===================================== @@ -35,8 +35,6 @@ nitpick_ignore = [ ("envvar", "TMPDIR"), ("c:type", "bool"), - - ("extension", "RelaxedPolyRec"), ] rst_prolog = """ ===================================== docs/users_guide/expected-undocumented-flags.txt ===================================== @@ -14,7 +14,6 @@ -XPolymorphicComponents -XRecordPuns -XRelaxedLayout --XRelaxedPolyRec -copy-libs-when-linking -dannot-lint -dppr-ticks ===================================== docs/users_guide/exts/doandifthenelse.rst ===================================== @@ -8,7 +8,7 @@ Do And If Then Else :since: 7.0.1 - :status: Included in :extension:`Haskell2010` + :status: Included in :extension:`GHC2024`, :extension:`GHC2021`, :extension:`Haskell2010` Allow semicolons in ``if`` expressions. ===================================== docs/users_guide/exts/relaxed_poly_rec.rst ===================================== @@ -0,0 +1,17 @@ +.. _relaxed-poly-rec: + +Generalised typing of mutually recursive bindings +------------------------------------------------- + +.. extension:: RelaxedPolyRec + :shortdesc: Generalised typing of mutually recursive bindings. + + :since: 6.8.1 + + :status: Included in :extension:`GHC2024`, :extension:`GHC2021`, :extension:`Haskell2010` + +See :ref:`infelicities-recursive-groups` for a description of this extension. +This is a long-standing GHC extension. Around the time of GHC 7.6.3, this +extension became required as part of a typechecker refactoring. +The ``-XRelaxedPolyRec`` flag is now deprecated (since the feature is always +enabled) and may be removed at some future time. ===================================== docs/users_guide/exts/types.rst ===================================== @@ -30,3 +30,4 @@ Types type_errors defer_type_errors roles + relaxed_poly_rec ===================================== testsuite/tests/numeric/should_compile/T26229.hs ===================================== @@ -0,0 +1,12 @@ +{-# LANGUAGE NegativeLiterals #-} + +module T26229 where + +sqrte2pqiq :: (Floating a, Ord a) => a -> a -> a +sqrte2pqiq e qiq -- = sqrt (e*e + qiq) + | e < - 1.5097698010472593e153 = -(qiq/e) - e + | e < 5.582399551122541e57 = sqrt (e*e + qiq) -- test Infinity# + | e < -5.582399551122541e57 = -sqrt (e*e + qiq) -- test -Infinity# + | otherwise = (qiq/e) + e +{-# SPECIALIZE sqrte2pqiq :: Double -> Double -> Double #-} +{-# SPECIALIZE sqrte2pqiq :: Float -> Float -> Float #-} ===================================== testsuite/tests/numeric/should_compile/all.T ===================================== @@ -22,3 +22,4 @@ test('T15547', normal, compile, ['-ddump-simpl -O -dsuppress-all -dno-typeable-b test('T23019', normal, compile, ['-O']) test('T23907', [ when(wordsize(32), expect_broken(23908))], compile, ['-ddump-simpl -O2 -dsuppress-all -dno-typeable-binds -dsuppress-uniques']) test('T24331', normal, compile, ['-O -ddump-simpl -dsuppress-all -dsuppress-uniques -dno-typeable-binds']) +test('T26229', normal, compile, ['-O2']) ===================================== testsuite/tests/partial-sigs/should_compile/T26256.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE GHC2021 #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PartialTypeSignatures #-} + +module M (go) where + +import Data.Kind + +type Apply :: (Type -> Type) -> Type +data Apply m + +type (:->) :: Type -> Type -> Type +type family (:->) where (:->) = (->) + +f :: forall (k :: Type -> Type -> Type) (m :: Type -> Type). + k Int (m Char) -> k Bool (Apply m) +f = f + +x :: Int :-> Maybe Char +x = x + +go :: Bool -> _ _ +go = f x ===================================== testsuite/tests/partial-sigs/should_compile/T26256.stderr ===================================== @@ -0,0 +1,8 @@ +T26256.hs:22:15: warning: [GHC-88464] [-Wpartial-type-signatures (in -Wdefault)] + • Found type wildcard ‘_’ standing for ‘Apply :: (* -> *) -> *’ + • In the type signature: go :: Bool -> _ _ + +T26256.hs:22:17: warning: [GHC-88464] [-Wpartial-type-signatures (in -Wdefault)] + • Found type wildcard ‘_’ standing for ‘Maybe :: * -> *’ + • In the first argument of ‘_’, namely ‘_’ + In the type signature: go :: Bool -> _ _ ===================================== testsuite/tests/partial-sigs/should_compile/all.T ===================================== @@ -108,3 +108,4 @@ test('T21667', normal, compile, ['']) test('T22065', normal, compile, ['']) test('T16152', normal, compile, ['']) test('T20076', expect_broken(20076), compile, ['']) +test('T26256', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_compile/T26256a.hs ===================================== @@ -0,0 +1,19 @@ +{-# LANGUAGE GHC2021 #-} +{-# LANGUAGE TypeFamilies #-} + +module T26256 (go) where + +import Data.Kind + +class Cat k where (<<<) :: k a b -> k x a -> k x b +instance Cat (->) where (<<<) = (.) +class Pro k p where pro :: k a b s t -> p a b -> p s t +data Hiding o a b s t = forall e. Hiding (s -> o e a) +newtype Apply e a = Apply (e a) + +type (:->) :: Type -> Type -> Type +type family (:->) where + (:->) = (->) + +go :: (Pro (Hiding Apply) p) => (s :-> e a) -> p a b -> p s t +go sea = pro (Hiding (Apply <<< sea)) ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -940,3 +940,4 @@ test('T26020', normal, compile, ['']) test('T26020a', [extra_files(['T26020a_help.hs'])], multimod_compile, ['T26020a', '-v0']) test('T25992', normal, compile, ['']) test('T14010', normal, compile, ['']) +test('T26256a', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/464c54b8490fbb21049cc184bd1fac7... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/464c54b8490fbb21049cc184bd1fac7... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)