[GHC] #13738: TypeApplications-related GHC internal error
GHC
ghc-devs at haskell.org
Mon May 22 01:15:43 UTC 2017
#13738: TypeApplications-related GHC internal error
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
| TypeApplications
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: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Here's a somewhat more minimal example:
{{{#!hs
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Bug where
import Data.Coerce
newtype Wrap f a = Wrap (f a)
class C f where
c :: f a
instance C f => C (Wrap f) where
c = coerce @(forall (a :: k). f a)
@(forall (a :: k). C f a)
c
}}}
{{{
$ ~/Software/ghc/inplace/bin/ghc-stage2 --interactive Bug.hs
GHCi, version 8.3.20170516: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:15:29: error:
• GHC internal error: ‘k’ is not in scope during type checking, but it
passed the renamer
tcl_env of environment: [a1tN :-> Type variable ‘a’ = a,
a1tQ :-> Type variable ‘f’ = f, a1uU :->
Type variable ‘k’ = k]
• In the kind ‘k’
In the type ‘(forall (a :: k). f a)’
In the expression:
coerce @(forall (a :: k). f a) @(forall (a :: k). C f a) c
|
15 | c = coerce @(forall (a :: k). f a)
|
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13738#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list