[GHC] #15120: Default methods don't pass implicit kind parameters properly

GHC ghc-devs at haskell.org
Fri May 4 11:45:37 UTC 2018


#15120: Default methods don't pass implicit kind parameters properly
-------------------------------------+-------------------------------------
           Reporter:  mbieleck       |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.2
           Keywords:  PolyKinds,     |  Operating System:  Unknown/Multiple
  DefaultSignatures                  |
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 When compiling the following module:

 {{{#!hs
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE DefaultSignatures #-}
 module TestCase where

 import Data.Proxy

 class Describe a where
   describe :: Proxy a -> String

   default describe :: Proxy a -> String
   describe _ = ""

 data Foo = Foo

 instance Describe Foo
 }}}

 I get the following error (on GHC 8.0.2 and 8.2.2, with `-fprint-explicit-
 kinds`):

 {{{
 TestCase.hs:15:10: error:
     • Couldn't match type ‘*’ with ‘Foo’
       Expected type: Proxy * Foo -> String
         Actual type: Proxy Foo Foo -> String
     • In the expression: TestCase.$dmdescribe @Foo
       In an equation for ‘describe’: describe = TestCase.$dmdescribe @Foo
       In the instance declaration for ‘Describe * Foo’
    |
 15 | instance Describe Foo
    |          ^^^^^^^^^^^^
 }}}

 The Core generated for `$dmdescribe` has the following type signature:

 {{{
 TestCase.$dmdescribe
   :: forall k (a :: k). Describe k a => Proxy k a -> String
 }}}

 I believe the failure results from the fact that the type application
 `TestCase.$dmdescribe @Foo` passes `Foo` as the `k` parameter instead of
 `a`.

 Seems related to https://ghc.haskell.org/trac/ghc/ticket/13998 .

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


More information about the ghc-tickets mailing list