#1807: type equality coercions not symmetric + order dependent
----------------------------------------------------------------+-----------
 Reporter:  guest                                               |          
Owner:  chak       
     Type:  bug                                                 |         
Status:  new        
 Priority:  normal                                              |      
Milestone:  6.10 branch
Component:  Compiler (Type checker)                             |        
Version:  6.8        
 Severity:  normal                                              |     
Resolution:             
 Keywords:  type equality coercions symmetry order constraints  |     
Difficulty:  Unknown    
 Testcase:                                                      |   
Architecture:  Unknown    
       Os:  Unknown                                             |  
----------------------------------------------------------------+-----------
Comment (by Remi):

 Not sure whether it's the same bug, but at least it looks very similiar.
 In ghc-6.9.20071105, x typechecks, but y doesn't. And the only difference
 is which side of the (a ~ b) the Eq constraint is on..
 (there unfortunately are no newer binary linux i386 snapshots that
 actually install..)
 {{{
 {-# LANGUAGE TypeFamilies, GADTs, KindSignatures, TypeOperators,
 RankNTypes, FlexibleContexts #-}
 module Foo where

 data Equal a b = (b ~ a) => Refl

 foo         :: forall a b. ((a ~ b) => a -> b -> Bool) -> Equal a b -> a
 -> b -> Bool
 foo f Refl a b = f a b

 x   :: Eq b => Equal a b -> a -> b -> Bool
 x   = foo (==)

 -- Doesn't typecheck
 {-
 y   :: Eq a => Equal a b -> a -> b -> Bool
 y   = foo (==)
 -}
 }}}

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