
#10362: Make tuple constraints into a class -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- At the moment GHC treats tuple constraints specially. If you grep for `TuplePred` you'll see this. But the special treatment is strange; see the confusion between constraint tuples and ordinary tuples in #9858. But I now realise that we can sweep away all this nonsense. Suppose we declare {{{ module GHC.Classes where class (c1, c2) => (,) c1 c2 instance (c1, c2) => (,) c1 c2 class (c1, c2, c3) => (,) c1 c2 c3 instance (c1, c2, c3) => (,) c1 c2 c3 }}} and so on. (This is analogous the tuple data type declarations in `GHC.Tuple`.) Notice that: * `GHC.Classes,(,)` is a class, of kind `Constraint -> Constraint -> Constraint`. quite distinct from `GHC.Tuple.(,)`, whose kind is `* -> * -> *`. * `GHC.Classes.(,)` is a perfectly ordinary class, with no methods and two superclasses. * So all the usual superclass stuff applies. * If you have a given `Ord a` then you have a given `Eq a` (its superclass). Similarly if you have a given `(,) c1 c2` then you also have given `c1` and `given `c2`. * If you want to construct a dictionary of type `Ord a` (a "wanted"), you must supply a dictionary of type `Eq a`. Similarly, if you want to construct a dictionary of type `(,) c1 c2` then you must supply `c1` and `c2`. * I have written `(,) c1 c2` to stress that there is a class `GHC.Classes.(,)`, but we'll also allow the concrete syntax `(c1,c2)` instead. * Nevertheless the syntactic form `(c1, c2) => blah` is just sugar for `c1 => c2 => blah` (a type with two, curried constraints); it does not stand a type with a single constraint. Otherwise the instance {{{ instance (c1,c2) => (c1,c2) }}} would be the identity function! The key thing is that, aside from special syntax, `(,)` is a perfectly ordinary class, so we can simply delete all the special treatment of `TuplePred`. (Implicit parameters are also treated as a special class, incidentally.) There should be no user-visible effects. But I think it would cure the worst aspects of #10359, as well as cleaning up `TypeRep` confusion. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10362 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler