[GHC] #16394: GHC internal error while typechecking of instance definition

#16394: GHC internal error while typechecking of instance definition -------------------------------------+------------------------------------- Reporter: Day1721 | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.6.3 (Type checker) | Keywords: | Operating System: Linux Architecture: | Type of failure: Incorrect Unknown/Multiple | error/warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Hello. \\ This code won't typecheck because of GHC internal error. {{{#!hs {-# LANGUAGE PolyKinds, TypeFamilies, DataKinds #-} class C a where type T (n :: a) -- v--DIFF--v instance C a => C b => C (a, b) where type T '(n, m) = (T n, T m) }}} with error message: {{{ Bug.hs:7:10: error: • GHC internal error: ‘T’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [a1LS :-> Type variable ‘a’ = a :: *, a1LT :-> Type variable ‘b’ = b :: *] • In the type instance declaration for ‘T’ In the instance declaration for ‘C b => C (a, b)’ | 7 | type T (n, m) = (T n, T m) | ^ Failed, no modules loaded. }}} but this works fine: {{{#!hs {-# LANGUAGE PolyKinds, TypeFamilies, DataKinds #-} class C a where type T (n :: a) -- v--DIFF--v instance (C a, C b) => C (a, b) where type T '(n, m) = (T n, T m) }}} Not sure is a bug, but either way it would be better to make more understandable error message -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16394 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16394: GHC internal error while typechecking of instance definition -------------------------------------+------------------------------------- Reporter: Day1721 | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Happily, HEAD gives {{{ T16394.hs:9:10: error: Illegal class instance: `C a => C b => C (a, b)' Class instances must be of the form context => C ty_1 ... ty_n where `C' is a class | 9 | instance C a => C b => C (a, b) where | ^^^^^^^^^^^^^^^^^^^^^^ }}} Would someone like to add a regression test and close this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16394#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16394: GHC internal error while typechecking of instance definition -------------------------------------+------------------------------------- Reporter: Day1721 | Owner: (none) Type: bug | Status: closed Priority: low | Milestone: Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: fixed | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Done in !496. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16394#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16394: GHC internal error while typechecking of instance definition -------------------------------------+------------------------------------- Reporter: Day1721 | Owner: (none) Type: bug | Status: closed Priority: low | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: fixed | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.8.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16394#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16394: GHC internal error while typechecking of instance definition -------------------------------------+------------------------------------- Reporter: Day1721 | Owner: (none) Type: bug | Status: closed Priority: low | Milestone: 8.8.1 Component: Compiler (Type | Version: 8.6.3 checker) | Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: error/warning at compile-time | typecheck/should_fail/T16394 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): MR!496 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => typecheck/should_fail/T16394 * differential: => MR!496 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16394#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16394: GHC internal error while typechecking of instance definition
-------------------------------------+-------------------------------------
Reporter: Day1721 | Owner: (none)
Type: bug | Status: closed
Priority: low | Milestone: 8.8.1
Component: Compiler (Type | Version: 8.6.3
checker) |
Resolution: fixed | Keywords:
Operating System: Linux | Architecture:
| Unknown/Multiple
Type of failure: Incorrect | Test Case:
error/warning at compile-time | typecheck/should_fail/T16394
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): MR!496
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari
participants (1)
-
GHC