[GHC] #12522: GHC 8.0.1 hangs, looping forever in type-checker

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm not sure if this is a bug or hanging the compiler is expected here. This was the minimal example that causes GHC to hang: {{{#!hs {-# LANGUAGE TypeFamilyDependencies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE AllowAmbiguousTypes #-} main = return $ f (Just 'c') data D1 x data D2 type family TF x = t | t -> x type instance TF (D1 x, a) = Maybe (TF (x, a)) type instance TF (D2, ()) = Char class C p where f :: TF (x, a) -> () }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: jstolarek (added) Comment: Given that `TypeFamilyDependencies` are involved I'm ccing Jan. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by jstolarek): Surprising. I was expecting that GHC will hang on a black-hole but this indeed looks like an infinite loop in the type checker. I'm afraid Simon or Richard will have to take a look at this. Oh, and `f` need not be a part of a type class. It can be a standalone function with undefined definition. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by clinton): Oh yes, silly me. As you said, replacing the class with: {{{ f :: TF (x, a) -> () f _ = () }}} also illustrates the bug. This still causes the compiler to loop forever in GHC HEAD 21st September 2016 (8.1.20160921) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by clinton): * failure: Other => GHC rejects valid program -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by clinton): * failure: GHC rejects valid program => Compile-time crash -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by clinton: @@ -5,3 +5,1 @@ - {-# LANGUAGE TypeFamilyDependencies #-} - {-# LANGUAGE FlexibleInstances #-} - {-# LANGUAGE AllowAmbiguousTypes #-} + {-# LANGUAGE TypeFamilyDependencies #-} @@ -9,1 +7,1 @@ - main = return $ f (Just 'c') + main = return $ f (Just 'c') @@ -11,2 +9,2 @@ - data D1 x - data D2 + data D1 x + data D2 @@ -14,3 +12,3 @@ - type family TF x = t | t -> x - type instance TF (D1 x, a) = Maybe (TF (x, a)) - type instance TF (D2, ()) = Char + type family TF x = t | t -> x + type instance TF (D1 x, a) = Maybe (TF (x, a)) + type instance TF (D2, ()) = Char @@ -18,2 +16,2 @@ - class C p where - f :: TF (x, a) -> () + f :: TF (x, a) -> () + f _ = () New description: I'm not sure if this is a bug or hanging the compiler is expected here. This was the minimal example that causes GHC to hang: {{{#!hs {-# LANGUAGE TypeFamilyDependencies #-} main = return $ f (Just 'c') data D1 x data D2 type family TF x = t | t -> x type instance TF (D1 x, a) = Maybe (TF (x, a)) type instance TF (D2, ()) = Char f :: TF (x, a) -> () f _ = () }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by clinton): Further simplified code in bug report, removed unnecessary extensions. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by clinton: @@ -1,2 +1,5 @@ - I'm not sure if this is a bug or hanging the compiler is expected here. - This was the minimal example that causes GHC to hang: + There's a subtle issue going on with injective type families. Simply + reordering the arguments can cause an otherwise legal program to hang on + compile. Calling `f_bad` instead of `f_good` will cause the compiler to + hang, looping forever in the typechecker, but the only difference between + `TF_Good` and `TF_Bad` is that the argument order is swapped. @@ -5,1 +8,1 @@ - {-# LANGUAGE TypeFamilyDependencies #-} + {-# LANGUAGE TypeFamilyDependencies #-} @@ -7,1 +10,2 @@ - main = return $ f (Just 'c') + main = return $ f_good (Just 'c') + --main = return $ f_bad (Just 'c') @@ -9,2 +13,2 @@ - data D1 x - data D2 + type family TF x y = t | t -> x y + type instance TF Int Float = Char @@ -12,3 +16,2 @@ - type family TF x = t | t -> x - type instance TF (D1 x, a) = Maybe (TF (x, a)) - type instance TF (D2, ()) = Char + type family TF_Good x y = t | t -> x y + type instance TF_Good a (Maybe x) = Maybe (TF a x) @@ -16,2 +19,8 @@ - f :: TF (x, a) -> () - f _ = () + f_good :: TF_Good a x -> () + f_good _ = () + + type family TF_Bad x y = t | t -> x y + type instance TF_Bad (Maybe x) a = Maybe (TF a x) + + f_bad :: TF_Bad x a -> () + f_bad _ = () New description: There's a subtle issue going on with injective type families. Simply reordering the arguments can cause an otherwise legal program to hang on compile. Calling `f_bad` instead of `f_good` will cause the compiler to hang, looping forever in the typechecker, but the only difference between `TF_Good` and `TF_Bad` is that the argument order is swapped. {{{#!hs {-# LANGUAGE TypeFamilyDependencies #-} main = return $ f_good (Just 'c') --main = return $ f_bad (Just 'c') type family TF x y = t | t -> x y type instance TF Int Float = Char type family TF_Good x y = t | t -> x y type instance TF_Good a (Maybe x) = Maybe (TF a x) f_good :: TF_Good a x -> () f_good _ = () type family TF_Bad x y = t | t -> x y type instance TF_Bad (Maybe x) a = Maybe (TF a x) f_bad :: TF_Bad x a -> () f_bad _ = () }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by clinton): Modified example code again. A recursive definition is not required for the bug to occur, and the order of arguments matters. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: simonpj (added) Comment: Simon, I had meant to mention this ticket in our meeting today. Do you think you could have a look? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK I had a look. What is happening is this. We have a wanted constraint {{{ [W] TF (x_aDY, a_aJn) ~ s_aF4 FunEq }}} where `s_aF4` is a flatten-unification-variable; and in our mdel we have {{{ [D] s_aF4 ~ Maybe Char }}} We can't reduce the wanted constraint so we try irmpvoement. Now rightly or wrongly, "improvement" kicks in, by matching the constraint with the axiom {{{ type instance TF (D1 x, a) = Maybe (TF (x, a)) }}} In improvement we seem to use "pre-unification" from the paper, so that matching `Maybe Char` against `Maybe (TF (x,a))` succeeds. So we emit two new derived constraint {{{ [D] a_aJn ~ a_fresh1 [D] x_aDY ~ D1 x_fresh2 }}} The match on RHS is incomplete so we just get a "shape", with fresh unification variables. But that is bad. Now we take `[D] a_aJn ~ a_fresh1` as our next work item, unify `a_a7n := a_fresh`, kick out the TF FunEq, and now we are in an infinite loop. Question: why do we use pre-unification when matching the RHS in the injectivity-improvement step. That's what is causing the trouble. Richard? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:11 simonpj]:
Question: why do we use pre-unification when matching the RHS in the injectivity-improvement step. That's what is causing the trouble.
This all looks like reasonable behavior to me on a line-by-line basis. Obviously a loop is bad, but each step along the way is OK. We use pre-unification here because we want to match the pattern `Maybe (TF (x, a))` against `Maybe Char`. And indeed we should, because injectivity tells us that the equation `TF (D1 x, a) = Maybe (TF (x, a))` must be the one used to produce `Maybe Char`. (In fact, the solver should also generate `[W] TF (x, a) ~ Char`. Or maybe it should be Derived. Does it?) So I like the use of pre-unification here. What I find strange is that we're using the model when triggering improvement as we're looking at a Wanted. Doesn't the model (that is, all the Derived constraints) live off in its own world with minimal interaction with Wanteds? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

What I find strange is that we're using the model when triggering improvement as we're looking at a Wanted. Doesn't the model (that is, all
#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I've re-read our Haskell Symposium '15 paper "Injective type families". It's rather good! Section 5.2 covers exactly the point at issue here. * You point out above that we can really also produce `[D] Char ~ TF (x_fresh2, a_fresh1)`. Very true! WE don't currently do that. Moreover, this idea is missing from Section 5.2 in the paper. In the example here we should add `[D] G beta ~ Int`, shouldn't we? Doing so could lead to more progress. Would you like to cook up an example that will only work if we do this? * How to avoid the loop? Well we basically emit `[D] (x_aDY, a_aJn) ~ (D x_fresh2, a_fresh1)`. When we boil this down to `a_aJn ~ a_fresh1` we really really want to unify `a_fresh1 := a_aJn`. If we do it the other way round we get the infinite loop. Or to put it another way, we don't want to invent more fresh variables than we need to. In this case, let's no invent `a_fresh1` at all; just re-use `a_aJn`. You might think of it as an optimisation, but acutally it's essential to avoid the loop. the Derived constraints) live off in its own world with minimal interaction with Wanteds? Every Wanted effectively has a "shadow Derived" behind it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:13 simonpj]:
I've re-read our Haskell Symposium '15 paper "Injective type families". It's rather good!
Glad you like it. :)
Section 5.2 covers exactly the point at issue here.
* You point out above that we can really also produce `[D] Char ~ TF (x_fresh2, a_fresh1)`. Very true! WE don't currently do that.
* How to avoid the loop? Well we basically emit `[D] (x_aDY, a_aJn) ~ (D x_fresh2, a_fresh1)`. When we boil this down to `a_aJn ~ a_fresh1` we really really want to unify `a_fresh1 := a_aJn`. If we do it the other way round we get the infinite loop.
Or to put it another way, we don't want to invent more fresh variables
But I wonder if we need to. The existing machinery for dealing with type functions should add that equality in short order once we do the partial improvement. Perhaps that's why we left this out of the paper. than we need to. In this case, let's no invent `a_fresh1` at all; just re-use `a_aJn`. You might think of it as an optimisation, but acutally it's essential to avoid the loop. I trust your judgment here, but it all looks rather fragile. What termination property does setting `a_aJn := a_fresh1` violate? Or, said differently, ''why'' does this fix the problem. You might say "you won't kick out the `FunEqCan`" and you'd be right, but that doesn't seem like a fundamental enough reason. But perhaps this is a battle for another day.
What I find strange is that we're using the model when triggering
improvement as we're looking at a Wanted. Doesn't the model (that is, all the Derived constraints) live off in its own world with minimal interaction with Wanteds?
Every Wanted effectively has a "shadow Derived" behind it.
Yes, I suppose I knew that. But I thought these Deriveds only come into play when working with other Deriveds. Put another way: should we try improvement only when working with Deriveds? Given your statement above about shadow Deriveds, my new plan would seem to cover all cases where we try improvement now, but we would seemingly be saved from this loop. Am I missing anything? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andreash): I think I may just have hit the same bug. I've extracted a small example: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeFamilyDependencies #-} {-# LANGUAGE TypeOperators #-} newtype I a = I a type family Curry (as :: [*]) b = f | f -> as b where Curry '[] b = I b Curry (a:as) b = a -> Curry as b data Uncurried (as :: [*]) b def :: Curry as b -> Uncurried as b def = undefined test :: Uncurried [Int, String] String test = def $ \n s -> I $ show n ++ s test2 :: Uncurried [Bool, Bool] Bool test2 = def $ \a b -> I $ a && b }}} Removing the type signatures from either `test`, or `test2` will hang ghc. If the type family is not defined as injective, then ghc doesn't hang, but instead gives an error message about ambiguous type variables. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker
-------------------------------------+-------------------------------------
Reporter: clinton | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12522: GHC 8.0.1 hangs, looping forever in type-checker
-------------------------------------+-------------------------------------
Reporter: clinton | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
crash | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge Comment: Main bug is fixed, happily. Worth merging. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 801cbb42638714004587ba39d1d6b2bbc9ad3b9d and 12cfcbeb93cff0747259e2cc5be652184734a292. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.0.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12522: GHC 8.0.1 hangs, looping forever in type-checker -------------------------------------+------------------------------------- Reporter: clinton | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: indexed- crash | types/should_compile/T12522, | T12522b, should_fail/T12522a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => indexed-types/should_compile/T12522, T12522b, should_fail/T12522a -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12522#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC