#2203: TFs in class instances heads
-------------------------+--------------------------------------------------
    Reporter:  chak      |       Owner:  chak                   
        Type:  bug       |      Status:  new                    
    Priority:  normal    |   Component:  Compiler (Type checker)
     Version:  6.9       |    Severity:  normal                 
    Keywords:            |    Testcase:                         
Architecture:  Multiple  |          Os:  Multiple               
-------------------------+--------------------------------------------------
 Ganesh posted the following example on haskell-cafe:
 {{{
 {-# LANGUAGE ScopedTypeVariables, TypeFamilies, FlexibleInstances #-}

 module Test1a where

 class Foo a where
    type TheFoo a
    foo :: TheFoo a -> a
    foo' :: a -> Int

 class Bar b where
    bar :: b -> Int

 instance Foo a => Bar (Either a (TheFoo a)) where
    bar (Left a) = foo' a
    bar (Right b) = foo' (foo b :: a)

 instance Foo Int where
    type TheFoo Int = Int
    foo = id
    foo' = id

 val :: Either Int Int
 val = Left 5

 res :: Int
 res = bar val
 }}}
 It fails to type check as the type of `bar` cannot be inferred.  However,
 GHC should reject the instance due to the TF in the head despite
 `FlexibleInstances`.

 Moreover, the corrected code
 {{{
 {-# LANGUAGE ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}

 module Test1a where

 class Foo a where
    type TheFoo a
    foo :: TheFoo a -> a
    foo' :: a -> Int

 class Bar b where
    bar :: b -> Int

 instance (b ~ TheFoo a, Foo a) => Bar (Either a b) where
    bar (Left a) = foo' a
    bar (Right b) = foo' (foo b :: a)

 instance Foo Int where
    type TheFoo Int = Int
    foo = id
    foo' = id

 val :: Either Int Int
 val = Left 5

 res :: Int
 res = bar val
 }}}
 requires `UndecidableInstances`, although it shouldn't.

 We should be able to allow equalities of the form `tv ~ F tv1 .. tvn` with
 tv and tvi being distinct type variables without requiring
 `UndecidableInstances`.

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