[Git][ghc/ghc][master] Added explicit fixity to (~).
Marge Bot
gitlab at gitlab.haskell.org
Thu Sep 17 12:49:59 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00
Added explicit fixity to (~).
Solves #18252
- - - - -
7 changed files:
- libraries/ghc-prim/GHC/Types.hs
- libraries/ghc-prim/changelog.md
- testsuite/tests/ghci/T18060/T18060.stdout
- testsuite/tests/ghci/scripts/T10059.stdout
- + testsuite/tests/typecheck/should_compile/T18252.hs
- + testsuite/tests/typecheck/should_fail/T18252a.hs
- + testsuite/tests/typecheck/should_fail/T18252a.stderr
Changes:
=====================================
libraries/ghc-prim/GHC/Types.hs
=====================================
@@ -256,13 +256,20 @@ inside GHC, to change the kind and type.
-- about the difference between heterogeneous equality @~~@ and
-- homogeneous equality @~@, this is printed as @~@ unless
-- @-fprint-equality-relations@ is set.
+--
+-- In @0.7.0@, the fixity was set to @infix 4@ to match the fixity of 'Data.Type.Equality.:~~:'.
class a ~~ b
+
-- See also Note [The equality types story] in GHC.Builtin.Types.Prim
-- | Lifted, homogeneous equality. By lifted, we mean that it
-- can be bogus (deferred type error). By homogeneous, the two
-- types @a@ and @b@ must have the same kinds.
+
+-- In @0.7.0@, the fixity was set to @infix 4@ to match the fixity of 'Data.Type.Equality.:~:'.
class a ~ b
+
+infix 4 ~, ~~
-- See also Note [The equality types story] in GHC.Builtin.Types.Prim
-- | @Coercible@ is a two-parameter class that has instances for types @a@ and @b@ if
=====================================
libraries/ghc-prim/changelog.md
=====================================
@@ -24,6 +24,10 @@
interlockedExchangeAddr# :: Addr# -> Addr# -> State# s -> (# State# s, Addr# #)
interlockedExchangeInt# :: Addr# -> Int# -> State# s -> (# State# s, Int# #)
+- Add an explicit fixity for `(~)` and `(~~)`:
+
+ infix 4 ~, ~~
+
## 0.6.1 (edit as necessary)
- Shipped with GHC 8.10.1
=====================================
testsuite/tests/ghci/T18060/T18060.stdout
=====================================
@@ -10,3 +10,4 @@ instance Semigroup b => Semigroup (a -> b) -- Defined in ‘GHC.Base’
type (~) :: forall k. k -> k -> Constraint
class (a ~ b) => (~) a b
-- Defined in ‘GHC.Types’
+infix 4 ~
=====================================
testsuite/tests/ghci/scripts/T10059.stdout
=====================================
@@ -1,7 +1,9 @@
type (~) :: forall k. k -> k -> Constraint
class (a ~ b) => (~) a b
-- Defined in ‘GHC.Types’
+infix 4 ~
(~) :: k -> k -> Constraint
type (~) :: forall k. k -> k -> Constraint
class (a GHC.Prim.~# b) => (~) a b
-- Defined in ‘GHC.Types’
+infix 4 ~
=====================================
testsuite/tests/typecheck/should_compile/T18252.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeOperators #-}
+module T18252 where
+
+import Data.Type.Equality
+import GHC.TypeNats
+
+eq :: (1 + 2 ~ 3) :~: ((1 + 2) ~ 3)
+eq = Refl
=====================================
testsuite/tests/typecheck/should_fail/T18252a.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeOperators #-}
+module T18252a where
+
+import Data.Type.Equality
+import GHC.TypeNats
+
+eq :: (a ~ b ~ c) :~: ()
+eq = Refl
=====================================
testsuite/tests/typecheck/should_fail/T18252a.stderr
=====================================
@@ -0,0 +1,4 @@
+
+T18252a.hs:8:10:
+ Precedence parsing error
+ cannot mix ‘~’ [infix 4] and ‘~’ [infix 4] in the same infix expression
\ No newline at end of file
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c94c81629ac9159775b8b70baf2c635f0331708
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c94c81629ac9159775b8b70baf2c635f0331708
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/20200917/c5a8151d/attachment-0001.html>
More information about the ghc-commits
mailing list