[GHC] #15215: GHC HEAD internal error when FlexibleContexts isn't enabled
GHC
ghc-devs at haskell.org
Sat Jun 2 22:57:17 UTC 2018
#15215: GHC HEAD internal error when FlexibleContexts isn't enabled
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Compile-time
Unknown/Multiple | crash or panic
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following code produces a GHC internal error on GHC HEAD:
{{{#!hs
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeInType #-}
module Bug where
import Data.Kind
data A :: Type -> Type where
MkA :: Show (Maybe a) => A a
data SA :: forall a. A a -> Type where
SMkA :: SA MkA
}}}
{{{
$ ~/Software/ghc5/inplace/bin/ghc-stage2 Bug.hs[1 of 1] Compiling Bug
( Bug.hs, Bug.o )
Bug.hs:9:3: error:
• Non type-variable argument in the constraint: Show (Maybe a)
(Use FlexibleContexts to permit this)
• In the definition of data constructor ‘MkA’
In the data type declaration for ‘A’
|
9 | MkA :: Show (Maybe a) => A a
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Bug.hs:12:14: error:
• GHC internal error: ‘MkA’ is not in scope during type checking, but
it passed the renamer
tcl_env of environment: [rqU :-> ATcTyCon SA :: forall a. A a -> *,
rsV :-> APromotionErr RecDataConPE]
• In the first argument of ‘SA’, namely ‘MkA’
In the type ‘SA MkA’
In the definition of data constructor ‘SMkA’
|
12 | SMkA :: SA MkA
| ^^^
}}}
Enabling `FlexibleContexts` causes the internal error to go away.
This is a regression from GHC 8.4, which does not give an internal error.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15215>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list