#7137: Unnecessary -XRank2Types requirement involving type alias containing
"forall" from another module
---------------------------------------+------------------------------------
 Reporter:  joeyadams                  |          Owner:                  
     Type:  bug                        |         Status:  new             
 Priority:  normal                     |      Component:  Compiler        
  Version:                             |       Keywords:                  
       Os:  Unknown/Multiple           |   Architecture:  Unknown/Multiple
  Failure:  GHC rejects valid program  |       Testcase:                  
Blockedby:                             |       Blocking:                  
  Related:                             |  
---------------------------------------+------------------------------------
 The following builds with GHC 7.4, but not 7.6.

 '''Bottom.hs'''
 {{{
 {-# LANGUAGE Rank2Types #-}
 module Bottom where

 type Bottom = forall a. a

 data Pipe l i o u m r = Pipe
 type GSource m o = forall l i u. Pipe l i o u m ()
 }}}


 '''Main.hs'''
 {{{
 import Bottom

 myBottom :: Int -> Bottom
 myBottom _ = error "Bottom"

 main :: IO ()
 main = myBottom 3
 }}}

 Note that Main.hs does not have the Rank2Types extension turned on.

 myBottom does not have a rank-2 type.  After expanding the type alias, you
 get:

 {{{
 myBottom :: Int -> forall a. a
 }}}

 This is logically equivalent to:

 {{{
 myBottom :: forall a. Int -> a
 }}}

 GHC 7.4.2 accepts this use of type alias, but GHC 7.6 does not.

 Note that if we make something that does in fact expand to a rank-2 type:

 {{{
 foo :: Bottom -> Int
 foo x = x
 }}}

 GHC 7.4.2 correctly rejects the program unless you enable Rank2Types.

 Also, if we use a standalone Bottom type alias:

 {{{
 myBottom :: Bottom
 }}}

 Then GHC 7.6 accepts the program.  It does not accept Int -> Bottom
 without Rank2Types, but it does accept Bottom by itself.

 This issue is easy to work around: just add {-# LANGUAGE Rank2Types #-} or
 {-# LANGUAGE RankNTypes #-} to the top of the module.

 Is this a bug, or have the rules for type aliases and forall been
 deliberately tightened?

 P.S.: This ticket is for GHC 7.6.1-rc1.  That version tag is not
 available, though.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7137>
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