[GHC] #12447: Pretty-printing of equality `~` without parentheses

#12447: Pretty-printing of equality `~` without parentheses -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Based off on [https://github.com/ekmett/constraints/blob/master/src/Data/Constraint/Deferr... Data.Constraint.Deferrable] {{{#!hs {-# Language RankNTypes, ConstraintKinds #-} import Data.Typeable class Deferrable p where deferEither :: proxy p -> (p => r) -> Either String r instance (Typeable a, Typeable b) => Deferrable (a ~ b) where deferEither = undefined }}} `PolyKinds` aren't enabled so `deferEither @(_ ~ _)` is not enough to select the `Deferrable (a ~ b)` instance, but it is displayed without parentheses {{{ $ ghci -XTypeApplications -ignore-dot-ghci tyiS.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( tyiS.hs, interpreted ) Ok, modules loaded: Main. *Main> :t deferEither @(_ ~ _) deferEither @(_ ~ _) :: Deferrable t ~ t1 => proxy t ~ t1 -> (t ~ t1 => r) -> Either String r }}} Instead of a preferable {{{#!hs deferEither @(_ ~ _) :: Deferrable (t ~ t1) => proxy (t ~ t1) -> (t ~ t1 => r) -> Either String r }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12447 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12447: Pretty-printing of equality `~` without parentheses -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Same with {{{#!hs {-# Language KindSignatures, TypeOperators #-} import Data.Kind import Data.Type.Equality class Foo (p :: Constraint) instance Foo (a ~ b) instance Foo (a ~~ b) }}} {{{ $ ghci -ignore-dot-ghci /tmp/tOrO.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tOrO.hs, interpreted ) Ok, modules loaded: Main. *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo a ~ b -- Defined at /tmp/tOrO.hs:8:10 }}} {{{ *Main> :set -fprint-equality-relations *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo (a :: *) ~~ (b :: *) -- Defined at /tmp/tOrO.hs:8:10 }}} Should be ` {{{ *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo (a ~ b) -- Defined at /tmp/tOrO.hs:8:10 *Main> :set -fprint-equality-relations *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo ((a :: *) ~~ (b :: *)) -- Defined at /tmp/tOrO.hs:8:10 }}} ---- Is this the same as #12005, two instances are defined: {{{#!hs instance Foo (a ~ b) instance Foo (a ~~ b) }}} but only one displayed in `:info`: is the first subsumed by the latter? There is some funny business going on in the [https://hackage.haskell.org/package/base-4.9.0.0/docs/Data-Type- Equality.html#t:-126--126- definition of ‘~~’] so I don't know if those are separate instances. For example what is the difference between these two instances `↓`? {{{#!hs instance Foo (a ~ b) instance Foo ((a::Type) ~~ (b::Type)) }}} Again, only the latter is displayed: {{{#!hs *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo a ~ b -- Defined at /tmp/tOrO.hs:8:10 *Main> :set -fprint-equality-relations *Main> :i Foo class Foo (p :: Constraint) -- Defined at /tmp/tOrO.hs:6:1 instance [safe] Foo (a :: *) ~~ (b :: *) -- Defined at /tmp/tOrO.hs:8:10 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12447#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12447: Pretty-printing of equality `~` without parentheses -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): This is likely something to fix in #11660. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12447#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12447: Pretty-printing of equality `~` without parentheses
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#12447: Pretty-printing of equality `~` without parentheses -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): It appears that this was fixed in GHC 8.2.2, since now the type signature has parentheses where it didn't before: {{{ $ ghci -XTypeApplications Bug.hs GHCi, version 8.4.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Ok, one module loaded. λ> :t deferEither @(_ ~ _) deferEither @(_ ~ _) :: (Typeable w1, Typeable w2) => proxy (w1 ~ w2) -> ((w1 ~ w2) => r) -> Either String r }}} I'll unmark the test case from its current `expected_broken` state. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12447#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12447: Pretty-printing of equality `~` without parentheses
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12447: Pretty-printing of equality `~` without parentheses -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/scripts/T12447 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => ghci/scripts/T12447 * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12447#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC