[GHC] #13784: Infinite loop in compiler without undecidableXXX

#13784: Infinite loop in compiler without undecidableXXX -------------------------------------+------------------------------------- Reporter: tysonzero | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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: -------------------------------------+------------------------------------- The following code causes the compiler to loop. {{{#!hs {-# LANGUAGE DataKinds, FlexibleContexts, FlexibleInstances, GADTs #-} {-# LANGUAGE KindSignatures, MultiParamTypeClasses, TypeFamilies, TypeOperators #-} module Arithmetic where import Data.Monoid ((<>)) data Product :: [*] -> * where (:*) :: a -> Product as -> Product (a : as) Unit :: Product '[] infixr 5 :* instance Show (Product '[]) where show Unit = "Unit" instance (Show a, Show (Product as)) => Show (Product (a : as)) where show (a :* as) = show a <> " :* " <> show as class Divideable a as where type Divide a as :: [*] divide :: Product as -> (a, Product (Divide a as)) instance Divideable a (a : as) where -- type Divide a (a : as) = as -- Conflicting type family instances, seems like OVERLAPS isn't a thing for type families. divide (a :* as) = (a, as) instance Divideable b as => Divideable b (a : as) where type Divide b (a : as) = a : Divide b as divide (a :* as) = a :* divide as }}} Looks like it is because it is erroneously trying to solve `as ~ Product (Divide a as)` in order to type check `divide`. This bug has been fixed in more recent versions of GHC. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13784 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13784: Infinite loop in compiler without undecidableXXX -------------------------------------+------------------------------------- Reporter: tysonzero | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 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 dfeuer): * milestone: => 8.2.1 Comment: Do we have a test case for this yet? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13784#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13784: Infinite loop in compiler without undecidableXXX -------------------------------------+------------------------------------- Reporter: tysonzero | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 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 RyanGlScott): This was fixed in commit 1eec1f21268af907f59b5d5c071a9a25de7369c7 (Another major constraint-solver refactoring). In particular, this reminds me a lot of #12538, wherein overlapping multi-parameter type classes with type families also resulted in an infinite loop at compile-time. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13784#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13784: Infinite loop in compiler without undecidableXXX
-------------------------------------+-------------------------------------
Reporter: tysonzero | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 8.0.2
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

#13784: Infinite loop in compiler without undecidableXXX -------------------------------------+------------------------------------- Reporter: tysonzero | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.2 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): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13784#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC