[GHC] #7891: Can't write type signature for top-level polymorphic pattern binding

GHC cvs-ghc at haskell.org
Tue May 7 11:56:50 CEST 2013


#7891: Can't write type signature for top-level polymorphic pattern binding
--------------------------------------+-------------------------------------
Reporter:  MartijnVanSteenbergen      |          Owner:                         
    Type:  bug                        |         Status:  new                    
Priority:  normal                     |      Component:  Compiler (Type checker)
 Version:  7.6.3                      |       Keywords:                         
      Os:  Unknown/Multiple           |   Architecture:  Unknown/Multiple       
 Failure:  GHC rejects valid program  |      Blockedby:                         
Blocking:                             |        Related:                         
--------------------------------------+-------------------------------------
 Hi,

 In GHC 7.4.1 and 7.6.3 I can't write a type signature for a top-level
 polymorphic pattern binding. Consider this program:

 {{{
 {-# LANGUAGE RankNTypes #-}

 newtype T = T (forall t. t -> t)

 tf :: T
 tf = T id

 -- Can't write this type signature:
 -- f :: t -> t
 T f = tf

 -- But with an indirection we can:
 g :: t -> t
 g = f

 -- We can still use f as it were fully polymorphic (which is good):
 a :: ()
 a = f ()
 b :: Char
 b = f 'b'
 }}}

 I expect to be able to specify a type for f.

 The same applies for a data family constructor, which is my original use
 case. I don't think it matters much, but here is an similar test case that
 uses a data family:

 {{{
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE TypeFamilies #-}

 class C t where
   data F t :: *
   mkF :: t -> F t

 instance C () where
   data F () = FUnit (forall t. t -> t)
   mkF () = FUnit id

 -- Can't write a type for f here either:
 FUnit f = mkF ()
 }}}

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



More information about the ghc-tickets mailing list