
#8550: GHC builds recursive coerctions when using recursive type families -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Compiler | Version: (Type checker) | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thomie): * priority: normal => high * milestone: => 7.10.1 Old description:
Consider {{{ {-# LANGUAGE TypeFamilies, GADTs, UndecidableInstances #-} type family F a type instance F () = F () data A where A :: F () ~ () => A x :: A x = A }}}
On GHC 7.6.3 it yields a context reduction stack overflow (despite F () ~ () being put into the “solved funeqs” list).
In HEAD, a recursive dictionary is built, but then detected: {{{ [1 of 1] Compiling Foo ( Foo.hs, Foo.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.7.20131108 for x86_64-unknown-linux): Cycle in coercion bindings [[cobox_ayX{v} [lid] = CO main:Foo.TFCo:R:F(){tc rob}[0] ; cobox_ayZ{v} [lid], cobox_ayZ{v} [lid] = CO cobox_ayX{v} [lid] ; cobox_az0{v} [lid]]]
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}}
Either this panic needs to be turned into an error, or we need to prevent recursive dictionaries for when solving funeqs (similar to how we do it for `Coercible`).
New description: Consider {{{ {-# LANGUAGE TypeFamilies, GADTs, UndecidableInstances #-} type family F a type instance F () = F () data A where A :: F () ~ () => A x :: A x = A main = seq A (return ()) }}} On GHC 7.6.3 it yields a context reduction stack overflow (despite F () ~ () being put into the “solved funeqs” list). In HEAD, a recursive dictionary is built, but then detected: {{{ [1 of 1] Compiling Foo ( Foo.hs, Foo.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.7.20131108 for x86_64-unknown-linux): Cycle in coercion bindings [[cobox_ayX{v} [lid] = CO main:Foo.TFCo:R:F(){tc rob}[0] ; cobox_ayZ{v} [lid], cobox_ayZ{v} [lid] = CO cobox_ayX{v} [lid] ; cobox_az0{v} [lid]]] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Either this panic needs to be turned into an error, or we need to prevent recursive dictionaries for when solving funeqs (similar to how we do it for `Coercible`). -- Comment: Trying to compile the example from the description with ghc-7.9.20141115 results in GHC using lots of memory, making my machine unusable until I kill the process. This seems like a regression, setting priority to high. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8550#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler