[GHC] #8346: Rank 1 type signature still requires RankNTypes

GHC ghc-devs at haskell.org
Mon Sep 23 16:26:41 CEST 2013


#8346: Rank 1 type signature still requires RankNTypes
----------------------------+----------------------------------------------
       Reporter:            |             Owner:
  tinctorius                |            Status:  new
           Type:  bug       |         Milestone:
       Priority:  normal    |           Version:  7.6.3
      Component:  Compiler  |  Operating System:  Unknown/Multiple
       Keywords:            |   Type of failure:  GHC rejects valid program
   Architecture:            |         Test Case:
  Unknown/Multiple          |          Blocking:
     Difficulty:  Unknown   |
     Blocked By:            |
Related Tickets:  #2605     |
----------------------------+----------------------------------------------
 When trying to figure out which type variable names are *actually* bound
 in `ScopedTypeVariables`, I tried floating `forall`s into the covariant
 argument of the function type. Essentially, I ran into the problem that
 programs like the following are rejected:

 {{{
 #!hs
 {-# LANGUAGE ExplicitForAll #-}
 tuple :: forall a. a -> (forall b. b -> (a, b))
 tuple = (,)
 }}}

 The message is as follows:
 {{{
 Main.hs:2:10:
     Illegal polymorphic or qualified type: forall b. b -> (a, b)
     Perhaps you intended to use -XRankNTypes or -XRank2Types
     In the type signature for `tuple':
       tuple :: forall a. a -> (forall b. b -> (a, b))
 }}}

 As far as I know, the rank of a type is defined by how deep quantifiers
 are nested in contravariant parts of that type. Or something like that.
 Also, as far as I know, `forall a. a -> (forall b. b -> (a, b))` is
 equivalent to `forall a b. a -> b -> (a, b)`, and more importantly, both
 are rank-1 polymorphic. There should be no need to use extensions that
 allow higher-ranked polymorphism.

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



More information about the ghc-tickets mailing list