#7485: Tuple constraints not properly kinded
-----------------------------+----------------------------------------------
Reporter:  goldfire          |          Owner:                  
    Type:  bug               |         Status:  new             
Priority:  normal            |      Component:  Compiler        
 Version:  7.7               |       Keywords:  ConstraintKinds 
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown      |      Blockedby:                  
Blocking:                    |        Related:                  
-----------------------------+----------------------------------------------
 Consider this:

 {{{
 {-# LANGUAGE DataKinds, ConstraintKinds, KindSignatures #-}

 import GHC.Exts ( Constraint )

 type UnitType = (() :: *)
 type UnitConstraint = (() :: Constraint)

 type PairType = ((,) :: * -> * -> *)
 }}}

 So far, so good. But, adding the following causes an error:

 {{{
 type PairConstraint = ((,) :: Constraint -> Constraint -> Constraint)
 }}}

 The error is

 {{{
     The signature specified kind `Constraint
                                   -> Constraint -> Constraint',
       but `(,)' has kind `* -> * -> *'
 }}}

 In general, you can't use the prefix form of {{{(,)}}} in a constraint, to
 my surprise. It's not entirely clear what is the "correct" behavior here,
 but this all seems a little fishy as currently implemented.

 This was all tested on 7.7.20121130.

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

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to