[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Add heqT, a kind-heterogeneous variant of heq
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Mon Dec 12 16:32:36 UTC 2022
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
b3e98a92 by Oleg Grenrus at 2022-12-11T12:26:17-05:00
Add heqT, a kind-heterogeneous variant of heq
CLC proposal https://github.com/haskell/core-libraries-committee/issues/99
- - - - -
bfd7c1e6 by Bodigrim at 2022-12-11T12:26:55-05:00
Document that Bifunctor instances for tuples are lawful only up to laziness
- - - - -
c1871200 by Bryan Richter at 2022-12-12T11:32:29-05:00
Mark T21336a fragile
- - - - -
26edef7b by Matthew Pickering at 2022-12-12T11:32:30-05:00
Add test for #21476
This issues seems to have been fixed since the ticket was made, so let's
add a test and move on.
Fixes #21476
- - - - -
6 changed files:
- libraries/base/Data/Bifunctor.hs
- libraries/base/Data/Typeable.hs
- libraries/base/changelog.md
- libraries/base/tests/IO/T21336/all.T
- + testsuite/tests/simplCore/should_compile/T21476.hs
- testsuite/tests/simplCore/should_compile/all.T
Changes:
=====================================
libraries/base/Data/Bifunctor.hs
=====================================
@@ -120,8 +120,17 @@ class (forall a. Functor (p a)) => Bifunctor p where
second = bimap id
-
--- | @since 4.8.0.0
+-- | Class laws for tuples hold only up to laziness. Both
+-- 'first' 'id' and 'second' 'id' are lazier than 'id' (and 'fmap' 'id'):
+--
+-- >>> first id (undefined :: (Int, Word)) `seq` ()
+-- ()
+-- >>> second id (undefined :: (Int, Word)) `seq` ()
+-- ()
+-- >>> id (undefined :: (Int, Word)) `seq` ()
+-- *** Exception: Prelude.undefined
+--
+-- @since 4.8.0.0
instance Bifunctor (,) where
bimap f g ~(a, b) = (f a, g b)
=====================================
libraries/base/Data/Typeable.hs
=====================================
@@ -4,6 +4,7 @@
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Trustworthy #-}
+{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
-----------------------------------------------------------------------------
@@ -56,6 +57,7 @@ module Data.Typeable
-- * Type-safe cast
, cast
, eqT
+ , heqT
, gcast -- a generalisation of cast
-- * Generalized casts for higher-order kinds
@@ -135,8 +137,14 @@ cast x
-- @since 4.7.0.0
eqT :: forall a b. (Typeable a, Typeable b) => Maybe (a :~: b)
eqT
- | Just HRefl <- ta `I.eqTypeRep` tb = Just Refl
- | otherwise = Nothing
+ | Just HRefl <- heqT @a @b = Just Refl
+ | otherwise = Nothing
+
+-- | Extract a witness of heterogeneous equality of two types
+--
+-- @since 4.18.0.0
+heqT :: forall a b. (Typeable a, Typeable b) => Maybe (a :~~: b)
+heqT = ta `I.eqTypeRep` tb
where
ta = I.typeRep :: I.TypeRep a
tb = I.typeRep :: I.TypeRep b
=====================================
libraries/base/changelog.md
=====================================
@@ -57,6 +57,7 @@
of individually allocated pointers as well as freeing each one of them when
freeing a `Pool`. (#14762) (#18338)
* `Type.Reflection.Unsafe` is now marked as unsafe.
+ * Add `Data.Typeable.heqT`, a kind-heterogeneous version of `Data.Typeable.eqT`.
## 4.17.0.0 *August 2022*
=====================================
libraries/base/tests/IO/T21336/all.T
=====================================
@@ -1,6 +1,9 @@
# N.B. /dev/full exists on Darwin but cannot be opened, failing with -EPERM
test('T21336a',
- [unless(opsys('linux') or opsys('freebsd'), skip), js_broken(22261)],
+ [ unless(opsys('linux') or opsys('freebsd'), skip)
+ , js_broken(22261)
+ , fragile(22022)
+ ],
compile_and_run, [''])
test('T21336b',
[unless(opsys('linux') or opsys('freebsd'), skip), js_broken(22352)],
=====================================
testsuite/tests/simplCore/should_compile/T21476.hs
=====================================
@@ -0,0 +1,4 @@
+{-# LANGUAGE MagicHash #-}
+module T21476 where
+import GHC.Exts
+f = keepAlive#
=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -456,3 +456,4 @@ test('T22317', [grep_errmsg(r'ANSWER = YES') ], compile, ['-O -dinline-check m -
test('T22494', [grep_errmsg(r'case') ], compile, ['-O -ddump-simpl -dsuppress-uniques'])
test('T22491', normal, compile, ['-O2'])
+test('T21476', normal, compile, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2eedf815a9c58484dc1a27be7f508551953d7594...26edef7bde915be5481b1b42a1cbd1414538e57c
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2eedf815a9c58484dc1a27be7f508551953d7594...26edef7bde915be5481b1b42a1cbd1414538e57c
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20221212/2eb248d4/attachment-0001.html>
More information about the ghc-commits
mailing list