#4338: weird discrepancies between TFs and FDs in GHC7
--------------------------+-------------------------------------------------
    Reporter:  illissius  |       Owner:                         
        Type:  bug        |      Status:  new                    
    Priority:  normal     |   Component:  Compiler (Type checker)
     Version:  6.13       |    Keywords:                         
    Testcase:             |   Blockedby:                         
          Os:  Linux      |    Blocking:                         
Architecture:  x86        |     Failure:  Compile-time crash     
--------------------------+-------------------------------------------------
 I'm trying to do some seemingly equivalent code with GHC7 as of 09/19,
 using !TypeFamilies on the one hand and !FunctionalDependencies on the
 other, and my experience is that the TFs version results in some really
 weird-ass error messages from the compiler -- and a hang in one case --
 whereas the FDs version works just fine. I'm not sure about the errors,
 though they certainly seem bizarre, but I'm pretty sure the compiler
 hanging is a bug. (And I assume a hang is morally equivalent to a crash,
 so I'm marking this as such.)

 Here's the version with TFs:

 {{{
 {-# LANGUAGE MultiParamTypeClasses, TypeFamilies, FlexibleContexts #-}

 class (There a ~ b, BackAgain b ~ a) => Foo a b where
     type There a
     type BackAgain b
     there :: a -> b
     back :: b -> a
     tickle :: b -> b

 instance Foo Char Int where
     type There Char = Int
     type BackAgain Int = Char
     there = fromEnum
     back = toEnum
     tickle = (+1)

 test :: (Foo a b) => a -> a
 test = back . tickle . there

 main :: IO ()
 main = print $ test 'F'
 }}}


 and the one with FDs:

 {{{
 {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}

 class Bar a b | a -> b, b -> a where
     there :: a -> b
     back :: b -> a
     tickle :: b -> b

 instance Bar Char Int where
     there = fromEnum
     back = toEnum
     tickle = (+1)

 test :: (Bar a b) => a -> a
 test = back . tickle . there

 main :: IO ()
 main = print $ test 'F'
 }}}

 Are these as functionally-equivalent as they seem, or are there some
 subtle differences I'm missing? (Is it possible there's some kind of
 configuration problem on my end?)


 In any case, the result is that the TFs version gives me different errors
 depending on which type signatures I supply or omit, whereas the version
 with FDs compiles and works correctly in all cases.

 The TFs version, if I supply both type signatures (as listed):

 {{{
 $ ghc Foo.hs
 [1 of 1] Compiling Main             ( Foo.hs, Foo.o )

 Foo.hs:18:15:
     Could not deduce (Foo (BackAgain (There a)) (There a))
       from the context (Foo a b)
       arising from a use of `tickle'
     Possible fix:
       add (Foo (BackAgain (There a)) (There a)) to the context of
         the type signature for `test'
       or add an instance declaration for
          (Foo (BackAgain (There a)) (There a))
     In the first argument of `(.)', namely `tickle'
     In the second argument of `(.)', namely `tickle . there'
     In the expression: back . tickle . there

 Foo.hs:21:16:
     Overlapping instances for Foo Char Int
       arising from a use of `test'
     Matching instances:
       instance Foo Char Int -- Defined at Foo.hs:10:10-21
     (The choice depends on the instantiation of `'
      To pick the first instance above, use -XIncoherentInstances
      when compiling the other instance declarations)
     In the second argument of `($)', namely `test 'F''
     In the expression: print $ test 'F'
     In an equation for `main': main = print $ test 'F'
 }}}


 If I leave off the type signature for main, but not test:

 {{{
 $ ghc Foo.hs
 [1 of 1] Compiling Main             ( Foo.hs, Foo.o )

 Foo.hs:18:15:
     Could not deduce (Foo (BackAgain (There a)) (There a))
       from the context (Foo a b)
       arising from a use of `tickle'
     Possible fix:
       add (Foo (BackAgain (There a)) (There a)) to the context of
         the type signature for `test'
       or add an instance declaration for
          (Foo (BackAgain (There a)) (There a))
     In the first argument of `(.)', namely `tickle'
     In the second argument of `(.)', namely `tickle . there'
     In the expression: back . tickle . there
 }}}

 If I leave off the signature for test, regardless of whether I supply one
 for main:

 {{{
 $ ghc Foo.hs
 [1 of 1] Compiling Main             ( Foo.hs, Foo.o )
 ^C
 -- a seemingly infinite loop
 }}}

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