[Git][ghc/ghc][master] Make flip representation polymorphic, similar to ($) and (&)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sun Jun 16 21:58:07 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00
Make flip representation polymorphic, similar to ($) and (&)

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245

- - - - -


10 changed files:

- libraries/base/changelog.md
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/typecheck/should_compile/abstract_refinement_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/holes.stderr
- testsuite/tests/typecheck/should_compile/holes3.stderr
- testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr


Changes:

=====================================
libraries/base/changelog.md
=====================================
@@ -3,6 +3,7 @@
 ## 4.21.0.0 *TBA*
   * Add the `MonadFix` instance for `(,) a`, similar to the one for `Writer a` ([CLC proposal #238](https://github.com/haskell/core-libraries-committee/issues/238))
   * Improve `toInteger :: Word32 -> Integer` on 64-bit platforms ([CLC proposal #259](https://github.com/haskell/core-libraries-committee/issues/259))
+  * Make `flip` representation polymorphic ([CLC proposal #245](https://github.com/haskell/core-libraries-committee/issues/245))
   * The `HasField` class now supports representation polymorphism ([CLC proposal #194](https://github.com/haskell/core-libraries-committee/issues/194))
   * Make `read` accept binary integer notation ([CLC proposal #177](https://github.com/haskell/core-libraries-committee/issues/177))
   * Improve the performance of `Data.List.sort` using an improved merging strategy. Instead of `compare`, `sort` now uses `(>)` which may break *malformed* `Ord` instances ([CLC proposal #236](https://github.com/haskell/core-libraries-committee/issues/236))


=====================================
libraries/ghc-internal/src/GHC/Internal/Base.hs
=====================================
@@ -2184,7 +2184,7 @@ const x _               =  x
 --
 -- >>> let (.>) = flip (.) in (+1) .> show $ 5
 -- "6"
-flip                    :: (a -> b -> c) -> b -> a -> c
+flip :: forall repc a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
 flip f x y              =  f y x
 
 -- Note: Before base-4.19, ($) was not representation polymorphic


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -1095,7 +1095,7 @@ module Data.Function where
   applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a
   const :: forall a b. a -> b -> a
   fix :: forall a. (a -> a) -> a
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   id :: forall a. a -> a
   on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
 
@@ -3714,7 +3714,7 @@ module GHC.Base where
   fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
   fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #)
   finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #)
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   float2Double# :: Float# -> Double#
   float2Int# :: Float# -> Int#
   fmaddDouble# :: Double# -> Double# -> Double# -> Double#
@@ -10127,7 +10127,7 @@ module Prelude where
   errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a
   even :: forall a. Integral a => a -> Bool
   filter :: forall a. (a -> Bool) -> [a] -> [a]
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   fromIntegral :: forall a b. (Integral a, Num b) => a -> b
   fst :: forall a b. (a, b) -> a
   gcd :: forall a. Integral a => a -> a -> a


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -1095,7 +1095,7 @@ module Data.Function where
   applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a
   const :: forall a b. a -> b -> a
   fix :: forall a. (a -> a) -> a
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   id :: forall a. a -> a
   on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
 
@@ -3714,7 +3714,7 @@ module GHC.Base where
   fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
   fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #)
   finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #)
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   float2Double# :: Float# -> Double#
   float2Int# :: Float# -> Int#
   fmaddDouble# :: Double# -> Double# -> Double# -> Double#
@@ -13169,7 +13169,7 @@ module Prelude where
   errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a
   even :: forall a. Integral a => a -> Bool
   filter :: forall a. (a -> Bool) -> [a] -> [a]
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   fromIntegral :: forall a b. (Integral a, Num b) => a -> b
   fst :: forall a b. (a, b) -> a
   gcd :: forall a. Integral a => a -> a -> a


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -1095,7 +1095,7 @@ module Data.Function where
   applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a
   const :: forall a b. a -> b -> a
   fix :: forall a. (a -> a) -> a
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   id :: forall a. a -> a
   on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
 
@@ -3717,7 +3717,7 @@ module GHC.Base where
   fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
   fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #)
   finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #)
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   float2Double# :: Float# -> Double#
   float2Int# :: Float# -> Int#
   fmaddDouble# :: Double# -> Double# -> Double# -> Double#
@@ -10413,7 +10413,7 @@ module Prelude where
   errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a
   even :: forall a. Integral a => a -> Bool
   filter :: forall a. (a -> Bool) -> [a] -> [a]
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   fromIntegral :: forall a b. (Integral a, Num b) => a -> b
   fst :: forall a b. (a, b) -> a
   gcd :: forall a. Integral a => a -> a -> a


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -1095,7 +1095,7 @@ module Data.Function where
   applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a
   const :: forall a b. a -> b -> a
   fix :: forall a. (a -> a) -> a
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   id :: forall a. a -> a
   on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
 
@@ -3714,7 +3714,7 @@ module GHC.Base where
   fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #)
   fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #)
   finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #)
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   float2Double# :: Float# -> Double#
   float2Int# :: Float# -> Int#
   fmaddDouble# :: Double# -> Double# -> Double# -> Double#
@@ -10127,7 +10127,7 @@ module Prelude where
   errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a
   even :: forall a. Integral a => a -> Bool
   filter :: forall a. (a -> Bool) -> [a] -> [a]
-  flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+  flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c
   fromIntegral :: forall a b. (Integral a, Num b) => a -> b
   fst :: forall a b. (a, b) -> a
   gcd :: forall a. Integral a => a -> a -> a


=====================================
testsuite/tests/typecheck/should_compile/abstract_refinement_hole_fits.stderr
=====================================
@@ -39,14 +39,14 @@ abstract_refinement_hole_fits.hs:4:5: warning: [GHC-88464] [-Wtyped-holes (in -W
           where const :: forall a b. a -> b -> a
         (.) (_ :: b1 -> Integer) (_ :: [Integer] -> b1)
           where (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c
-        flip (_ :: [Integer] -> t0 -> Integer) (_ :: t0)
-          where flip :: forall a b c. (a -> b -> c) -> b -> a -> c
         curry (_ :: (t0, [Integer]) -> Integer) (_ :: t0)
           where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c
         ($) (_ :: [Integer] -> Integer)
           where ($) :: forall a b. (a -> b) -> a -> b
         ($!) (_ :: [Integer] -> Integer)
           where ($!) :: forall a b. (a -> b) -> a -> b
+        flip (_ :: [Integer] -> t0 -> Integer) (_ :: t0)
+          where flip :: forall a b c. (a -> b -> c) -> b -> a -> c
         id (_ :: t0 -> [Integer] -> Integer) (_ :: t0)
           where id :: forall a. a -> a
         head (_ :: [t0 -> [Integer] -> Integer]) (_ :: t0)
@@ -160,22 +160,22 @@ abstract_refinement_hole_fits.hs:7:5: warning: [GHC-88464] [-Wtyped-holes (in -W
           where foldr :: forall (t :: * -> *) a b.
                          Foldable t =>
                          (a -> b -> b) -> b -> t a -> b
-        flip (_ :: [Integer] -> Integer -> Integer)
-          where flip :: forall a b c. (a -> b -> c) -> b -> a -> c
         curry (_ :: (Integer, [Integer]) -> Integer)
           where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c
         const (_ :: [Integer] -> Integer)
           where const :: forall a b. a -> b -> a
+        flip (_ :: [Integer] -> Integer -> Integer)
+          where flip :: forall a b c. (a -> b -> c) -> b -> a -> c
         (.) (_ :: b1 -> [Integer] -> Integer) (_ :: Integer -> b1)
           where (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c
-        flip (_ :: Integer -> t0 -> [Integer] -> Integer) (_ :: t0)
-          where flip :: forall a b c. (a -> b -> c) -> b -> a -> c
         curry (_ :: (t0, Integer) -> [Integer] -> Integer) (_ :: t0)
           where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c
         ($) (_ :: Integer -> [Integer] -> Integer)
           where ($) :: forall a b. (a -> b) -> a -> b
         ($!) (_ :: Integer -> [Integer] -> Integer)
           where ($!) :: forall a b. (a -> b) -> a -> b
+        flip (_ :: Integer -> t0 -> [Integer] -> Integer) (_ :: t0)
+          where flip :: forall a b c. (a -> b -> c) -> b -> a -> c
         id (_ :: t0 -> Integer -> [Integer] -> Integer) (_ :: t0)
           where id :: forall a. a -> a
         head (_ :: [t0 -> Integer -> [Integer] -> Integer]) (_ :: t0)


=====================================
testsuite/tests/typecheck/should_compile/holes.stderr
=====================================
@@ -194,7 +194,6 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
         seq :: forall a b. a -> b -> b
         ($!) :: forall a b. (a -> b) -> a -> b
         (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c
-        flip :: forall a b c. (a -> b -> c) -> b -> a -> c
         either :: forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
         curry :: forall a b c. ((a, b) -> c) -> a -> b -> c
         uncurry :: forall a b c. (a -> b -> c) -> (a, b) -> c
@@ -202,5 +201,6 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
         zip3 :: forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
         zipWith :: forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
         ($) :: forall a b. (a -> b) -> a -> b
+        flip :: forall a b c. (a -> b -> c) -> b -> a -> c
         zipWith3 :: forall a b c d.
                     (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]


=====================================
testsuite/tests/typecheck/should_compile/holes3.stderr
=====================================
@@ -197,7 +197,6 @@ holes3.hs:11:15: error: [GHC-88464]
         seq :: forall a b. a -> b -> b
         ($!) :: forall a b. (a -> b) -> a -> b
         (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c
-        flip :: forall a b c. (a -> b -> c) -> b -> a -> c
         either :: forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
         curry :: forall a b c. ((a, b) -> c) -> a -> b -> c
         uncurry :: forall a b c. (a -> b -> c) -> (a, b) -> c
@@ -205,5 +204,6 @@ holes3.hs:11:15: error: [GHC-88464]
         zip3 :: forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
         zipWith :: forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
         ($) :: forall a b. (a -> b) -> a -> b
+        flip :: forall a b c. (a -> b -> c) -> b -> a -> c
         zipWith3 :: forall a b c d.
                     (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]


=====================================
testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr
=====================================
@@ -172,11 +172,6 @@ refinement_hole_fits.hs:7:5: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           with foldr @[] @Integer @Integer
           (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30
            (and originally defined in ‘GHC.Internal.Data.Foldable’))
-        flip (_ :: [Integer] -> Integer -> Integer)
-          where flip :: forall a b c. (a -> b -> c) -> b -> a -> c
-          with flip @[Integer] @Integer @Integer
-          (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30
-           (and originally defined in ‘GHC.Internal.Base’))
         curry (_ :: (Integer, [Integer]) -> Integer)
           where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c
           with curry @Integer @[Integer] @Integer
@@ -187,6 +182,11 @@ refinement_hole_fits.hs:7:5: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
           with const @([Integer] -> Integer) @Integer
           (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30
            (and originally defined in ‘GHC.Internal.Base’))
+        flip (_ :: [Integer] -> Integer -> Integer)
+          where flip :: forall a b c. (a -> b -> c) -> b -> a -> c
+          with flip @GHC.Types.LiftedRep @[Integer] @Integer @Integer
+          (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30
+           (and originally defined in ‘GHC.Internal.Base’))
         ($) (_ :: Integer -> [Integer] -> Integer)
           where ($) :: forall a b. (a -> b) -> a -> b
           with ($) @GHC.Types.LiftedRep



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e0099721ce4b2f7f2b5ab21a75160aa212751804

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e0099721ce4b2f7f2b5ab21a75160aa212751804
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/20240616/b83e2c4f/attachment-0001.html>


More information about the ghc-commits mailing list