[GHC] #9301: Rank-2 constraints are assigned kind *

#9301: Rank-2 constraints are assigned kind * ------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- Compile this program with GHC-HEAD (I have 7.9.20140605, but I guess 7.8.3 will also do): {{{ {-# LANGUAGE RankNTypes #-} strangelet :: (forall t . Num t) => () strangelet = \_ -> () }}} Very strangely it gets accepted! {{{ *Main> :t strangelet strangelet :: (forall t. Num t) -> () }}} I suspect that the type checker assigns kind `*` to rank-2 constraints. Of course it should assign a `Constraint` kind. What I ultimately want is to declare: {{{ foo :: (Monad m, forall n . Num (m n)) => m n foo = ... }}} ..or such. Would that be unreasonable? NB: 7.4.2 rejects it (even with `-XConstraintKinds`). I did not try 7.6.3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9301 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9301: Rank-2 constraints are assigned kind * -------------------------------------+------------------------------------ Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Description changed by heisenbug: Old description:
Compile this program with GHC-HEAD (I have 7.9.20140605, but I guess 7.8.3 will also do): {{{ {-# LANGUAGE RankNTypes #-}
strangelet :: (forall t . Num t) => () strangelet = \_ -> () }}}
Very strangely it gets accepted! {{{ *Main> :t strangelet strangelet :: (forall t. Num t) -> () }}} I suspect that the type checker assigns kind `*` to rank-2 constraints. Of course it should assign a `Constraint` kind.
What I ultimately want is to declare: {{{ foo :: (Monad m, forall n . Num (m n)) => m n foo = ... }}} ..or such. Would that be unreasonable?
NB: 7.4.2 rejects it (even with `-XConstraintKinds`). I did not try 7.6.3.
New description: Compile this program with GHC-HEAD (I have 7.9.20140605, but I guess 7.8.3 will also do): {{{ {-# LANGUAGE RankNTypes #-} strangelet :: (forall t . Num t) => () strangelet = \_ -> () }}} Very strangely it gets accepted! {{{ *Main> :t strangelet strangelet :: (forall t. Num t) -> () }}} I suspect that the type checker assigns kind `*` to rank-2 constraints. Of course it should assign a `Constraint` kind. What I ultimately want is to declare: {{{ foo :: (Monad m, forall n . Num (m n)) => m n foo = ... }}} ...or such. Would that be unreasonable? NB: 7.4.2 rejects it (even with `-XConstraintKinds`). I did not try 7.6.3. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9301#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9301: Rank-2 constraints are assigned kind * -------------------------------------+------------------------------------ Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by heisenbug): Running GHC with debug options `ghci -XRankNTypes -XConstraintKinds -ddump-parsed -ddump-rn -ddump-types -ddump-tcstrangelet.hs` I get: {{{ ==================== Parser ==================== strangelet :: forall t. Num t => () strangelet = \ _ -> () ==================== Renamer ==================== Main.strangelet :: forall t. Num t => () Main.strangelet = \ _ -> () TYPE SIGNATURES strangelet :: (forall t. Num t) -> () TYPE CONSTRUCTORS COERCION AXIOMS Dependent modules: [] Dependent packages: [base, ghc-prim, integer-gmp] ==================== Typechecker ==================== AbsBinds [] [] {Exports: [strangelet <= strangelet <>] Exported types: strangelet :: (forall t. Num t) -> () [LclId, Str=DmdType] Binds: strangelet = \ _ -> GHC.Tuple.()} Ok, modules loaded: Main. }}} The renamer still has it right, while both `-ddump-types -ddump-tc` already show the wrong signature. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9301#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9301: Rank-2 constraints are assigned kind * -------------------------------------+------------------------------------ Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by heisenbug): Ooops, just repeated this experiment with 7.9.20140712 and now I get: {{{ strangelet.hs:3:16: Illegal constraint: forall t. Num t In the type signature for ‘strangelet’: strangelet :: (forall t. Num t) => () Failed, modules loaded: none. }}} So that type gets rejected. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9301#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9301: Rank-2 constraints are assigned kind * -------------------------------------+------------------------------------ Reporter: heisenbug | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by heisenbug): * status: new => closed * resolution: => duplicate Comment: This very much looks like a duplicate of #9196, closing. But my point is that I'd like to have polymorphic (multiparameter) constraints, where the param universally abstracted over is a non-`*` kind, that is an ADT. See: {{{ class Foo a where ... data Bar (b :: Bool) x = ... instance Foo (Bar True x) where ... instance Foo (Bar False x) where ... test :: (forall b. Foo (Bar b x)) =>... }}} Here the `forall` condition is satisfiable, as all `Bool` alternatives are covered with `instance` declarations. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9301#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9301: Rank-2 constraints are assigned kind * -------------------------------------+------------------------------------ Reporter: heisenbug | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): The trouble is that I don't know how to do type inference in the presence of polymorphic constraints. It is not a small change. It would be a useful feature. I've wanted it since at least 2000 (see [http://research.microsoft.com/en-us/um/people/simonpj/papers/derive.htm Derivable Type Classes]). Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9301#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC