Default methods don't pass implicit kind parameters properly
When compiling the following module:
{-# 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 #13998 (closed) .
Trac metadata
Trac field | Value |
---|---|
Version | 8.2.2 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |