[GHC] #11498: GHC requires kind-polymorphic signatures on class head

#11498: GHC requires kind-polymorphic signatures on class head -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I have the following compiling example: {{{ {-# LANGUAGE DataKinds, FlexibleContexts, FlexibleInstances, KindSignatures, MultiParamTypeClasses, PolyKinds, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators #-} import Data.Proxy import GHC.Prim type family CtxOf d (args :: k) :: Constraint class Run ctx (params :: [k]) where runAll :: Proxy params -> Proxy ctx -> (forall (args :: k) . (CtxOf ctx args) => Proxy args -> Bool) -> [Bool] data BasicCtxD type instance CtxOf BasicCtxD '(a,b) = (a ~ b) instance (Run BasicCtxD params, a ~ b) => Run BasicCtxD ( '(a,b) ': params) where runAll _ pctx f = (f (Proxy::Proxy '(a,b))) : (runAll (Proxy::Proxy params) pctx f) }}} But if I move the kind signature of `params` to its occurrence in the signature of `runAll`: {{{ class Run ctx params where runAll :: Proxy (params :: [k]) -> Proxy ctx -> (forall (args :: k) . (CtxOf ctx args) => Proxy args -> Bool) -> [Bool] }}} I get a couple of nasty (and confusing) compile errors. {{{ Main.hs:20:25: Couldn't match kind ‘k1’ with ‘(,) k k’ ‘k1’ is a rigid type variable bound by the type signature for runAll :: Proxy ('(a, b) : params) -> Proxy BasicCtxD -> (forall (args :: k1). CtxOf BasicCtxD args => Proxy args -> Bool) -> [Bool] at Main.hs:20:3 Expected type: Proxy args0 Actual type: Proxy '(a, b) Relevant bindings include f :: forall (args :: k1). CtxOf BasicCtxD args => Proxy args -> Bool (bound at Main.hs:20:17) runAll :: Proxy ('(a, b) : params) -> Proxy BasicCtxD -> (forall (args :: k1). CtxOf BasicCtxD args => Proxy args -> Bool) -> [Bool] (bound at Main.hs:20:3) In the first argument of ‘f’, namely ‘(Proxy :: Proxy '(a, b))’ In the first argument of ‘(:)’, namely ‘(f (Proxy :: Proxy '(a, b)))’ In the expression: (f (Proxy :: Proxy '(a, b))) : (runAll (Proxy :: Proxy params) pctx f) Main.hs:21:42: Could not deduce (k1 ~ (,) k k) from the context (CtxOf BasicCtxD args) bound by a type expected by the context: CtxOf BasicCtxD args => Proxy args -> Bool at Main.hs:21:8-42 ‘k1’ is a rigid type variable bound by the type signature for runAll :: Proxy ('(a, b) : params) -> Proxy BasicCtxD -> (forall (args :: k1). CtxOf BasicCtxD args => Proxy args -> Bool) -> [Bool] at Main.hs:20:3 Expected type: Proxy args -> Bool Actual type: Proxy args1 -> Bool Relevant bindings include f :: forall (args :: k1). CtxOf BasicCtxD args => Proxy args -> Bool (bound at Main.hs:20:17) runAll :: Proxy ('(a, b) : params) -> Proxy BasicCtxD -> (forall (args :: k1). CtxOf BasicCtxD args => Proxy args -> Bool) -> [Bool] (bound at Main.hs:20:3) In the third argument of ‘runAll’, namely ‘f’ In the second argument of ‘(:)’, namely ‘(runAll (Proxy :: Proxy params) pctx f)’ }}} It seems to me that the two definitions of the class are equivalent, so it would be nice if they both compiled. It wasn't obvious to me that the kind signature had to go on the class parameter rather than somewhere else. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11498 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11498: GHC requires kind-polymorphic signatures on class head -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Compiler (Type checker) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11498#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11498: GHC requires kind-polymorphic signatures on class head -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This is rather strange. Here is a slightly more compact example: {{{#!hs {-# LANGUAGE PolyKinds #-} module Prog1 where import Data.Proxy class C (a :: k) where c :: Proxy a -> Proxy (b :: k) }}} Let's see what GHCi thinks the type of `c` is: {{{ λ> :i C class C (a :: k) where c :: forall (b :: k). Proxy a -> Proxy b }}} So far, so good. But if you move the kind signature: {{{#!hs {-# LANGUAGE PolyKinds #-} module Prog2 where import Data.Proxy class C a where c :: Proxy (a :: k) -> Proxy (b :: k) }}} Then the type changes! {{{ λ> :i C class C (a :: k) where c :: forall k1 (b :: k1). Proxy a -> Proxy b }}} All of a sudden, the kinds of `a` and `b` have become entirely different. To add to the strangeness, `Prog2` doesn't compile at all on GHC HEAD: {{{ $ /opt/ghc/head/bin/ghci Prog2.hs GHCi, version 8.5.20180501: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Prog2 ( Prog2.hs, interpreted ) Prog2.hs:7:15: error: • Expected kind ‘k’, but ‘a’ has kind ‘k0’ • In the first argument of ‘Proxy’, namely ‘(a :: k)’ In the type signature: c :: Proxy (a :: k) -> Proxy (b :: k) In the class declaration for ‘C’ | 7 | c :: Proxy (a :: k) -> Proxy (b :: k) | ^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11498#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11498: GHC requires kind-polymorphic signatures on class head -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11498#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11498: GHC requires kind-polymorphic signatures on class head -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sighingnow): * cc: sighingnow (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11498#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11498: GHC requires kind-polymorphic signatures on class head -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2-rc2 checker) | Resolution: | Keywords: CUSKs Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => CUSKs -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11498#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11498: GHC requires kind-polymorphic signatures on class head -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.2-rc2 checker) | Resolution: duplicate | Keywords: CUSKs Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #13365 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #13365 Comment: OK, I now understand what is going on here. The fact that the second version of `C` doesn't typecheck in comment:2 is expected behavior. Once again, this all comes back to the fact that `C` doesn't have a complete user-specified kind (CUSK). As a result, the kind of `a` (in `class C a`) is chosen to be some fresh kind variable `k0`. When you try to declare a method of type `forall k. Proxy (a :: k) -> Proxy (b :: k)`, GHC complains because the kind `k` is bound in the method's type signature and //not// by the class (which binds `k0`), and thus `k` is not the same as `k0`. GHC perhaps ought to warn about the lack of a CUSK here, but that is the subject of #13365. Therefore, I'm opting to close this ticket and a duplicate of that one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11498#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC