#7217: Unification of type variables in constraints
------------------------------+---------------------------------------------
 Reporter:  sjoerd_visscher   |          Owner:                  
     Type:  bug               |         Status:  new             
 Priority:  normal            |      Component:  Compiler        
  Version:  7.6.1-rc1         |       Keywords:                  
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown      |       Testcase:                  
Blockedby:                    |       Blocking:                  
  Related:                    |  
------------------------------+---------------------------------------------
 The following code works:

 {{{
 {-# LANGUAGE RankNTypes, ConstraintKinds, KindSignatures, GADTs #-}

 import Data.Monoid
 import GHC.Prim (Constraint)

 data Dict :: Constraint -> * where
   Dict :: a => Dict a

 f :: (c (), c String) => (forall a. Dict (c a) -> a) -> ((), String)
 f g = (g Dict, g Dict)

 test :: ((), String)
 test = f g
   where
     g :: Dict (Monoid a) -> a
     g Dict = mempty
 }}}

 But this doesn't:

 {{{
 f :: (c (), c String) => (forall a. c a => a) -> ((), String)
 f g = (g, g)

 test :: ((), String)
 test = f g
   where
     g :: Monoid a => a
     g = mempty
 }}}

 With the errors:

 {{{
 Could not deduce (c0 String, c0 ()) arising from a use of `f'

 Could not deduce (Monoid a) arising from a use of `g'
 }}}

 So it seems that type variables in constraints are not unified. At first I
 thought this might not be easy to fix, but since there's a workaround I
 guess it should be possible.

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