[GHC] #12867: Internal error while typechecking invalid program
GHC
ghc-devs at haskell.org
Mon Nov 21 23:50:12 UTC 2016
#12867: Internal error while typechecking invalid program
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 8.0.1
(Type checker) |
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:
-------------------------------------+-------------------------------------
While trying to reduce #12866 I encountered this program,
{{{#!hs
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
module T12866 where
type Test2 a = (Eq (TestM a))
class Test a where
type TestM :: *
}}}
which gives rise to this internal GHC error during typechecking,
{{{
$ ghc Hi2.hs
Hi2.hs:7:21: error:
• GHC internal error: ‘TestM’ is not in scope during type checking,
but it passed the renamer
tcl_env of environment: [ap0 :-> Type variable ‘a’ = a]
• In the first argument of ‘Eq’, namely ‘TestM a’
In the type ‘Eq (TestM a)’
In the type declaration for ‘Test2’
Hi2.hs:9:1: error:
• The associated type ‘TestM’
mentions none of the type or kind variables of the class ‘Test a’
• In the class declaration for ‘Test’
}}}
Clearly the program is bogus, but the first error message is quite
suspicious.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12867>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list