[GHC] #13738: TypeApplications-related GHC internal error

GHC ghc-devs at haskell.org
Tue May 23 16:35:59 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):

 There are two workarounds that I'm aware of. One is to explicitly quantify
 the kind variable `k` in the instance declaration:

 {{{#!hs
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeApplications #-}
 {-# LANGUAGE TypeInType #-}
 module Bug where

 import Data.Coerce
 import Data.Kind (Type)

 newtype Wrap f a = Wrap (f a)

 class C f where
   c :: f a

 instance forall k (f :: k -> Type). C f => C (Wrap f) where
   c = coerce @(forall (a :: k). f a)
              @(forall (a :: k). C f a)
       c
 }}}

 (This, of course, requires that you turn on `TypeInType`.)

 The other workaround is to leave off the kind annotations in the instance
 altogether:

 {{{#!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. f a)
              @(forall a. C f a)
       c
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13738#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list