[GHC] #10592: Allow cycles in class declarations

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: | Owner: MikeIzbicki | Status: new Type: feature | Milestone: request | Version: 7.10.1 Priority: normal | Operating System: Unknown/Multiple Component: Compiler | Type of failure: None/Unknown (Type checker) | Blocked By: Keywords: | Related Tickets: Architecture: | Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- In particular, I would like to have a class hierarchy that looks like: {{{ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} type family Scalar x class Field (Scalar x) => Vector x class Vector x => Field x }}} It is the case that every field is a vector, and the scalar associated with every vector is a field. But we can't currently enforce that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by adamgundry): * cc: adamgundry (added) Comment: Somewhat surprisingly, this appears to be a valid workaround: {{{ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE UndecidableInstances #-} type family Scalar x type family FieldScalar x where FieldScalar x = Field (Scalar x) class FieldScalar x => Vector x class Vector x => Field x }}} I suspect the `"Cycle in class declaration (via superclasses)"` error is a little bit too conservative. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by MikeIzbicki): Thanks! That workaround solves my immediate problem :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): See also #10318 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Hmm. I think it'd be easy to send GHC into an infinite loop using this; i.e. the current implementation is over-liberal. {{{ type instance FieldScalar x = Field x }}} Is it true that you expect `Scalar (Scalar a) ~ Scalar a)` (cf #10318). If so, you could make it better behaved by saying {{{ class (Scalar (Scalar a) ~ Scalar a, Field (Scalar a)) => Vector a class Vector x => Field x }}} This still isn't accepted but could be under comment:6 of #10318 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by MikeIzbicki): I actually tried the technique on my current code base and it did appear GHC went into an infinite loop. I didn't report it here though because I wasn't sure exactly what was going on and I haven't had a chance to look into it more fully. I'm not sure what you mean by this could be accepted with regards to comment:6 of #10318. There's a lot going on in that thread, and it's hard for me to get a good grasp of what's relevant. I basically know nothing about how type inference actually works, I'm just a big fan of using it :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): The stuff in #10318 is speculation about a possible feature. But the question remains: in your application If {{{ class (Scalar (Scalar a) ~ Scalar a, Field (Scalar a)) => Vector a class Vector x => Field x }}} was accepted by GHC, would it serve your purpose? That means that in any instance of `Vector t`, GHC will need to prove that `Scalar (Scalar t) ~ Scalar t`. Will that be true, in your application? If so, that makes the speculation in #10318 more persuasive. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by MikeIzbicki): My current implementation has constraints that look exactly like this, plus a lot more related to other aspects of the class hierarchy. So supporting this would be a necessary condition for me cyclic class declarations for me, but I can't say for sure if it would be sufficient (but my guess is probably). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations
-------------------------------------+-------------------------------------
Reporter: MikeIzbicki | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.10.1
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | 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): MikeIzbicki: OK so this is implemented! Could you give a test case, perhaps that can run? Simply accepting the above code isn't really a good test :-). Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | 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 bgamari: Old description:
In particular, I would like to have a class hierarchy that looks like:
{{{ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-}
type family Scalar x
class Field (Scalar x) => Vector x
class Vector x => Field x }}}
It is the case that every field is a vector, and the scalar associated with every vector is a field. But we can't currently enforce that.
New description: In particular, I would like to have a class hierarchy that looks like: {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} type family Scalar x class Field (Scalar x) => Vector x class Vector x => Field x }}} It is the case that every field is a vector, and the scalar associated with every vector is a field. But we can't currently enforce that. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: infoneeded Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => infoneeded -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: infoneeded Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | 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 MikeIzbicki): Awesome! I have two comments: 1. One of my use cases is very similar to the code attached below, which causes GHC to loop. The code provides an alternate class hierarchy for comparisons. One of the features of the hierarchy is that `(||)` and `(&&)` can be used directly on functions. Unfortunately, the instances for `(->)` cause GHC to loop. The instances seem like they should work to me. I'm not sure if my reasoning is faulty or if there's a bug in the implementation. 2. I believe there is an incorrect error message. If you take the code below and comment out the line `instance Boolean b => Boolean (a -> b)`, then GHC gives the error message: {{{ [1 of 1] Compiling ClassCycles ( ClassCycles.hs, ClassCycles.o ) ClassCycles.hs:1:1: error: solveWanteds: too many iterations (limit = 4) Set limit with -fsolver-iterations=n; n=0 for no limit WC {wc_simple = [W] $dBoolean_a1KZ :: Boolean (a -> fsk_a1KH) (CDictCan) [D] _ :: Boolean (a -> fsk_a1Ll) (CDictCan)} }}} But when I try to set the limit to something different, GHC complains that the flag doesn't exist: {{{ $ ~/proj/ghc/inplace/bin/ghc-stage2 ClassCycles.hs -fsolver-iterations=10 ghc-stage2: unrecognised flag: -fsolver-iterations=10 Usage: For basic information, try the `--help' option }}} ---- {{{ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableSuperClasses #-} module ClassCycles where import Prelude (Bool(True,False),Integer,Ordering) import qualified Prelude -------------------- -- class hierarchy class Boolean (Logic a) => Eq a where type Logic a :: * (==) :: a -> a -> Logic a class Eq a => POrd a where inf :: a -> a -> a class POrd a => MinBound a where minBound :: a class POrd a => Lattice a where sup :: a -> a -> a class (Lattice a, MinBound a) => Bounded a where maxBound :: a class Bounded a => Complemented a where not :: a -> a class Bounded a => Heyting a where infixr 3 ==> (==>) :: a -> a -> a class (Complemented a, Heyting a) => Boolean a (||) :: Boolean a => a -> a -> a (||) = sup (&&) :: Boolean a => a -> a -> a (&&) = inf -------------------- -- Bool instances -- (these work fine) instance Eq Bool where type Logic Bool = Bool (==) = (Prelude.==) instance POrd Bool where inf True True = True inf _ _ = False instance MinBound Bool where minBound = False instance Lattice Bool where sup False False = False sup _ _ = True instance Bounded Bool where maxBound = True instance Complemented Bool where not True = False not False = True instance Heyting Bool where False ==> _ = True True ==> a = a instance Boolean Bool -------------------- -- Integer instances -- (these work fine) instance Eq Integer where type Logic Integer = Bool (==) = (Prelude.==) instance POrd Integer where inf = Prelude.min instance Lattice Integer where sup = Prelude.max -------------------- -- function instances -- (these cause GHC to loop) instance Eq b => Eq (a -> b) where type Logic (a -> b) = a -> Logic b f==g = \a -> f a == g a instance POrd b => POrd (a -> b) where inf f g = \a -> inf (f a) (g a) instance MinBound b => MinBound (a -> b) where minBound = \_ -> minBound instance Lattice b => Lattice (a -> b) where sup f g = \a -> sup (f a) (g a) instance Bounded b => Bounded (a -> b) where maxBound = \_ -> maxBound instance Complemented b => Complemented (a -> b) where not f = \a -> not (f a) instance Heyting b => Heyting (a -> b) where f ==> g = \a -> f a ==> g a instance Boolean b => Boolean (a -> b) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: infoneeded Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | 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 MikeIzbicki): I've found another suspicious edge case. GHC will loop if you use the same code above, but add the `(/=)` function to the `Eq` class as follows: {{{ class Boolean (Logic a) => Eq a where type Logic a :: * (==) :: a -> a -> Logic a (/=) :: a -> a -> Logic a a/=b = not (a==b) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: infoneeded Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | 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): OK I've got it. Patch coming. Your example differs from Edward's in #10318, because you really do have an infinite stack of superclasses. * `Eq a` has `Boolean (Logic a)` as a superclass * `Boolean a` ultimately has `Eq a` as a superclass So we get `Eq (Logic a)`, `Eq (Logic (Logic a))`, etc forever. Do you really mean that. Edward cut this off by adding a constraint {{{ Frac (Frac a) ~ Frac a }}} Can you do something like that for `Logic`? If you really really do have infinitely many superclasses then unsolved constraints will indeed hit the iteration limit as you found... GHC keeps adding superclasses in the hope of finding one that works, but there are infinitely many of them (I fixed the error message to give the right flag name, but it doesn't solve the problem). I don't see any way to solve this without you giving GHC some way to bound the tower as Edward did. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations
-------------------------------------+-------------------------------------
Reporter: MikeIzbicki | Owner:
Type: feature request | Status: infoneeded
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.10.1
checker) |
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 Simon Peyton Jones

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: infoneeded Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | 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): MikeIzbicki: OK can you try again now? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: infoneeded Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | 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 MikeIzbicki): Okay, I understand the limitations a bit better now. Adding the `Logic a ~ Logic (Logic a)` constraint makes it work for me. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: infoneeded Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | 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): Well, you only want to add that constraint if it's actually true -- that is, if you intend that `Logic` is idempotent. But hurrah anyway. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10592 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * testcase: => typecheck/should_compile/T10592 * resolution: => fixed * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10592#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC