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
-
6c956af3
by J. Ryan Stinnett at 2025-08-10T22:21:42-04:00
-
6dc420b1
by J. Ryan Stinnett at 2025-08-10T22:21:42-04:00
-
0927bda0
by Simon Peyton Jones at 2025-08-11T03:30:50-04:00
-
e7755f73
by Zubin Duggal at 2025-08-11T03:30:51-04:00
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:
... | ... | @@ -478,7 +478,7 @@ opsysVariables _ (Windows {}) = mconcat |
478 | 478 | , "LANG" =: "en_US.UTF-8"
|
479 | 479 | , "CABAL_INSTALL_VERSION" =: "3.10.2.0"
|
480 | 480 | , "HADRIAN_ARGS" =: "--docs=no-sphinx-pdfs"
|
481 | - , "GHC_VERSION" =: "9.6.4"
|
|
481 | + , "GHC_VERSION" =: "9.10.1"
|
|
482 | 482 | ]
|
483 | 483 | opsysVariables _ _ = mempty
|
484 | 484 |
... | ... | @@ -3698,7 +3698,7 @@ |
3698 | 3698 | "BUILD_FLAVOUR": "validate",
|
3699 | 3699 | "CABAL_INSTALL_VERSION": "3.10.2.0",
|
3700 | 3700 | "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
3701 | - "GHC_VERSION": "9.6.4",
|
|
3701 | + "GHC_VERSION": "9.10.1",
|
|
3702 | 3702 | "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
|
3703 | 3703 | "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
3704 | 3704 | "LANG": "en_US.UTF-8",
|
... | ... | @@ -3761,7 +3761,7 @@ |
3761 | 3761 | "BUILD_FLAVOUR": "validate",
|
3762 | 3762 | "CABAL_INSTALL_VERSION": "3.10.2.0",
|
3763 | 3763 | "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
3764 | - "GHC_VERSION": "9.6.4",
|
|
3764 | + "GHC_VERSION": "9.10.1",
|
|
3765 | 3765 | "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
|
3766 | 3766 | "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
3767 | 3767 | "LANG": "en_US.UTF-8",
|
... | ... | @@ -5579,7 +5579,7 @@ |
5579 | 5579 | "BUILD_FLAVOUR": "release",
|
5580 | 5580 | "CABAL_INSTALL_VERSION": "3.10.2.0",
|
5581 | 5581 | "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
5582 | - "GHC_VERSION": "9.6.4",
|
|
5582 | + "GHC_VERSION": "9.10.1",
|
|
5583 | 5583 | "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
|
5584 | 5584 | "IGNORE_PERF_FAILURES": "all",
|
5585 | 5585 | "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
... | ... | @@ -5643,7 +5643,7 @@ |
5643 | 5643 | "BUILD_FLAVOUR": "release",
|
5644 | 5644 | "CABAL_INSTALL_VERSION": "3.10.2.0",
|
5645 | 5645 | "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
5646 | - "GHC_VERSION": "9.6.4",
|
|
5646 | + "GHC_VERSION": "9.10.1",
|
|
5647 | 5647 | "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
|
5648 | 5648 | "IGNORE_PERF_FAILURES": "all",
|
5649 | 5649 | "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
... | ... | @@ -7982,7 +7982,7 @@ |
7982 | 7982 | "BUILD_FLAVOUR": "validate",
|
7983 | 7983 | "CABAL_INSTALL_VERSION": "3.10.2.0",
|
7984 | 7984 | "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
7985 | - "GHC_VERSION": "9.6.4",
|
|
7985 | + "GHC_VERSION": "9.10.1",
|
|
7986 | 7986 | "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
|
7987 | 7987 | "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
7988 | 7988 | "LANG": "en_US.UTF-8",
|
... | ... | @@ -8044,7 +8044,7 @@ |
8044 | 8044 | "BUILD_FLAVOUR": "validate",
|
8045 | 8045 | "CABAL_INSTALL_VERSION": "3.10.2.0",
|
8046 | 8046 | "CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
8047 | - "GHC_VERSION": "9.6.4",
|
|
8047 | + "GHC_VERSION": "9.10.1",
|
|
8048 | 8048 | "HADRIAN_ARGS": "--docs=no-sphinx-pdfs",
|
8049 | 8049 | "INSTALL_CONFIGURE_ARGS": "--enable-strict-ghc-toolchain-check",
|
8050 | 8050 | "LANG": "en_US.UTF-8",
|
... | ... | @@ -29,6 +29,7 @@ import GHC.Utils.Word64 (truncateWord64ToWord32) |
29 | 29 | import Control.Arrow (first, second)
|
30 | 30 | import Data.List.NonEmpty (NonEmpty (..))
|
31 | 31 | import qualified Data.List.NonEmpty as NE
|
32 | +import GHC.Real (infinity,notANumber)
|
|
32 | 33 | |
33 | 34 | -- -----------------------------------------------------------------------------
|
34 | 35 | -- Eliminate common blocks
|
... | ... | @@ -167,7 +168,12 @@ hash_block block = |
167 | 168 | |
168 | 169 | hash_lit :: CmmLit -> Word32
|
169 | 170 | hash_lit (CmmInt i _) = fromInteger i
|
170 | - hash_lit (CmmFloat r _) = truncate r
|
|
171 | + hash_lit (CmmFloat r _)
|
|
172 | + -- handle these special cases as `truncate` fails on non-fractional numbers (#26229)
|
|
173 | + | r == infinity = 9999999
|
|
174 | + | r == -infinity = 9999998
|
|
175 | + | r == notANumber = 6666666
|
|
176 | + | otherwise = truncate r
|
|
171 | 177 | hash_lit (CmmVec ls) = hash_list hash_lit ls
|
172 | 178 | hash_lit (CmmLabel _) = 119 -- ugh
|
173 | 179 | hash_lit (CmmLabelOff _ i) = cvt $ 199 + i
|
... | ... | @@ -197,12 +197,8 @@ zonkEqTypes ev eq_rel ty1 ty2 |
197 | 197 | then tycon tc1 tys1 tys2
|
198 | 198 | else bale_out ty1 ty2
|
199 | 199 | |
200 | - go ty1 ty2
|
|
201 | - | Just (ty1a, ty1b) <- tcSplitAppTyNoView_maybe ty1
|
|
202 | - , Just (ty2a, ty2b) <- tcSplitAppTyNoView_maybe ty2
|
|
203 | - = do { res_a <- go ty1a ty2a
|
|
204 | - ; res_b <- go ty1b ty2b
|
|
205 | - ; return $ combine_rev mkAppTy res_b res_a }
|
|
200 | + -- If you are temppted to add a case for AppTy/AppTy, be careful
|
|
201 | + -- See Note [zonkEqTypes and the PKTI]
|
|
206 | 202 | |
207 | 203 | go ty1@(LitTy lit1) (LitTy lit2)
|
208 | 204 | | lit1 == lit2
|
... | ... | @@ -278,6 +274,32 @@ zonkEqTypes ev eq_rel ty1 ty2 |
278 | 274 | combine_rev f (Right tys) (Right ty) = Right (f ty tys)
|
279 | 275 | |
280 | 276 | |
277 | +{- Note [zonkEqTypes and the PKTI]
|
|
278 | +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
279 | +Because `zonkEqTypes` does /partial/ zonking, we need to be very careful
|
|
280 | +to maintain the Purely Kinded Type Invariant: see GHC.Tc.Gen/HsType
|
|
281 | +HsNote [The Purely Kinded Type Invariant (PKTI)].
|
|
282 | + |
|
283 | +In #26256 we try to solve this equality constraint:
|
|
284 | + Int :-> Maybe Char ~# k0 Int (m0 Char)
|
|
285 | +where m0 and k0 are unification variables, and
|
|
286 | + m0 :: Type -> Type
|
|
287 | +It happens that m0 was already unified
|
|
288 | + m0 := (w0 :: kappa)
|
|
289 | +where kappa is another unification variable that is also already unified:
|
|
290 | + kappa := Type->Type.
|
|
291 | +So the original type satisifed the PKTI, but a partially-zonked form
|
|
292 | + k0 Int (w0 Char)
|
|
293 | +does not!! (This a bit reminiscent of Note [mkAppTyM].)
|
|
294 | + |
|
295 | +The solution I have adopted is simply to make `zonkEqTypes` bale out on `AppTy`.
|
|
296 | +After all, it's only supposed to be a quick hack to see if two types are already
|
|
297 | +equal; if we bale out we'll just get into the "proper" canonicaliser.
|
|
298 | + |
|
299 | +The only tricky thing about this approach is that it relies on /omitting/
|
|
300 | +code -- for the AppTy/AppTy case! Hence this Note
|
|
301 | +-}
|
|
302 | + |
|
281 | 303 | {- *********************************************************************
|
282 | 304 | * *
|
283 | 305 | * canonicaliseEquality
|
... | ... | @@ -35,8 +35,6 @@ nitpick_ignore = [ |
35 | 35 | ("envvar", "TMPDIR"),
|
36 | 36 | |
37 | 37 | ("c:type", "bool"),
|
38 | - |
|
39 | - ("extension", "RelaxedPolyRec"),
|
|
40 | 38 | ]
|
41 | 39 | |
42 | 40 | rst_prolog = """
|
... | ... | @@ -14,7 +14,6 @@ |
14 | 14 | -XPolymorphicComponents
|
15 | 15 | -XRecordPuns
|
16 | 16 | -XRelaxedLayout
|
17 | --XRelaxedPolyRec
|
|
18 | 17 | -copy-libs-when-linking
|
19 | 18 | -dannot-lint
|
20 | 19 | -dppr-ticks
|
... | ... | @@ -8,7 +8,7 @@ Do And If Then Else |
8 | 8 | |
9 | 9 | :since: 7.0.1
|
10 | 10 | |
11 | - :status: Included in :extension:`Haskell2010`
|
|
11 | + :status: Included in :extension:`GHC2024`, :extension:`GHC2021`, :extension:`Haskell2010`
|
|
12 | 12 | |
13 | 13 | Allow semicolons in ``if`` expressions.
|
14 | 14 |
1 | +.. _relaxed-poly-rec:
|
|
2 | + |
|
3 | +Generalised typing of mutually recursive bindings
|
|
4 | +-------------------------------------------------
|
|
5 | + |
|
6 | +.. extension:: RelaxedPolyRec
|
|
7 | + :shortdesc: Generalised typing of mutually recursive bindings.
|
|
8 | + |
|
9 | + :since: 6.8.1
|
|
10 | + |
|
11 | + :status: Included in :extension:`GHC2024`, :extension:`GHC2021`, :extension:`Haskell2010`
|
|
12 | + |
|
13 | +See :ref:`infelicities-recursive-groups` for a description of this extension.
|
|
14 | +This is a long-standing GHC extension. Around the time of GHC 7.6.3, this
|
|
15 | +extension became required as part of a typechecker refactoring.
|
|
16 | +The ``-XRelaxedPolyRec`` flag is now deprecated (since the feature is always
|
|
17 | +enabled) and may be removed at some future time. |
... | ... | @@ -30,3 +30,4 @@ Types |
30 | 30 | type_errors
|
31 | 31 | defer_type_errors
|
32 | 32 | roles
|
33 | + relaxed_poly_rec |
1 | +{-# LANGUAGE NegativeLiterals #-}
|
|
2 | + |
|
3 | +module T26229 where
|
|
4 | + |
|
5 | +sqrte2pqiq :: (Floating a, Ord a) => a -> a -> a
|
|
6 | +sqrte2pqiq e qiq -- = sqrt (e*e + qiq)
|
|
7 | + | e < - 1.5097698010472593e153 = -(qiq/e) - e
|
|
8 | + | e < 5.582399551122541e57 = sqrt (e*e + qiq) -- test Infinity#
|
|
9 | + | e < -5.582399551122541e57 = -sqrt (e*e + qiq) -- test -Infinity#
|
|
10 | + | otherwise = (qiq/e) + e
|
|
11 | +{-# SPECIALIZE sqrte2pqiq :: Double -> Double -> Double #-}
|
|
12 | +{-# SPECIALIZE sqrte2pqiq :: Float -> Float -> Float #-} |
... | ... | @@ -22,3 +22,4 @@ test('T15547', normal, compile, ['-ddump-simpl -O -dsuppress-all -dno-typeable-b |
22 | 22 | test('T23019', normal, compile, ['-O'])
|
23 | 23 | test('T23907', [ when(wordsize(32), expect_broken(23908))], compile, ['-ddump-simpl -O2 -dsuppress-all -dno-typeable-binds -dsuppress-uniques'])
|
24 | 24 | test('T24331', normal, compile, ['-O -ddump-simpl -dsuppress-all -dsuppress-uniques -dno-typeable-binds'])
|
25 | +test('T26229', normal, compile, ['-O2']) |
1 | +{-# LANGUAGE GHC2021 #-}
|
|
2 | +{-# LANGUAGE TypeFamilies #-}
|
|
3 | +{-# LANGUAGE PartialTypeSignatures #-}
|
|
4 | + |
|
5 | +module M (go) where
|
|
6 | + |
|
7 | +import Data.Kind
|
|
8 | + |
|
9 | +type Apply :: (Type -> Type) -> Type
|
|
10 | +data Apply m
|
|
11 | + |
|
12 | +type (:->) :: Type -> Type -> Type
|
|
13 | +type family (:->) where (:->) = (->)
|
|
14 | + |
|
15 | +f :: forall (k :: Type -> Type -> Type) (m :: Type -> Type).
|
|
16 | + k Int (m Char) -> k Bool (Apply m)
|
|
17 | +f = f
|
|
18 | + |
|
19 | +x :: Int :-> Maybe Char
|
|
20 | +x = x
|
|
21 | + |
|
22 | +go :: Bool -> _ _
|
|
23 | +go = f x |
1 | +T26256.hs:22:15: warning: [GHC-88464] [-Wpartial-type-signatures (in -Wdefault)]
|
|
2 | + • Found type wildcard ‘_’ standing for ‘Apply :: (* -> *) -> *’
|
|
3 | + • In the type signature: go :: Bool -> _ _
|
|
4 | + |
|
5 | +T26256.hs:22:17: warning: [GHC-88464] [-Wpartial-type-signatures (in -Wdefault)]
|
|
6 | + • Found type wildcard ‘_’ standing for ‘Maybe :: * -> *’
|
|
7 | + • In the first argument of ‘_’, namely ‘_’
|
|
8 | + In the type signature: go :: Bool -> _ _ |
... | ... | @@ -108,3 +108,4 @@ test('T21667', normal, compile, ['']) |
108 | 108 | test('T22065', normal, compile, [''])
|
109 | 109 | test('T16152', normal, compile, [''])
|
110 | 110 | test('T20076', expect_broken(20076), compile, [''])
|
111 | +test('T26256', normal, compile, ['']) |
1 | +{-# LANGUAGE GHC2021 #-}
|
|
2 | +{-# LANGUAGE TypeFamilies #-}
|
|
3 | + |
|
4 | +module T26256 (go) where
|
|
5 | + |
|
6 | +import Data.Kind
|
|
7 | + |
|
8 | +class Cat k where (<<<) :: k a b -> k x a -> k x b
|
|
9 | +instance Cat (->) where (<<<) = (.)
|
|
10 | +class Pro k p where pro :: k a b s t -> p a b -> p s t
|
|
11 | +data Hiding o a b s t = forall e. Hiding (s -> o e a)
|
|
12 | +newtype Apply e a = Apply (e a)
|
|
13 | + |
|
14 | +type (:->) :: Type -> Type -> Type
|
|
15 | +type family (:->) where
|
|
16 | + (:->) = (->)
|
|
17 | + |
|
18 | +go :: (Pro (Hiding Apply) p) => (s :-> e a) -> p a b -> p s t
|
|
19 | +go sea = pro (Hiding (Apply <<< sea)) |
... | ... | @@ -940,3 +940,4 @@ test('T26020', normal, compile, ['']) |
940 | 940 | test('T26020a', [extra_files(['T26020a_help.hs'])], multimod_compile, ['T26020a', '-v0'])
|
941 | 941 | test('T25992', normal, compile, [''])
|
942 | 942 | test('T14010', normal, compile, [''])
|
943 | +test('T26256a', normal, compile, ['']) |