[GHC] #8634: Code valid in GHC 7.6 is impossible to move over GHC 7.7 (because of liberal coverage condition)

GHC ghc-devs at haskell.org
Fri Dec 27 18:42:19 UTC 2013


#8634: Code valid in GHC 7.6 is impossible to move over GHC 7.7 (because of
liberal coverage condition)
-----------------------------------+---------------------------------------
        Reporter:  danilo2         |            Owner:
            Type:  bug             |           Status:  new
        Priority:  high            |        Milestone:
       Component:  Compiler        |          Version:  7.7
      Resolution:                  |         Keywords:
Operating System:                  |     Architecture:  Unknown/Multiple
  Unknown/Multiple                 |       Difficulty:  Unknown
 Type of failure:  None/Unknown    |       Blocked By:
       Test Case:                  |  Related Tickets:  #1241, #2247, #8356
        Blocking:                  |
-----------------------------------+---------------------------------------

Comment (by danilo2):

 Replying to [comment:1 rwbarton]:

 First of all, thank you for your response and your comments :)

 > This means "for any type `cls`, there must be at most one type `func`
 for which there is an instance `Method1 cls m func`". (And the same for
 `m`.)
 Exactly - with one data type `cls` there could be "associated" only one
 function `func` with the name `method1`.

 >
 > {{{#!haskell
 > instance (out ~ (t1->t1)) => Method1 (Vector a) Vector_testid out where
 ...
 > }}}
 >
 > This defines instances like `Method1 (Vector Bool) Vector_testid (Int ->
 Int)`, `Method1 (Vector Bool) Vector_testid (Char -> Char)`, etc., so it
 violates the functional dependency. So, it was a (long-standing) bug that
 GHC 7.6 allowed this instance declaration.

 Hm, but if we assume, that there is only one such function `(a->a)` for a
 given `cls`, this should not be a problem? In such case, we are sure, that
 for `Vector a` and `Vector_testid` there is 0 or 1 functions with such
 signature (of course without such assumption this could be dangerous, but
 if a "power user" is writing lets say a DSL or is generating Haskell code
 and knows what he is doing, I see no point in preventing it.

 > See the related tickets for further discussion.

 I'll read them, thank you.

 > As for how to fix your program: it's hard to see what's going on with
 the `Call` type class (...)

 I'm really sorry for this - my example was probalby too simplified. Please
 take a look at this code (this is the same as above, but slighty modified
 and extended):
 {{{#!haskell
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE FunctionalDependencies #-}

 import Data.Tuple.OneTuple

 ------------------------------
 data Vector a = Vector {x :: a, y :: a, z :: a} deriving (Show)
 newtype Vector_method1 a = Vector_method1 a
 newtype Vector_method2 a = Vector_method2 a

 ------------------------------
 testid (v :: Vector a) x = x
 testf2 (v :: Vector a) x = (x,x)

 ------------------------------
 testx x = call (method1 x) "test"

 ------------------------------
 class Method1 cls m func | cls -> m, cls -> func where
     method1 :: cls -> m func

 class Method2 cls m func | cls -> m, cls -> func where
     method2 :: cls -> m func

 class Call ptr args result | ptr args -> result where
     call :: ptr -> args -> result

 ------------------------------
 instance (out ~ (t1->t1)) => Method1 (Vector a) Vector_method1 out where
   method1 = (Vector_method1 . testid)

 instance (base ~ (t1 -> t2), out ~ t2) => Call (Vector_method1 base)
 (OneTuple t1) out where
     call (Vector_method1 val) (OneTuple arg) = val arg

 instance (base ~ (String -> t2), out ~ t2) => Call (Vector_method1 base)
 () out where
     call (Vector_method1 val) _ = val "default string"

 ------------------------------
 instance (out ~ (t1->(t1,t1))) => Method2 (Vector a) Vector_method2 out
 where
   method2 = (Vector_method2 . testf2)

 instance (base ~ (t1 -> t2), out ~ t2) => Call (Vector_method2 base)
 (OneTuple t1) out where
     call (Vector_method2 val) (OneTuple arg) = val arg


 ------------------------------
 main = do
     let v = Vector (1::Int) (2::Int) (3::Int)
     print $ call (method1 v) (OneTuple "test")
     print $ call (method1 v) ()
     print $ call (method2 v) (OneTuple "test")
 }}}

 output:
 {{{#!haskell
 "test"
 "default string"
 ("test","test")
 }}}

 Here you can see, that we can call "method1" giving it `(OneTuple "test")`
 or `()`. The former passes simply one argument, while the later passes 0
 arguments and the default value of "default string" is choosen instead.

 > (...) but can you try dropping both functional dependencies and writing
 > {{{#!haskell
 > instance (m ~ Vector_testid, out ~ (t1->t1)) => Method1 (Vector a) m out
 where ...
 > }}}

 Unfortunatelly I can not :( Look, `Vector_testid` indicates, that it holds
 "testid" method (it should be named `Vector_method1` instead - sorry for
 that typo.
 If we get more associated functions, we would have `Vector_method2`,
 `Vector_method3` etc, so we need to distinguish them - see the sample code
 in this comment.


 > I'll leave this ticket open as several people have asked for an option
 to relax this functional dependency sanity condition, but I don't think
 it's a very good idea myself; the condition seems to usually catch real
 bugs.

 I do not think to allow some "power users" to relax this condition, if
 such people know what they are doing.
 I completely agree, such condition usually catches a lot of bugs - so it
 should be enabled by default, but If you know, what you are doing, you've
 ben warned and you should make it off :)

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8634#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list