[GHC] #8758: GeneralizedNewtypeDeriving sometimes needs RankNTypes

GHC ghc-devs at haskell.org
Sun Feb 9 15:49:10 UTC 2014


#8758: GeneralizedNewtypeDeriving sometimes needs RankNTypes
-------------------------------------------+-------------------------------
       Reporter:  goldfire                 |             Owner:  goldfire
           Type:  bug                      |            Status:  new
       Priority:  normal                   |         Milestone:
      Component:  Compiler (Type checker)  |           Version:  7.8.1-rc1
       Keywords:                           |  Operating System:
   Architecture:  Unknown/Multiple         |  Unknown/Multiple
     Difficulty:  Unknown                  |   Type of failure:
     Blocked By:                           |  None/Unknown
Related Tickets:                           |         Test Case:
                                           |          Blocking:
-------------------------------------------+-------------------------------
 Consider

 {{{
 {-# LANGUAGE RankNTypes #-}

 module A where

 class C m where
   foo :: (forall b. b -> m b) -> c -> m c

 instance C [] where
   foo f c = f c
 }}}

 and

 {{{
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}

 module B where

 import A

 newtype MyList a = Mk [a]
   deriving C
 }}}

 When I compile B.hs, I get

 {{{
     Illegal polymorphic or qualified type: forall b. b -> MyList b
     Perhaps you intended to use RankNTypes or Rank2Types
     In an expression type signature:
       forall (c :: *). (forall (b :: *). b -> MyList b) -> c -> MyList c
     In the expression:
         GHC.Prim.coerce
           (foo :: (forall (b :: *). b -> [] b) -> c -> [] c) ::
           forall (c :: *). (forall (b :: *). b -> MyList b) -> c -> MyList
 c
     In an equation for ‛foo’:
         foo
           = GHC.Prim.coerce
               (foo :: (forall (b :: *). b -> [] b) -> c -> [] c) ::
               forall (c :: *). (forall (b :: *). b -> MyList b) -> c ->
 MyList c
 }}}

 I will fix shortly.

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


More information about the ghc-tickets mailing list