[GHC] #11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 (Type checker) | Keywords: PolyKinds, | Operating System: Unknown/Multiple UndecidableSuperClasses | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: #10318 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Looks like I spoke too soon when I said all my examples worked in #10318 -- it doesn't seem to work when the superclass cycle gets sufficiently interesting, possibly caused by the use of `PolyKinds` in the style mentioned in #9201. I took my `hask` code, and removed the shimming hacks above, and the following stripped down example sends the compiler into an infinite loop, which I believe should be able to work: {{{#!hs {-# language KindSignatures, PolyKinds, TypeFamilies, NoImplicitPrelude, FlexibleContexts, MultiParamTypeClasses, GADTs, ConstraintKinds, FlexibleInstances, FunctionalDependencies, UndecidableSuperClasses #-} import GHC.Types (Constraint) import qualified Prelude data Nat (c :: i -> i -> *) (d :: j -> j -> *) (f :: i -> j) (g :: i -> j) class Functor p (Nat p (->)) p => Category (p :: i -> i -> *) class (Category dom, Category cod) => Functor (dom :: i -> i -> *) (cod :: j -> j -> *) (f :: i -> j) | f -> dom cod instance (Category c, Category d) => Category (Nat c d) instance (Category c, Category d) => Functor (Nat c d) (Nat (Nat c d) (->)) (Nat c d) instance (Category c, Category d) => Functor (Nat c d) (->) (Nat c d f) instance Category (->) instance Functor (->) (->) ((->) e) instance Functor (->) (Nat (->) (->)) (->) }}} Sorry for the largish example, but I don't know how to strip it down smaller than the 6 instances that remain. One potentially telling observation is that without the instances it compiles, and produces what I expect, so the `UndecidableSuperClasses` part seems to be letting the classes compile, but there seems to be a bad interaction with the way the instances work. Also, in this stripped down form, I can remove the use of `UndecidableInstances` and that avoids the spinning problem, but once I flesh it out further I need `UndecidableInstances` in the "real" version of the problem. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ekmett): * version: 7.10.3 => 8.0.1-rc1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): There also seems to be a bad interaction with the `?callStack` machinery. Here is a differently modified test case: {{{ {-# language KindSignatures, PolyKinds, DataKinds, TypeFamilies, RankNTypes, NoImplicitPrelude, FlexibleContexts, MultiParamTypeClasses, GADTs, ConstraintKinds, FlexibleInstances, TypeOperators, ScopedTypeVariables, UndecidableSuperClasses, FunctionalDependencies #-} import GHC.Types (Constraint) import qualified Prelude data Dict p where Dict :: p => Dict p newtype p :- q = Sub (p => Dict q) data Nat (c :: i -> i -> *) (d :: j -> j -> *) (f :: i -> j) (g :: i -> j) class Functor p (Nat p (->)) p => Category (p :: i -> i -> *) where type Ob p :: i -> Constraint class (Category dom, Category cod) => Functor (dom :: i -> i -> *) (cod :: j -> j -> *) (f :: i -> j) | f -> dom cod bug :: Functor c d f => Ob c a :- Ob d (f a) bug = Prelude.undefined }}} I attempted to place `undefined` there as a placeholder while I worked on the surrounding code, but compiling `bug` causes {{{ solveWanteds: too many iterations (limit = 4) Unsolved: WC {wc_simple = [W] $dIP_a15a :: ?callStack::GHC.Stack.Types.CallStack (CDictCan)} New superclasses found Set limit with -fconstraint-solver-iterations=n; n=0 for no limit }}} Raising the limit gets me right back to the same unsolved constraint. Without the class cycle, we don't spin forever trying to find a `?callStack`. It seems odd that looking for `?callStack` would cause us to unroll superclasses though, as implicit parameters can't be a superclass of any class. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high * milestone: => 8.0.1 Comment: This is something we should try to sort out before the release. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * priority: high => normal * milestone: 8.0.1 => Comment: comment:2 does indeed suggest a special case. I'll implement that. Your original example seems to work in HEAD. I'll try the current 8.0 branch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): Sorry, I pasted the first example after I removed the `UndecidableInstances` from the code. With that turned on it spins. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Ah! Correct. I have nailed it. Patch coming. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I've been bit by this -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with
UndecidableInstances
-------------------------------------+-------------------------------------
Reporter: ekmett | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.0.1-rc1
checker) | Keywords: PolyKinds,
Resolution: | UndecidableSuperClasses
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #10318 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#11480: UndecidableSuperClasses causes the compiler to spin with
UndecidableInstances
-------------------------------------+-------------------------------------
Reporter: ekmett | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.0.1-rc1
checker) | Keywords: PolyKinds,
Resolution: | UndecidableSuperClasses
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #10318 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11480, | polykinds/T11480a Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => typecheck/should_compile/T11480, polykinds/T11480a Comment: OK I've fixed both the original report (with the commit in comment:9) and comment:2 (the commit in comment:8). Pls merge both. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: fixed | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11480, | polykinds/T11480a Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.0.1 Comment: Cherry-picked to `ghc-8.0` as 6217147e0895e98b08e597660ea941a544943a4d and e37b571baabf18621eb3b471fddc015a021ecf46. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: fixed | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11480, | polykinds/T11480a Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ekmett): * Attachment "Categories.hs" added. full test case -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: fixed | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11480, | polykinds/T11480a Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): I've attached the full source file that I was trying to compile when I found this issue. With the above patches merged in, it compiles clean, but it may supply you with a longer worked example for testing that uses a lot of advanced techniques together. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11480: UndecidableSuperClasses causes the compiler to spin with UndecidableInstances -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: PolyKinds, Resolution: fixed | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T11480, | polykinds/T11480a, | polykinds/T11480b Blocked By: | Blocking: Related Tickets: #10318 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: typecheck/should_compile/T11480, polykinds/T11480a => typecheck/should_compile/T11480, polykinds/T11480a, polykinds/T11480b Comment: Thanks -- I've added your example to the regression suite. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11480#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC