[GHC] #12923: MultiParamTypeClasses + ExtendedDefaultRules

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature | Status: new request | 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: -------------------------------------+------------------------------------- -XExtendedDefaultRules allows us to avoid ambiguity for unannotated numeric literals: {{{#!hs {-# LANGUAGE ExtendedDefaultRules #-} data A = A deriving Show class ToA a where toA :: a -> A instance ToA Double where toA _ = A main = print (toA 5 :: A) }}} But if we have a multi-param typeclass, -XExtendedDefaultRules doesn't help us: {{{#!hs {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} data A x = A deriving Show class ToA a x where toA :: a -> A x instance ToA Double x where toA _ = A main = print (toA 5 :: A Bool) }}} It would be really nice for an EDSL I'm working on to be able to use extended defaults here! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | 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: | -------------------------------------+------------------------------------- Description changed by amindfv: @@ -44,2 +44,3 @@ - It would be really nice for an EDSL I'm working on to be able to use - extended defaults here! + It would be really nice for an EDSL of mine to be able to use extended + defaults here! At the moment my only option has been to use incoherent + instances, which has resulted in incoherent behavior... New description: -XExtendedDefaultRules allows us to avoid ambiguity for unannotated numeric literals: {{{#!hs {-# LANGUAGE ExtendedDefaultRules #-} data A = A deriving Show class ToA a where toA :: a -> A instance ToA Double where toA _ = A main = print (toA 5 :: A) }}} But if we have a multi-param typeclass, -XExtendedDefaultRules doesn't help us: {{{#!hs {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} data A x = A deriving Show class ToA a x where toA :: a -> A x instance ToA Double x where toA _ = A main = print (toA 5 :: A Bool) }}} It would be really nice for an EDSL of mine to be able to use extended defaults here! At the moment my only option has been to use incoherent instances, which has resulted in incoherent behavior... -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | 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 simonpj): What, precisely, would you like the defaulting rule to be? Ideally, express your proposed rule(s) in the same way as [the user manual does](https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html #type-defaulting-in-ghci). Thanks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | 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 amindfv): For my needs, given the rule linked above: "All of the classes Ci are single-parameter type classes." I would relax it to say: "Only one parameter in each class Ci has kind `:: *` " so this would be a valid program... {{{#!hs class Works a (b :: Bool) where works :: a -> A b instance Works Double 'True main = print (works 5 :: A 'True) }}} ...but this would remain ambiguous: {{{#!hs class Doesnt a b where doesnt :: a -> b instance Doesnt Double Bool main = print $ doesnt 5 True }}} The defaulting rule could be relaxed more, but this seems like the smallest possible change. Additionally, this change is critical for my EDSL's coherence; a more-relaxed rule would just be nice-to-have. Thank you! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | 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): It's hard to imagine the small generalization in comment:3 doing any harm. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2816 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D2816 * milestone: => 8.2.1 Comment: Here's a quick patch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2816 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I don't think that rule will work. As the user manual page says, the list type `[] :: * -> *` is in the list of type defaults, so that higher-kinded variables can be defaulted too. See #10971. So we can't restrict to *. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2816 Wiki Page: | -------------------------------------+------------------------------------- Comment (by amindfv): Ahhh. Maybe we can say something like this?: "Only one parameter in each class Ci has kind `:: *` or `:: (->) * _` " -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2816 Wiki Page: | -------------------------------------+------------------------------------- Comment (by amindfv): By the way, to get the current code to work we need to add: ` {-# LANGUAGE KindSignatures #-} ` and ` data A (b :: Bool) = A deriving Show ` to testsuite/tests/typecheck/should_compile/T12923.hs and ` import Kind ` to compiler/typecheck/TcSimplify.hs It does regress for Foldable at the moment, as Simon predicted, but in the test case I provided it does in fact work, beautifully! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2816 Wiki Page: | -------------------------------------+------------------------------------- Comment (by amindfv): I've got both `*` and `* -> *` (test T10971a) defaulting working with: https://phabricator.haskell.org/D2822 Let me know how it looks. Thanks -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2822 Wiki Page: | -------------------------------------+------------------------------------- Changes (by amindfv): * differential: Phab:D2816 => Phab:D2822 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2822 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): This is the sort of change that the proposal process was designed to consider. That being said, this particular change is fairly small in scope and it is quite late in the 8.2 cycle. If no one else objects I would be willing to forgo the proposal and merge Phab:D2822. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2822 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The proposed new defaulting rules in the patch are: Find all the unsolved constraints. Then: * Find those of form `(C t1 ... a ... tn)`, where `C` is a class, and `a` is a type variable of kind `Type` or `(Type -> Type)`, and all the other parameters of `C` have kinds other than `Type` or `Type -> Type`. * Partition this set into groups that share a common type variable `a`. * Now default `a` (to one of the types in the default list) if * The type variable `a` appears in no other constraint outside that group * At least one of the classes `Ci` is an interactive class ("Interactive class" is defined [http://downloads.haskell.org/~ghc/master /users-guide/ghci.html#type-defaulting-in-ghci here].) This seems a bit complicated to me. What about this instead. Find all the unsolved constraints. Then: * Find those that have exactly one free type variable, and partition that subset into groups that share a common type variable `a`. * Now default `a` (to one of the types in the default list) if at least one of the classes `Ci` is an interactive class This is a bit more flexible, and a bit simpler to describe. The "just one free type variable" part is meant to avoid having to look for ''combinations'' of defaulting types that will allow the constraint to be solved. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2822 Wiki Page: | -------------------------------------+------------------------------------- Comment (by amindfv): Simon: this seems like a really elegant solution to me. Starting work on it now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2822 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): You have realised that the spec in comment:12 can be further simplified (without changing its meaning): Find all the unsolved constraints. Then: * Find those that are of form `(C a)` where `a` is a type variable, and partition those constraints into groups that share a common type variable `a`. * Keep only the groups in which at least one of the classes is an interactive class. * Now, for each remaining group G, try each type `ty` from the default- type list in turn; if setting `a = ty` would allow the constraints in G to be completely solved. If so, default `a` to `ty`. Note that any multi-parameter constraints `(D a b)` or `(D [a] Int)` do not participate in the process (either to help or to hinder); but they must of course be soluble once the defaulting process is complete. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2822 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): On Phab you comment that this program is still rejected with ambiguous variables. {{{ {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} module T12924 where import GHC.TypeLits data A (b :: [Symbol]) = A deriving Show class Works a (b :: [Symbol]) where works :: a -> A b instance Works Integer a where works _ = A addA :: A a -> A a -> A a addA A A = A test2 :: A x test2 = addA (works 5) (works 5) }}} The reason is described in `Note [ApproximateWC]` in `TcSimplify`, item (2) in that note. It arose from Trac #8155. We have a constraint {{{ forall x. () => Num alpha, Works alpha x }}} but because we carefully make the `Works alpha x` prevent the `Num alpha` float out for defaulting, for reasons described in the Note. The rule is un-documented and indeed hard to explain. I'm quite inclined to back-pedal on the fix to #8155. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2822 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): PS: you can go ahead with adding the user documentation for your patch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2822 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Turns out that back-pedaling on #8155 doesn't break #8155! So I'm going to do that. It's no documented feature, and it'll make more programs do defaulting. That leaves your tiny patch. It is no so small, and so well defined, that I think we should go ahead. Please do the user manual stuff and then we can land it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules
-------------------------------------+-------------------------------------
Reporter: amindfv | Owner:
Type: feature request | Status: patch
Priority: normal | Milestone: 8.2.1
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): Phab:D2822
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2822 Wiki Page: | -------------------------------------+------------------------------------- Comment (by amindfv): Thanks so much, Simon -- your fix for the #8155 issue will make this much easier to work with in practice! Along with the user doc updates, I've added another unit test, to ensure the behavior from the #8155 backpedal works. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: amindfv | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D2822 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK I think we are done. Please add a Note as suggested on Phab, then Ben can you land this? Thanks for being so patient with this. I think it's been worth it though: the result is much better than were we started. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12923#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12923: MultiParamTypeClasses + ExtendedDefaultRules
-------------------------------------+-------------------------------------
Reporter: amindfv | Owner: (none)
Type: feature request | Status: closed
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 8.0.1
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2822
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by bgamari):
* status: patch => closed
* resolution: => fixed
Comment:
Merged in,
{{{
commit c3bbd1afc85cd634d8d26e27bafb92cc7481667b
Author: vivid-synth
participants (1)
-
GHC