[GHC] #7916: PolyKinds without type signatures

GHC cvs-ghc at haskell.org
Thu May 16 19:30:36 CEST 2013


#7916: PolyKinds without type signatures
--------------------------------------+-------------------------------------
Reporter:  monoidal                   |          Owner:                         
    Type:  bug                        |         Status:  new                    
Priority:  normal                     |      Component:  Compiler (Type checker)
 Version:  7.7                        |       Keywords:                         
      Os:  Unknown/Multiple           |   Architecture:  Unknown/Multiple       
 Failure:  GHC rejects valid program  |      Blockedby:                         
Blocking:                             |        Related:                         
--------------------------------------+-------------------------------------
 Consider

 {{{
 {-# LANGUAGE PolyKinds, ExplicitForAll #-}
 f :: forall (m :: k -> *) (a :: k). m a -> m a
 f = id

 g = f
 }}}

 I would expect GHC to infer the same type for `g` as for `f`. However, it
 gives the AnyK kind, and `g` is not possible to use:

 {{{
 ghci -Wall X.hs

 ...

 X.hs:5:1: Warning:
     Top-level binding with no type signature:
       g :: forall (m :: AnyK -> *) (a :: AnyK). m a -> m a
 Ok, modules loaded: Main.
 *Main> g "a"

 <interactive>:2:1:
     Kind incompatibility when matching types:
       a0 :: AnyK
       Char :: *
     In the first argument of ‛print’, namely ‛it’
     In a stmt of an interactive GHCi command: print it
 }}}

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



More information about the ghc-tickets mailing list