[GHC] #10806: Type error and type level (<=) together cause GHC to hang

#10806: Type error and type level (<=) together cause GHC to hang -------------------------------------+------------------------------------- Reporter: htebalaka | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Type checker) | Keywords: | Operating System: MacOS X Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- The following incorrect type in the function wrongArity triggers an infinite loop in GHC, though only in the presence of triggersLoop. The issue is somehow related to the use of (<=) in constraints of the Q data constructor; if I remove either of the constraints or add an (a <= c) constraint it works as you would expect. {{{#!hs {-# LANGUAGE GADTs, ExplicitNamespaces, TypeOperators, DataKinds #-} import GHC.TypeLits (Nat, type (<=)) data Q a where Q :: (a <= b, b <= c) => proxy a -> proxy b -> Q c wrongArity :: a -> a wrongArity _ a = a triggersLoop :: Q b -> Q b -> Bool triggersLoop (Q _ _) (Q _ _) = undefined }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10806 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10806: Type error and type level (<=) together cause GHC to hang -------------------------------------+------------------------------------- Reporter: htebalaka | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by htebalaka: Old description:
The following incorrect type in the function wrongArity triggers an infinite loop in GHC, though only in the presence of triggersLoop. The issue is somehow related to the use of (<=) in constraints of the Q data constructor; if I remove either of the constraints or add an (a <= c) constraint it works as you would expect. {{{#!hs
{-# LANGUAGE GADTs, ExplicitNamespaces, TypeOperators, DataKinds #-}
import GHC.TypeLits (Nat, type (<=))
data Q a where Q :: (a <= b, b <= c) => proxy a -> proxy b -> Q c
wrongArity :: a -> a wrongArity _ a = a
triggersLoop :: Q b -> Q b -> Bool triggersLoop (Q _ _) (Q _ _) = undefined }}}
New description: The following incorrect type in the function wrongArity triggers an infinite loop at compile time, though only in the presence of triggersLoop. The issue is somehow related to the use of (<=) in constraints of the Q data constructor; if I remove either of the constraints or add an (a <= c) constraint it works as you would expect. {{{#!hs {-# LANGUAGE GADTs, ExplicitNamespaces, TypeOperators, DataKinds #-} import GHC.TypeLits (Nat, type (<=)) data Q a where Q :: (a <= b, b <= c) => proxy a -> proxy b -> Q c wrongArity :: a -> a wrongArity _ a = a triggersLoop :: Q b -> Q b -> Bool triggersLoop (Q _ _) (Q _ _) = undefined }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10806#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10806: Type error and type level (<=) together cause GHC to hang -------------------------------------+------------------------------------- Reporter: htebalaka | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by htebalaka: Old description:
The following incorrect type in the function wrongArity triggers an infinite loop at compile time, though only in the presence of triggersLoop. The issue is somehow related to the use of (<=) in constraints of the Q data constructor; if I remove either of the constraints or add an (a <= c) constraint it works as you would expect. {{{#!hs
{-# LANGUAGE GADTs, ExplicitNamespaces, TypeOperators, DataKinds #-}
import GHC.TypeLits (Nat, type (<=))
data Q a where Q :: (a <= b, b <= c) => proxy a -> proxy b -> Q c
wrongArity :: a -> a wrongArity _ a = a
triggersLoop :: Q b -> Q b -> Bool triggersLoop (Q _ _) (Q _ _) = undefined }}}
New description: The following incorrect arity triggers an infinite loop at compile time. The issue is somehow related to the use of (<=) in constraints of the Q data constructor; if I remove either of the constraints or add an (a <= c) constraint it works as you would expect. {{{#!hs {-# LANGUAGE GADTs, ExplicitNamespaces, TypeOperators, DataKinds #-} import GHC.TypeLits (Nat, type (<=)) data Q a where Q :: (a <= b, b <= c) => proxy a -> proxy b -> Q c triggersLoop :: Q b -> Q b -> Bool triggersLoop (Q _ _) (Q _ _) = print 'x' 'y' }}} Incorrect function definitions, like {{{foo :: a -> a ; foo _ x = x}}} also result in an infinite loop. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10806#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10806: Type error and type level (<=) together cause GHC to hang -------------------------------------+------------------------------------- Reporter: htebalaka | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 7.12.1 Comment: Oh dear. This should certainly be addressed for 7.12 if possible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10806#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10806: Type error and type level (<=) together cause GHC to hang -------------------------------------+------------------------------------- Reporter: htebalaka | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by htebalaka): Just to be clear, function definitions with the wrong arity still needed {{{triggersLoop (Q _ _) (Q _ _) = undefined}}} to trigger the issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10806#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10806: Type error and type level (<=) together cause GHC to hang -------------------------------------+------------------------------------- Reporter: htebalaka | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by htebalaka): Looking at this further, it seems like any type error in the file triggers the issue in the presence of triggersLoop. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10806#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10806: Type error and type level (<=) together cause GHC to hang -------------------------------------+------------------------------------- Reporter: htebalaka | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by kanetw): Seems to work fine in GHC HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10806#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10806: Type error and type level (<=) together cause GHC to hang -------------------------------------+------------------------------------- Reporter: htebalaka | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): htebalaka: your test case doesn't typecheck with ghc-7.10.2. Are you sure you were using 7.10.2? Can you please fix the description. Thanks. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10806#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10806: Type error and type level (<=) together cause GHC to hang
-------------------------------------+-------------------------------------
Reporter: htebalaka | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.0.1
Component: Compiler (Type | Version: 7.10.2
checker) |
Resolution: | Keywords:
Operating System: MacOS X | Architecture:
| Unknown/Multiple
Type of failure: Other | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10806: Type error and type level (<=) together cause GHC to hang -------------------------------------+------------------------------------- Reporter: htebalaka | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.10.2 checker) | Resolution: fixed | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: indexed- | types/should_compile/T10806 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => indexed-types/should_compile/T10806 * resolution: => fixed Comment: The test generates an error message (as it should) and does not make the compiler loop. So I'll close. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10806#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC