#4008: type error trying to specialize polymorphic function
----------------------------------------+-----------------------------------
    Reporter:  nr                       |        Owner:  simonpj                
  
        Type:  bug                      |       Status:  new                    
  
    Priority:  normal                   |    Milestone:  6.14.1                 
  
   Component:  Compiler (Type checker)  |      Version:  6.12.1                 
  
    Keywords:                           |   Difficulty:                         
  
          Os:  Linux                    |     Testcase:                         
  
Architecture:  x86                      |      Failure:  GHC rejects valid 
program
----------------------------------------+-----------------------------------
Changes (by igloo):

  * owner:  => simonpj
  * milestone:  => 6.14.1


Comment:

 Slightly simplified:
 {{{
 {-# LANGUAGE RankNTypes, EmptyDataDecls, LiberalTypeSynonyms #-}

 module Pain
 where

 data O
 data C

 type Counter n e x = n e x -> Int

 scalar :: (forall e x . a e x)
        -> (a C O, a O O, a O C)
 scalar z = (z, z, z)

 wrap :: (forall e x . Counter n e x)
      -> (Counter n C O, Counter n O O, Counter n O C)
 wrap = scalar
 }}}
 with HEAD:
 {{{
 Pain.hs:17:8:
     Couldn't match expected type `n C O' against inferred type `C'
       Expected type: (Counter n C O, Counter n O O, Counter n O C)
       Inferred type: (C -> O, O -> O, O -> C)
     In the expression: scalar
     In the definition of `wrap': wrap = scalar
 }}}
 (`LiberalTypeSynonyms` is actually no longer needed).

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