#3155: TypeOperators/Rank2Types clash
----------------------------------+-----------------------------------------
Reporter:  MartijnVanSteenbergen  |          Owner:                  
    Type:  bug                    |         Status:  new             
Priority:  normal                 |      Component:  Compiler        
 Version:  6.10.1                 |       Severity:  normal          
Keywords:                         |       Testcase:                  
      Os:  Unknown/Multiple       |   Architecture:  Unknown/Multiple
----------------------------------+-----------------------------------------
 Consider the following piece of code:

 {{{
 {-# LANGUAGE GADTs #-}

 data Any s where
   Any :: s ix -> ix -> Any s

 data AnyR s r where
   AnyR :: s ix -> r ix -> AnyR s r

 unR :: (forall ix. r ix -> ix) -> AnyR s r -> Any s
 unR f (AnyR ix rix) = Any ix (f rix)
 }}}

 GHC reports:

 {{{
     Illegal operator `.' in type `forall ix . (r ix -> ix)'
       Perhaps you intended to use -XRankNTypes or similar flag
       to enable explicit-forall syntax: forall <tvs>. <type>
 }}}

 Enabling TypeOperators causes the error to change to:

 {{{
     Occurs check: cannot construct the infinite type: ix = r ix
     In the pattern: AnyR ix rix
     In the definition of `unR': unR f (AnyR ix rix) = Any ix (f rix)
 }}}

 Which is very confusing, as the solution (still) is to turn on Rank2Types.

 Could it be made so that the error message stays the same when
 TypeOperators is turned on?

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3155>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to