looking for examples of non-full Functional Dependencies

Hello, I'm looking for practical examples of non-full functional dependencies and would be grateful if anyone could show me some or point to applications using them. A non-full functional dependency is one involves only part of the parameters of a type class. E.g. class C a b c | a -> b has a non-full functional dependency a -> b which does not involve c. Thanks, Tom -- Tom Schrijvers Department of Computer Science K.U. Leuven Celestijnenlaan 200A B-3001 Heverlee Belgium tel: +32 16 327544 e-mail: tom.schrijvers@cs.kuleuven.be url: http://www.cs.kuleuven.be/~toms/

We're also looking for (practical) examples of "multi-range" functional dependencies class C a b c | c -> a b Notice that there are multiple (two) parameters in the range of the FD. It's tempting to convert the above to class C a b c | c -> a, c -> b but this yields a weaker (in terms of type improvement) system. Thanks, Martin Tom Schrijvers wrote:
Hello,
I'm looking for practical examples of non-full functional dependencies and would be grateful if anyone could show me some or point to applications using them.
A non-full functional dependency is one involves only part of the parameters of a type class. E.g.
class C a b c | a -> b
has a non-full functional dependency a -> b which does not involve c.
Thanks,
Tom
-- Tom Schrijvers
Department of Computer Science K.U. Leuven Celestijnenlaan 200A B-3001 Heverlee Belgium
tel: +32 16 327544 e-mail: tom.schrijvers@cs.kuleuven.be url: http://www.cs.kuleuven.be/~toms/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello Martin, Wednesday, April 16, 2008, 7:06:07 PM, you wrote: i'm not 100% sure that you'll find there appropriate examples but i suggest you too look into http://haskell.org/haskellwiki/Library/Streams where i've used very sophisticated (for me) FDs
We're also looking for (practical) examples of "multi-range" functional dependencies
class C a b c | c ->> a b
Notice that there are multiple (two) parameters in the range of the FD.
It's tempting to convert the above to
class C a b c | c ->> a, c -> b
but this yields a weaker (in terms of type improvement) system.
Thanks, Martin
Tom Schrijvers wrote:
Hello,
I'm looking for practical examples of non-full functional dependencies and would be grateful if anyone could show me some or point to applications using them.
A non-full functional dependency is one involves only part of the parameters of a type class. E.g.
class C a b c | a -> b
has a non-full functional dependency a -> b which does not involve c.
Thanks,
Tom
-- Tom Schrijvers
Department of Computer Science K.U. Leuven Celestijnenlaan 200A B-3001 Heverlee Belgium
tel: +32 16 327544 e-mail: tom.schrijvers@cs.kuleuven.be url: http://www.cs.kuleuven.be/~toms/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello,
On Wed, Apr 16, 2008 at 8:06 AM, Martin Sulzmann
We're also looking for (practical) examples of "multi-range" functional dependencies
class C a b c | c -> a b
Notice that there are multiple (two) parameters in the range of the FD.
It's tempting to convert the above to
class C a b c | c -> a, c -> b
but this yields a weaker (in terms of type improvement) system.
Could you elaborate on this? I think that a system that distinguishes these two would be very confusing. If you think of the FDs as logical statements about what is known of type variables, then the FDs on the two classes correspond to equivalent logical statements, so I am not sure why would we distinguish them for improvement purposes. Also, it seems fairly easy to convert between the two forms purely based on syntax, so if the one somehow results in better improvements, why would we ever use the other one? As for examples of interesting uses of functional dependencies, perhaps the literature on relational databases would provide some? -Iavor

Iavor Diatchki wrote:
Hello,
On Wed, Apr 16, 2008 at 8:06 AM, Martin Sulzmann
wrote: We're also looking for (practical) examples of "multi-range" functional dependencies
class C a b c | c -> a b
Notice that there are multiple (two) parameters in the range of the FD.
It's tempting to convert the above to
class C a b c | c -> a, c -> b
but this yields a weaker (in terms of type improvement) system.
Could you elaborate on this? I think that a system that distinguishes these two would be very confusing. If you think of the FDs as logical statements about what is known of type variables, then the FDs on the two classes correspond to equivalent logical statements, so I am not sure why would we distinguish them for improvement purposes. Also, it seems fairly easy to convert between the two forms purely based on syntax, so if the one somehow results in better improvements, why would we ever use the other one?
The two are not isomorphic. The first one c -> a b contains an explicit order (class parameter order is significant), whereas the second does not (the FDs form a set). I think the isomorphic functional dependency in the first case would be the set of all FDs under permutation of class parameters, in this case: c -> a b, c -> b a
As for examples of interesting uses of functional dependencies, perhaps the literature on relational databases would provide some?
Elaborating on the relational connection, it seems at first blush that class C a b c | a -> b is not ideally normalized and might presumably be profitably broken up into class A a b | a -> b class A a b => B a b c

I'm still confused about this point:
On 4/16/08, Dan Weston
class C a b c | c -> a b
Notice that there are multiple (two) parameters in the range of the FD.
It's tempting to convert the above to
class C a b c | c -> a, c -> b
but this yields a weaker (in terms of type improvement) system.
In both cases the statement is that given a type x, the instance C x y z for some y,z and the constraint C x a b, we unambiguously have a ~ y, b ~ z (where ~ is type equality) How does the order in (c -> a b) matter? -- ryan

I think I was the one confused. I guess I was (falsely) thinking that both C Int Char T C Char Int T could both be instances of class C a b c | c -> a, c -> b but only one could be an instance of C a b c | c -> a b. Sorry for adding noise to the discussion. Ryan Ingram wrote:
I'm still confused about this point:
On 4/16/08, Dan Weston
wrote: class C a b c | c -> a b
Notice that there are multiple (two) parameters in the range of the FD.
It's tempting to convert the above to
class C a b c | c -> a, c -> b
but this yields a weaker (in terms of type improvement) system.
In both cases the statement is that given a type x, the instance C x y z for some y,z and the constraint C x a b, we unambiguously have a ~ y, b ~ z (where ~ is type equality)
How does the order in (c -> a b) matter?
-- ryan

Martin Sulzmann wrote:
We're also looking for (practical) examples of "multi-range" functional dependencies
class C a b c | c -> a b
Notice that there are multiple (two) parameters in the range of the FD.
It's tempting to convert the above to
class C a b c | c -> a, c -> b
but this yields a weaker (in terms of type improvement) system.
I agree with Iavor. In fact, the two sets of dependencies that you have given here are provably equivalent, so it would be decidedly odd to have a "type improvement" system that distinguishes between them. While you're looking for unusual examples of fundeps, you might also want to consider things like: class C a b c | a -> b, b -> c Note that this is subtly different from a -> b c because {a -> b, b -> c} |= {a -> b c} while the reverse does not hold. Instead of type classes, I'll give you some more down-to-earth examples of relations that satisfy these dependencies: {Paper, Conference, Year} {Professor, University, Country} {Person, FavoriteFood, FoodGroup} ... For further insight, you might want to take a look at the theory of relational databases to see how functional dependencies are used there. In that context, some sets of dependencies (such as {a -> b, b -> c}) can be interpreted as indicators of bad design. This, in turn, might give you some ideas about the kinds of dependencies you can expect to encounter in well-designed Haskell code. (Of course, you might still find examples in other Haskell code of dependencies that would make a database person wince :-) All the best, Mark

Mark P Jones wrote:
Martin Sulzmann wrote:
We're also looking for (practical) examples of "multi-range" functional dependencies
class C a b c | c -> a b
Notice that there are multiple (two) parameters in the range of the FD.
It's tempting to convert the above to
class C a b c | c -> a, c -> b
but this yields a weaker (in terms of type improvement) system.
I agree with Iavor.
In fact, the two sets of dependencies that you have given here are provably equivalent, so it would be decidedly odd to have a "type improvement" system that distinguishes between them.
Consider class C a b c | a -> b, a -> c instance C a b b => C [a] [b] [b] Suppose we encounter the constraint C [x] y z What results can we expect from type improvement? 1) Single-range non-full FDs in GHC following the FD-CHR formulation: The first FD C a b c | a -> b in combination with the instance head C [a] [b] [b] will yield C [x] y z improved by y = [b1] for some b1 A similar reasoning yields C [x] y z improved by z = [b2] for some b2 So, overall we get C [x] y z improved by y= [b1] and z = [b2] Unfortunately, we couldn't establish that b1 and b2 are equal. Hence, we can *not* apply the instance. 2) Alternative design: We could now argue that the improvement implied by the FD is only applicable if we are in the "right" context. That is, C [x] y z doesn't yield any improvement because the context y is still underspecified (doesn't match the instance). In case of C [x] [y] z we get z = [y] (and C [x] z [y] yields z = [y]) 3) Multi-range FDs Consider class C a b c | a -> b c instance C a b b => C [a] [b] [b] This time it's straightforward. C [x] y z yields the improvement y = [b] and z = [b] which then allows us to apply the instance. 4) Summary. With multi-range FDs we can derive "more" improvement. C [x] y z yields y = [b] and z = [b] Based on the FD-CHR formulation, for the single-range FD case we get C [x] y z yields y = [b1] and z = [b2] which is clearly weaker. The alternative design is even weaker, from C [x] y z we can derive any improvement. So, I conclude that in the Haskell type improvement context there's clearly a difference among single-range and multi-range FDs. Of course, we could define multi-range FDs in terms of single-range FDs which then trivially solves the "equivalence" problem (but some user may be disappointed that their multi-range FDs yield weaker improvement). Thanks for your pointers below but I believe that FDs in the Haskell context can be quite different from FDs in the database context. - Martin
While you're looking for unusual examples of fundeps, you might also want to consider things like:
class C a b c | a -> b, b -> c
Note that this is subtly different from a -> b c because
{a -> b, b -> c} |= {a -> b c}
while the reverse does not hold. Instead of type classes, I'll give you some more down-to-earth examples of relations that satisfy these dependencies:
{Paper, Conference, Year} {Professor, University, Country} {Person, FavoriteFood, FoodGroup} ...
For further insight, you might want to take a look at the theory of relational databases to see how functional dependencies are used there. In that context, some sets of dependencies (such as {a -> b, b -> c}) can be interpreted as indicators of bad design. This, in turn, might give you some ideas about the kinds of dependencies you can expect to encounter in well-designed Haskell code. (Of course, you might still find examples in other Haskell code of dependencies that would make a database person wince :-)

Martin Sulzmann wrote:
Mark P Jones wrote:
In fact, the two sets of dependencies that you have given here are provably equivalent, so it would be decidedly odd to have a "type improvement" system that distinguishes between them.
Based on the FD-CHR formulation, for the single-range FD case we get [...] which is clearly weaker. [...] So, I conclude that in the Haskell type improvement context there's clearly a difference among single-range and multi-range FDs.
This seems like a flaw in FD-CHR, rather than a fundamental difference between the dependencies.
Of course, we could define multi-range FDs in terms of single-range FDs which then trivially solves the "equivalence" problem (but some user may be disappointed that their multi-range FDs yield weaker improvement).
Why not instead transform single-range FDs into multi-range ones where possible? Ganesh ============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ==============================================================================

Sittampalam, Ganesh wrote:
Martin Sulzmann wrote:
Mark P Jones wrote:
In fact, the two sets of dependencies that you have given here are provably equivalent, so it would be decidedly odd to have a "type improvement" system that distinguishes between them.
Based on the FD-CHR formulation, for the single-range FD case we get [...] which is clearly weaker. [...] So, I conclude that in the Haskell type improvement context there's clearly a difference among single-range and multi-range FDs.
This seems like a flaw in FD-CHR, rather than a fundamental difference between the dependencies.
Of course, we could define multi-range FDs in terms of single-range FDs which then trivially solves the "equivalence" problem (but some user may be disappointed that their multi-range FDs yield weaker improvement).
Why not instead transform single-range FDs into multi-range ones where possible?
That's a perfectly reasonable assumption and would establish the logical property that a -> b /\ a -> c iff a -> b /\ c for FDs (by definition). But what about programmers who'd like that C [x] y z yields the improvement y = [b], z =[b] where class C a b c | a -> b c instance C a b b => C [a] [b] [b] It's hard to say who's right or wrong but there's a design space which needs to be explored further. Martin

Why not instead transform single-range FDs into multi-range ones where possible?
That's a perfectly reasonable assumption and would establish the logical property that
a -> b /\ a -> c iff a -> b /\ c
for FDs (by definition).
But what about programmers who'd like that
C [x] y z yields the improvement y = [b], z =[b]
where
class C a b c | a -> b c instance C a b b => C [a] [b] [b]
Isn't that precisely what you earlier said would happen with multi-range FDs? Either I'm missing some difference or we're talking at cross-purposes. My suggestion is that "class C a b c | a -> b c" and "class C a b c | a -> b, a -> c" be both treated as the former case, leading to both cases having the y=[b],z=[b] improvement as above. Cheers, Ganesh ============================================================================== Please access the attached hyperlink for an important electronic communications disclaimer: http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html ==============================================================================

Sittampalam, Ganesh wrote:
Why not instead transform single-range FDs into multi-range ones where possible?
That's a perfectly reasonable assumption and would establish the logical property that
a -> b /\ a -> c iff a -> b /\ c
for FDs (by definition).
But what about programmers who'd like that
C [x] y z yields the improvement y = [b], z =[b]
where
class C a b c | a -> b c instance C a b b => C [a] [b] [b]
Isn't that precisely what you earlier said would happen with multi-range FDs? Either I'm missing some difference or we're talking at cross-purposes.
My suggestion is that
"class C a b c | a -> b c" and "class C a b c | a -> b, a -> c" be both treated as the former case, leading to both cases having the y=[b],z=[b] improvement as above.
Misunderstanding. I see what you mean. Yes, I agree let's consider a -> b, a -> c as equivalent to a -> b c (I argued the other direction in my earlier email). One subtle point (Tom and I just discussed). It could happen that the programmer writes class SuperCtxt => C a b c | a -> b but there could be an implicit dependency a -> c arising from the super class context SuperCtxt. Hence, you suddenly get a -> b c. The problem is to generate the proper improvement rules. Well, it's not hard to generate these rules we just need to make sure that the rules generated match the programmers intuition how functional dependencies behave. Martin

class C a b c | a -> b, a -> c instance C a b b => C [a] [b] [b]
Suppose we encounter the constraint C [x] y z
interesting example. splitting improvement into two rules seems to lose the (b1=b2) constraint that spans both: [O] C [x] y z => y=[b1]. C [x] y z => z=[b2]. my first thought was that the improvement rules look too general as the instance only applies if (y=z), so i was tempted to add that constraint via guards or patterns: [A] C [x] y [b] => y=[b]. C [x] [b] z => z=[b]. but the FD states that knowing a is sufficient to know both b and c, so one could argue that (y=z), just like (y=[b]) and (z=[b]) should be a consequence rather than a condition for these improvements: [B] C [x] y z => y=z, y=[b]. C [x] y z => y=z, z=[b]. it is interesting to observe Hugs (20051031) vs GHCi (6.9.20080217) on this example and some slight variations (see below). it appears [1] that Hugs follows [B] while GHCi follows [A], and that [2,3] GHCi generally treats structural and unification constraints differently. i have no idea how GHCi comes up with the type (x, [Bool], [Char]) in [2]. btw, Ross started a survey of FD examples/requirements a while ago on the Haskell prime list - it would be nice to have any results of his and your's online (on the wiki perhaps?), especially as documentation regarding different interpretations of the same language extensions between Hugs and GHC (overlap resolution & FDs comes to mind as being fairly similar to this example): http://www.haskell.org/pipermail/haskell-prime/2006-April/001334.html http://www.haskell.org/pipermail/haskell-prime/2006-April/001440.html claus [1] class C a b c | a -> b, a -> c instance C a b b => C [a] [b] [b] Hugs: :t undefined::C [x] y z => (x,y,z) undefined :: C [a] [b] [b] => (a,[b],[b]) GHCi: :t undefined :: C [x] y z => (x,y,z) undefined :: C [x] y z => (x,y,z) :: (C [x] [b] [b1]) => (x, [b], [b1]) [2] class C a b c | a -> b, a -> c instance C a b b => C [a] [b] [b] instance C [a] [Bool] [Char] Hugs: ERROR file:.\C.hs:8 - Instances are not consistent with dependencies *** This instance : C [a] [Bool] [Char] *** Conflicts with : C [a] [b] [b] *** For class : C a b c *** Under dependency : a -> b GHCi: Ok, modules loaded: Main. :t undefined :: C [x] y z => (x,y,z) undefined :: C [x] y z => (x,y,z) :: (x, [Bool], [Char]) [3] class C a b c | a -> b, a -> c instance C a b b => C [a] [b] [b] instance C [a] Bool Char Hugs: ERROR file:.\C.hs:8 - Instances are not consistent with dependencies *** This instance : C [a] Bool Char *** Conflicts with : C [a] [b] [b] *** For class : C a b c *** Under dependency : a -> b GHCi: C:\Documents and Settings\cr3\Desktop\C.hs:7:0: Functional dependencies conflict between instance declarations: instance (C a b b) => C [a] [b] [b] -- Defined at C:\Documents and Settings\cr3\Desktop\C.hs:7:0-32 instance C [a] Bool Char -- Defined at C:\Documents and Settings\cr3\Desktop\C.hs:8:0-23 Failed, modules loaded: none.

a little more experimentation leaves me confused. consider
[4]
class C a b c | a -> b -- , a -> c
instance C a b b => C [a] [b] [b]
Hugs:
:t undefined :: C [x] y z => (x,y,z)
undefined :: C [a] [b] c => (a,[b],c)
GHCi:
:t undefined :: C [x] y z => (x,y,z)
undefined :: C [x] y z => (x,y,z) :: (C [x] [b] z) => (x, [b], z)
both systems improve 'y' to '[b]', but not to '[b] where z=[b]'.
ok, the third parameter is not in range of an FD, so cannot be
instantiated by improvement, and without that, 'y' cannot be
instantiated as far as the FD would suggest. it is slightly
surprising that 'y' get partially instantiated at this stage.
however, if we try to help the process along by instantiating
'z' to '[b]' ourselves, we get:
[5]
Hugs:
:t undefined :: C [x] y [b] => (x,y,[b])
undefined :: C [a] [b] [c] => (a,[b],[c])
GHCi:
:t undefined :: C [x] y [b] => (x,y,[b])
undefined :: C [x] y [b] => (x,y,[b]) :: (C [x] [b1] [b]) => (x, [b1], [b])
i would have expected 'C a c c => (a,[c],[c])' here, as
only instantiation of 'y' is required; so my intuition is still off,
and neither [A] nor [B] seems to capture Hugs' interpretation.
in particular, i don't see how to account for [5], even with
a refined ruleset that accounts for [4].
suggestions?-)
claus
----- Original Message -----
From: "Claus Reinke"
class C a b c | a -> b, a -> c instance C a b b => C [a] [b] [b]
Suppose we encounter the constraint C [x] y z
interesting example. splitting improvement into two rules seems to lose the (b1=b2) constraint that spans both:
[O] C [x] y z => y=[b1]. C [x] y z => z=[b2].
my first thought was that the improvement rules look too general as the instance only applies if (y=z), so i was tempted to add that constraint via guards or patterns:
[A] C [x] y [b] => y=[b]. C [x] [b] z => z=[b].
but the FD states that knowing a is sufficient to know both b and c, so one could argue that (y=z), just like (y=[b]) and (z=[b]) should be a consequence rather than a condition for these improvements:
[B] C [x] y z => y=z, y=[b]. C [x] y z => y=z, z=[b].
it is interesting to observe Hugs (20051031) vs GHCi (6.9.20080217) on this example and some slight variations (see below). it appears [1] that Hugs follows [B] while GHCi follows [A], and that [2,3] GHCi generally treats structural and unification constraints differently. i have no idea how GHCi comes up with the type (x, [Bool], [Char]) in [2].
btw, Ross started a survey of FD examples/requirements a while ago on the Haskell prime list - it would be nice to have any results of his and your's online (on the wiki perhaps?), especially as documentation regarding different interpretations of the same language extensions between Hugs and GHC (overlap resolution & FDs comes to mind as being fairly similar to this example):
http://www.haskell.org/pipermail/haskell-prime/2006-April/001334.html http://www.haskell.org/pipermail/haskell-prime/2006-April/001440.html
claus
[1] class C a b c | a -> b, a -> c instance C a b b => C [a] [b] [b]
Hugs: :t undefined::C [x] y z => (x,y,z) undefined :: C [a] [b] [b] => (a,[b],[b])
GHCi: :t undefined :: C [x] y z => (x,y,z) undefined :: C [x] y z => (x,y,z) :: (C [x] [b] [b1]) => (x, [b], [b1])
[2] class C a b c | a -> b, a -> c instance C a b b => C [a] [b] [b] instance C [a] [Bool] [Char]
Hugs: ERROR file:.\C.hs:8 - Instances are not consistent with dependencies *** This instance : C [a] [Bool] [Char] *** Conflicts with : C [a] [b] [b] *** For class : C a b c *** Under dependency : a -> b
GHCi: Ok, modules loaded: Main. :t undefined :: C [x] y z => (x,y,z) undefined :: C [x] y z => (x,y,z) :: (x, [Bool], [Char])
[3] class C a b c | a -> b, a -> c instance C a b b => C [a] [b] [b] instance C [a] Bool Char
Hugs: ERROR file:.\C.hs:8 - Instances are not consistent with dependencies *** This instance : C [a] Bool Char *** Conflicts with : C [a] [b] [b] *** For class : C a b c *** Under dependency : a -> b
GHCi: C:\Documents and Settings\cr3\Desktop\C.hs:7:0: Functional dependencies conflict between instance declarations: instance (C a b b) => C [a] [b] [b] -- Defined at C:\Documents and Settings\cr3\Desktop\C.hs:7:0-32 instance C [a] Bool Char -- Defined at C:\Documents and Settings\cr3\Desktop\C.hs:8:0-23 Failed, modules loaded: none.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

a little more experimentation leaves me confused. consider
[4] class C a b c | a -> b -- , a -> c instance C a b b => C [a] [b] [b]
Hugs: :t undefined :: C [x] y z => (x,y,z) undefined :: C [a] [b] c => (a,[b],c)
GHCi: :t undefined :: C [x] y z => (x,y,z) undefined :: C [x] y z => (x,y,z) :: (C [x] [b] z) => (x, [b], z)
both systems improve 'y' to '[b]', but not to '[b] where z=[b]'.
ok, the third parameter is not in range of an FD, so cannot be instantiated by improvement, and without that, 'y' cannot be instantiated as far as the FD would suggest. it is slightly surprising that 'y' get partially instantiated at this stage.
My understanding of an FD a -> b is to improve, or in other words instantiate, b as much as possible based on information from a. With C [x] y z we know for sure that y must be [b] for some b. Improvement adds (propagates) this information we know for sure. With our limited information, we may not know what b is, but just knowing the list type constructor [] may already be useful. For instance, if we had a second type class constraint D y for which there is an instance instance D [a] where ... Then inferring that y = [b] will allow us to figure out that we can use the above instance for it.
however, if we try to help the process along by instantiating 'z' to '[b]' ourselves, we get:
[5] Hugs: :t undefined :: C [x] y [b] => (x,y,[b]) undefined :: C [a] [b] [c] => (a,[b],[c])
GHCi: :t undefined :: C [x] y [b] => (x,y,[b]) undefined :: C [x] y [b] => (x,y,[b]) :: (C [x] [b1] [b]) => (x, [b1], [b])
i would have expected 'C a c c => (a,[c],[c])' here, as only instantiation of 'y' is required; so my intuition is still off, and neither [A] nor [B] seems to capture Hugs' interpretation.
You did not provide the FD a -> c (or even a -> b c). That means that you did not allow the type checker to improve c based on a. Nor did you provide the FD a c -> b. For that reason the type checker does not use any information from the third parameter to improve the second parameter. It does indeed feel somewhat strange, because there is no alternative for y (except if you allow overlapping instances and add e.g. an instance C [a] [b] [Int]). Cheers, Tom -- Tom Schrijvers Department of Computer Science K.U. Leuven Celestijnenlaan 200A B-3001 Heverlee Belgium tel: +32 16 327544 e-mail: tom.schrijvers@cs.kuleuven.be url: http://www.cs.kuleuven.be/~toms/

Hello,
On Wed, Apr 16, 2008 at 11:06 PM, Martin Sulzmann
3) Multi-range FDs
Consider
class C a b c | a -> b c
instance C a b b => C [a] [b] [b]
This time it's straightforward.
C [x] y z yields the improvement y = [b] and z = [b] which then allows us to apply the instance.
I don't think that this improvement rule is justified (unless there are some assumptions that are added to the system that go beyond FD?). By the way, note that the above example does not have any instances for C, so lets first add a base case like this: instance C Char Bool Bool Now the instances for C are: { C Char Bool Bool, C [Char] [Bool] [Bool], ... }. Certainly, if you just consider these instances, then the improvement rule that you suggest is valid. However, suppose that we also add the instance: instance C [Int] Char Bool Note that this instance does not violate the FD: if we know the first argument, then we know exactly what are the other two arguments. In this context, it is not OK to improve C [x] y z as you suggest because 'x' may be instantiate to 'Int'. -Iavor

Iavor Diatchki wrote:
Hello,
On Wed, Apr 16, 2008 at 11:06 PM, Martin Sulzmann
wrote: 3) Multi-range FDs
Consider
class C a b c | a -> b c
instance C a b b => C [a] [b] [b]
This time it's straightforward.
C [x] y z yields the improvement y = [b] and z = [b] which then allows us to apply the instance.
I don't think that this improvement rule is justified (unless there are some assumptions that are added to the system that go beyond FD?). By the way, note that the above example does not have any instances for C, so lets first add a base case like this:
instance C Char Bool Bool
Now the instances for C are: { C Char Bool Bool, C [Char] [Bool] [Bool], ... }. Certainly, if you just consider these instances, then the improvement rule that you suggest is valid. However, suppose that we also add the instance:
instance C [Int] Char Bool
Note that this instance does not violate the FD: if we know the first argument, then we know exactly what are the other two arguments. In this context, it is not OK to improve C [x] y z as you suggest because 'x' may be instantiate to 'Int'
There possible points of view here. Consider a -> b c as a short-hand for a -> b, a -> c. That's fine. But we may also want to go beyond (single-range) FDs. That's why I have in mind. Therefore, a -> b, a -> c is a short-hand for a -> b, c. (At least there's one supporter, Ganesh, assuming that Tom and I are neutral :) ) Suppose we encode the multi-range FD a -> b, c as defined in the FD-CHR paper. Then, class C a b c | a -> b c instance C a b b => C [a] [b] [b] instance C [Int] Char Bool leads to an instance improvement/instance improvement conflict, like in the single-range FD case class D a b | a -> b instance D a a => D [a] [a] instance D [Int] Char All of the above design choices make sense. There's no right or wrong. But it's wrong to simply ignore possible FD variants which go beyond single-range FDs. Martin

Hello,
On Thu, Apr 17, 2008 at 10:26 AM, Martin Sulzmann
leads to an instance improvement/instance improvement conflict, like in the single-range FD case
class D a b | a -> b
instance D a a => D [a] [a] instance D [Int] Char
Sorry to be picky but there is no violation of the FD here. Note that the class D has only a single ground instance and to violate an FD you need at least two. As in the previous example, we can add an instance like this: instance D Char Char This results in more ground instances: { D [Int] Char, D Char Char, D [Char] [Char], ... } but again, there is no violation of the FD. I think that a lot of the confusion in discussions such as this one (and we've had a few of those :-) stems from the fact that the term "functional dependency" seems to have become heavily overloaded. Often, the basic concept is mixed with (i) concepts related to checking that the basic concept holds (e.g., various restrictions on instances, etc), (ii) concepts related to how we might want to use the basic concept (e.g., what improvement rules to use). Of course, (i) and (ii) are very important, and there are a lot possible design choices. However, a number of the discussions I have seen go like this: 1) In general, it is hard to check if instances violate the stated functional dependencies. 2) So we have more restrictive rules, that are easier to check. 3) These more restrictive rules give us stronger guarantees, so we have more opportunity for improvement. While there is nothing inherently wrong with this, it is important to note that the extra improvement is not a result of the use of FDs but rather, from the extra restrictions that we placed on the instances. I think that this distinction is important because (i) it avoids mixing concepts, and (ii) points to new things that we may want to consider. For example, I think that there is an opportunity for improvement in situations where is class is not exported from a module. Then we know the full set of instances for the class, and we may be able to compute improvement rules. Hope this helps! -Iavor -Iavor

Iavor Diatchki wrote:
Hello,
On Thu, Apr 17, 2008 at 10:26 AM, Martin Sulzmann
wrote: leads to an instance improvement/instance improvement conflict, like in the single-range FD case
class D a b | a -> b
instance D a a => D [a] [a] instance D [Int] Char
Sorry to be picky but there is no violation of the FD here. Note that the class D has only a single ground instance and to violate an FD you need at least two. As in the previous example, we can add an instance like this:
instance D Char Char
This results in more ground instances: { D [Int] Char, D Char Char, D [Char] [Char], ... } but again, there is no violation of the FD.
I think that a lot of the confusion in discussions such as this one (and we've had a few of those :-) stems from the fact that the term "functional dependency" seems to have become heavily overloaded. Often, the basic concept is mixed with (i) concepts related to checking that the basic concept holds (e.g., various restrictions on instances, etc), (ii) concepts related to how we might want to use the basic concept (e.g., what improvement rules to use). Of course, (i) and (ii) are very important, and there are a lot possible design choices. However, a number of the discussions I have seen go like this: 1) In general, it is hard to check if instances violate the stated functional dependencies. 2) So we have more restrictive rules, that are easier to check. 3) These more restrictive rules give us stronger guarantees, so we have more opportunity for improvement. While there is nothing inherently wrong with this, it is important to note that the extra improvement is not a result of the use of FDs but rather, from the extra restrictions that we placed on the instances. I think that this distinction is important because (i) it avoids mixing concepts, and (ii) points to new things that we may want to consider. For example, I think that there is an opportunity for improvement in situations where is class is not exported from a module. Then we know the full set of instances for the class, and we may be able to compute improvement rules.
Hope this helps! -Iavor
Can you pl specify the improvement rules for your interpretation of FDs. That would help! I'm simply following Mark Jones' style FDs. Mark's ESOP'00 paper has a consistency condition: If two instances match on the FD domain then the must also match on their range. The motivation for this condition is to avoid inconsistencies when deriving improvement rules from instances. For class D a b | a -> b instance D a a => D [a] [a] instance D [Int] Char we get D [a] b ==> b =[a] D [Int] b ==> b=Char In case of D [Int] b we therefore get b=Char *and* b =[a] which leads to a (unification) error. The consistency condition avoids such situations. The beauty of formalism FDs with CHRs (or type functions/families) is that the whole improvement process becomes explicit. Of course, it has to match the programmer's intuition. See the discussion regarding multi-range FDs. Martin

Hello,
On Thu, Apr 17, 2008 at 12:05 PM, Martin Sulzmann
Can you pl specify the improvement rules for your interpretation of FDs. That would help!
Each functional dependency on a class adds one extra axiom to the system (aka CHR rule, improvement rule). For the example in question we have: class D a b | a -> b where ... the extra axiom is: forall a b c. (D a b, D a c) => (b = c) This is the definition of "functional dependency"---it specifies that the relation 'D' is functional. An improvement rule follows from a functional dependency if it can be derived from this rule. For example, if we have an instance (i.e., another axiom): instance D Char Bool Then we can derive the following theorem: (D Char a) => (a = Bool) I think that in the CHR paper this was called "instance" improvement. Note that this is not an extra axiom but rather a theorem---adding it to the system as an axiom does not make the system any more expressive. Now consider what happens when we have a qualified instance: instance D a a => D [a] [a] We can combine this with the FD axiom to get: (D a a, D [a] b) => b = [a] This is all that follows from the functional dependency. Of course, in the presence of other instances, we could obtain more improvement rules. As for the "consistency rule", it is intended to ensure that instances are consistent with the FD axiom. As we saw from the previous examples, it is a bit conservative in that it rejects some instances that do not violate the functional dependency. Now, we could choose to exploit this fact to compute stronger improvement rules---nothing wrong with that. However, this goes beyond FDs. -Iavor
I'm simply following Mark Jones' style FDs.
Mark's ESOP'00 paper has a consistency condition: If two instances match on the FD domain then the must also match on their range. The motivation for this condition is to avoid inconsistencies when deriving improvement rules from instances.
For
class D a b | a -> b
instance D a a => D [a] [a] instance D [Int] Char
we get
D [a] b ==> b =[a] D [Int] b ==> b=Char
In case of
D [Int] b we therefore get b=Char *and* b =[a] which leads to a (unification) error. The consistency condition avoids such situations.
The beauty of formalism FDs with CHRs (or type functions/families) is that the whole improvement process becomes explicit. Of course, it has to match the programmer's intuition. See the discussion regarding multi-range FDs.
Martin

Thanks Iavor! Things become now clear. Let's consider our running example class D a b | a -> b instance D a b => D [a] [b] which we can write in CHR notation D a b, D a c ==> b=c (FD) D [a] [b] <=> D a b (Inst) These rules overlap. Let's consider the critical pair D [a] [b], D [a] c The following two derivations are possible D [a] [b], D [a] c -->FD D [a] [b], c = [b] -->Inst D a b, c = [b] D [a] [b], D [a] c -->Inst D a b, D [a] c The two final stores differ which means that the CHR system is non-confluent. Hence, the proof theory is (potentially) incomplete. What does this mean? Logically true statement may not be derivable using our CHR/typeclass-FD solver. Iavor suggests to add the rule D [a] c, D a b ==> c = [b] (Imp1) Makes perfect sense! This rule is indeed a theorem and makes the system confluent. But that's not what the FD-CHR paper does. The FD-CHR paper generates the "stronger" rule D [a] c ==> c = [b] (Imp2) This rule is NOT a theorem (ie logical consequence from the FD and Inst rule). But this rule also makes the system confluent. Why does the FD-CHR paper suggest this rule. Some reasons: - the (Imp2) matches the GHC and I believe also Hugs implementation - the (Imp2) is "easier" to implement, we only need to look for a single constraint when firing the rule - (Arguable) The (Imp2) matches better the programmer's intuition. We only consider the instance head when generating improvement but ignore the instance context. - (Historical note: The rule suggested by Iavor were discussed when writing the FD-CHR paper but somehow we never pursued this alternative design space. I have to dig out some old notes, maybe there some other reasons, infinite completion, why this design space wasn't pursued). To summarize, I see now where the confusion lies. The FD-CHR studies a "stronger" form of FDs where the CHR improvement rules generated guarantee confluence but the rules are not necessarily logical consequence. Therefore, the previously discussed property a -> b and a -> c iff a -> b c does of course NOT hold. That is, the combination of improvement rules derived from a -> b and a -> c is NOT equivalent to the improvement rules derived from a -> b c. Logically, the equivalence obviously holds. Martin Iavor Diatchki wrote:
Hello,
On Thu, Apr 17, 2008 at 12:05 PM, Martin Sulzmann
wrote: Can you pl specify the improvement rules for your interpretation of FDs. That would help!
Each functional dependency on a class adds one extra axiom to the system (aka CHR rule, improvement rule). For the example in question we have:
class D a b | a -> b where ...
the extra axiom is:
forall a b c. (D a b, D a c) => (b = c)
This is the definition of "functional dependency"---it specifies that the relation 'D' is functional. An improvement rule follows from a functional dependency if it can be derived from this rule. For example, if we have an instance (i.e., another axiom):
instance D Char Bool
Then we can derive the following theorem:
(D Char a) => (a = Bool)
I think that in the CHR paper this was called "instance" improvement. Note that this is not an extra axiom but rather a theorem---adding it to the system as an axiom does not make the system any more expressive. Now consider what happens when we have a qualified instance:
instance D a a => D [a] [a]
We can combine this with the FD axiom to get:
(D a a, D [a] b) => b = [a]
This is all that follows from the functional dependency. Of course, in the presence of other instances, we could obtain more improvement rules.
As for the "consistency rule", it is intended to ensure that instances are consistent with the FD axiom. As we saw from the previous examples, it is a bit conservative in that it rejects some instances that do not violate the functional dependency. Now, we could choose to exploit this fact to compute stronger improvement rules---nothing wrong with that. However, this goes beyond FDs.
-Iavor
I'm simply following Mark Jones' style FDs.
Mark's ESOP'00 paper has a consistency condition: If two instances match on the FD domain then the must also match on their range. The motivation for this condition is to avoid inconsistencies when deriving improvement rules from instances.
For
class D a b | a -> b
instance D a a => D [a] [a] instance D [Int] Char
we get
D [a] b ==> b =[a] D [Int] b ==> b=Char
In case of
D [Int] b we therefore get b=Char *and* b =[a] which leads to a (unification) error. The consistency condition avoids such situations.
The beauty of formalism FDs with CHRs (or type functions/families) is that the whole improvement process becomes explicit. Of course, it has to match the programmer's intuition. See the discussion regarding multi-range FDs.
Martin

I now recall the reason for NOT using D a b, D [a] c ==> c = [b] The reason is that the above rule creates a new critical pair with instance D a b => D [a] [b] To resolve the critical pair we need yet another rule D a b, D [[a]] c ==> c =[[b]] You can already see where this leads to. In general, we need an infinite rules of the form D a b, D [a]^k c ==> c = [b]^k where [a]^k stands for the k nested list [ ... [a] ... ] The FD-CHR approach therefore proposes to use D [a] c ==> c = [b] which is a "stronger" rule (that is, is not a logical consequence). Martin Martin Sulzmann wrote:
Thanks Iavor! Things become now clear.
Let's consider our running example
class D a b | a -> b instance D a b => D [a] [b]
which we can write in CHR notation
D a b, D a c ==> b=c (FD)
D [a] [b] <=> D a b (Inst)
These rules overlap.
Let's consider the critical pair
D [a] [b], D [a] c
The following two derivations are possible
D [a] [b], D [a] c -->FD D [a] [b], c = [b] -->Inst D a b, c = [b]
D [a] [b], D [a] c -->Inst D a b, D [a] c
The two final stores differ which means that the CHR system is non-confluent. Hence, the proof theory is (potentially) incomplete. What does this mean? Logically true statement may not be derivable using our CHR/typeclass-FD solver.
Iavor suggests to add the rule
D [a] c, D a b ==> c = [b] (Imp1)
Makes perfect sense!
This rule is indeed a theorem and makes the system confluent.
But that's not what the FD-CHR paper does.
The FD-CHR paper generates the "stronger" rule
D [a] c ==> c = [b] (Imp2)
This rule is NOT a theorem (ie logical consequence from the FD and Inst rule). But this rule also makes the system confluent.
Why does the FD-CHR paper suggest this rule. Some reasons:
- the (Imp2) matches the GHC and I believe also Hugs implementation - the (Imp2) is "easier" to implement, we only need to look for a single constraint when firing the rule - (Arguable) The (Imp2) matches better the programmer's intuition. We only consider the instance head when generating improvement but ignore the instance context. - (Historical note: The rule suggested by Iavor were discussed when writing the FD-CHR paper but somehow we never pursued this alternative design space. I have to dig out some old notes, maybe there some other reasons, infinite completion, why this design space wasn't pursued).
To summarize, I see now where the confusion lies. The FD-CHR studies a "stronger" form of FDs where the CHR improvement rules generated guarantee confluence but the rules are not necessarily logical consequence. Therefore, the previously discussed property
a -> b and a -> c iff a -> b c
does of course NOT hold. That is, the combination of improvement rules derived from a -> b and a -> c is NOT equivalent to the improvement rules derived from a -> b c. Logically, the equivalence obviously holds.
Martin
Iavor Diatchki wrote:
Hello,
On Thu, Apr 17, 2008 at 12:05 PM, Martin Sulzmann
wrote: Can you pl specify the improvement rules for your interpretation of FDs. That would help!
Each functional dependency on a class adds one extra axiom to the system (aka CHR rule, improvement rule). For the example in question we have:
class D a b | a -> b where ...
the extra axiom is:
forall a b c. (D a b, D a c) => (b = c)
This is the definition of "functional dependency"---it specifies that the relation 'D' is functional. An improvement rule follows from a functional dependency if it can be derived from this rule. For example, if we have an instance (i.e., another axiom):
instance D Char Bool
Then we can derive the following theorem:
(D Char a) => (a = Bool)
I think that in the CHR paper this was called "instance" improvement. Note that this is not an extra axiom but rather a theorem---adding it to the system as an axiom does not make the system any more expressive. Now consider what happens when we have a qualified instance:
instance D a a => D [a] [a]
We can combine this with the FD axiom to get:
(D a a, D [a] b) => b = [a]
This is all that follows from the functional dependency. Of course, in the presence of other instances, we could obtain more improvement rules.
As for the "consistency rule", it is intended to ensure that instances are consistent with the FD axiom. As we saw from the previous examples, it is a bit conservative in that it rejects some instances that do not violate the functional dependency. Now, we could choose to exploit this fact to compute stronger improvement rules---nothing wrong with that. However, this goes beyond FDs.
-Iavor
I'm simply following Mark Jones' style FDs.
Mark's ESOP'00 paper has a consistency condition: If two instances match on the FD domain then the must also match on their range. The motivation for this condition is to avoid inconsistencies when deriving improvement rules from instances.
For
class D a b | a -> b
instance D a a => D [a] [a] instance D [Int] Char
we get
D [a] b ==> b =[a] D [Int] b ==> b=Char
In case of
D [Int] b we therefore get b=Char *and* b =[a] which leads to a (unification) error. The consistency condition avoids such situations.
The beauty of formalism FDs with CHRs (or type functions/families) is that the whole improvement process becomes explicit. Of course, it has to match the programmer's intuition. See the discussion regarding multi-range FDs.
Martin

On 18 Apr 2008, at 20:04, Martin Sulzmann wrote:
Let's consider our running example
class D a b | a -> b instance D a b => D [a] [b]
which we can write in CHR notation
D a b, D a c ==> b=c (FD)
D [a] [b] <=> D a b (Inst)
These rules overlap.
I experimented with translations into GNU Prolog (gprolog). Since "=" is hard to get working in Prolog unless integrated into unification, I tried (using the idea of rewriting unique existence as functions, possible if one assumes the axiom of choice): class(d, A, b(A)). instance(d, l(A), l(B)) :- class(d, A, B). Then: ?- instance(d, l(A), l(B)). B = b(A) ?- instance(d, l(A), C). C = l(b(A)) ?- instance(d, l(A), l(B)), instance(d, l(A), C). B = b(A) C = l(b(A)) Though I am not sure about the intended semantics, it does produce unique solutions. Hans

On Fri, 25 Apr 2008, Hans Aberg wrote:
On 18 Apr 2008, at 20:04, Martin Sulzmann wrote:
Let's consider our running example
class D a b | a -> b instance D a b => D [a] [b]
which we can write in CHR notation
D a b, D a c ==> b=c (FD)
D [a] [b] <=> D a b (Inst)
These rules overlap.
I experimented with translations into GNU Prolog (gprolog). Since "=" is hard to get working in Prolog unless integrated into unification, I tried (using the idea of rewriting unique existence as functions, possible if one assumes the axiom of choice): class(d, A, b(A)). instance(d, l(A), l(B)) :- class(d, A, B). Then: ?- instance(d, l(A), l(B)). B = b(A)
?- instance(d, l(A), C). C = l(b(A))
?- instance(d, l(A), l(B)), instance(d, l(A), C). B = b(A) C = l(b(A)) Though I am not sure about the intended semantics, it does produce unique solutions.
Prolog works under the assumption of a closed world. That's contrary to the open world view of regular type classes. So these aren't the intended semantics. Tom -- Tom Schrijvers Department of Computer Science K.U. Leuven Celestijnenlaan 200A B-3001 Heverlee Belgium tel: +32 16 327544 e-mail: tom.schrijvers@cs.kuleuven.be url: http://www.cs.kuleuven.be/~toms/

On 25 Apr 2008, at 14:20, Tom Schrijvers wrote:
Prolog works under the assumption of a closed world. That's contrary to the open world view of regular type classes. So these aren't the intended semantics.
By which I gather you mean the interpretation of ":-" as logical connective "=>" rather than provability "|-"? My point, though, was to interpret class a b | a -> b as a functional dependency b = b(a) rather than as D a b, D a c ==> b=c Thus trying to eliminate the use of "=". Might that be exploited in the type theory context? Hans

On Fri, 25 Apr 2008, Hans Aberg wrote:
On 25 Apr 2008, at 14:20, Tom Schrijvers wrote:
Prolog works under the assumption of a closed world. That's contrary to the open world view of regular type classes. So these aren't the intended semantics.
By which I gather you mean the interpretation of ":-" as logical connective "=>" rather than provability "|-"?
What I meant was that when Prolog says "there are no more solutions", it doesn't know of any more. In realtiy it means "there no more solutions under the closed world assumption". That means there could be more solutions if you haven't told Prolog everything. In this context, there may be more class instances (you simply haven't told the system yet).
My point, though, was to interpret class a b | a -> b as a functional dependency b = b(a) rather than as D a b, D a c ==> b=c Thus trying to eliminate the use of "=".
I don't follow you here. Tom -- Tom Schrijvers Department of Computer Science K.U. Leuven Celestijnenlaan 200A B-3001 Heverlee Belgium tel: +32 16 327544 e-mail: tom.schrijvers@cs.kuleuven.be url: http://www.cs.kuleuven.be/~toms/

On 25 Apr 2008, at 15:38, Tom Schrijvers wrote:
Prolog works under the assumption of a closed world. That's contrary to the open world view of regular type classes. So these aren't the intended semantics.
By which I gather you mean the interpretation of ":-" as logical connective "=>" rather than provability "|-"?
What I meant was that when Prolog says "there are no more solutions", it doesn't know of any more. In realtiy it means "there no more solutions under the closed world assumption". That means there could be more solutions if you haven't told Prolog everything. In this context, there may be more class instances (you simply haven't told the system yet).
I had no intention to deal with that problem. Just forget what Prolog says, and when it says "there are no more solutions" think of it as "no more solutions determined". (If one interprets ":-" as provability "|-", there needs to be additional axioms for the object theory, and if the theory is consistent, it becomes possible to prove that there are no more solutions.)
My point, though, was to interpret class a b | a -> b as a functional dependency b = b(a) rather than as D a b, D a c ==> b=c Thus trying to eliminate the use of "=".
I don't follow you here.
I got ?- instance(d, l(A), l(B)). B = b(A) ?- instance(d, l(A), C). C = l(b(A)) so pattern-wise C and l(B) are the same. But I do not bother introduce an explicit operator "=". So at least in this case, if say D [a] Int will be reject as Int is not of the feom l(_). If one has D [Int] [Char] and tries to define D [Int] [Float], the leads to trying to associate the implicit b(Int) with both Char and Float, which would be rejected. Hans

Sorry to be picky but there is no violation of the FD here. Note that the class D has only a single ground instance and to violate an FD you need at least two.
perhaps you are thinking of functional dependencies as being defined extensionally, over the extent of the type relations specified by multiparameter type classes? somewhat counterintuitively, this isn't quite the case (just as instance selection doesn't take contexts into account..). to get an FD conflict, it is sufficient to have two conflicting constraints, no need for any instances. consider module Fail(Fail) where class X a class X a => Fail a module Main where import Fail class C a b | a -> b instance Fail a => C [a] Bool since superclass X has no instances and is not exported from module Fail, class Fail, though exported, can have no instances. so the instance declaration given for C seems entirely useless, as far as the relation over types is concerned - there are no ground instances of C. nevertheless, it is taken into account when considering functional dependencies: Hugs: :t undefined :: C [a] b => (a,b) undefined :: C [a] Bool => (a,Bool) and so adding an instance for 'C [a] Char' would lead to an FD conflict. just checking, claus

To reuse a favorite word, I think that any implementation that distinguishes
'a -> b, a -> c' from 'a -> b c' is broken. :)
It does not implement FD, but something else. Maybe this something else is
useful, but if one of the forms is strictly more powerful than the other
then I don't see why you would ever want the less powerful one.
-- Lennart
On Thu, Apr 17, 2008 at 7:06 AM, Martin Sulzmann
Mark P Jones wrote:
Martin Sulzmann wrote:
We're also looking for (practical) examples of "multi-range" functional dependencies
class C a b c | c -> a b
Notice that there are multiple (two) parameters in the range of the FD.
It's tempting to convert the above to
class C a b c | c -> a, c -> b
but this yields a weaker (in terms of type improvement) system.
I agree with Iavor.
In fact, the two sets of dependencies that you have given here are provably equivalent, so it would be decidedly odd to have a "type improvement" system that distinguishes between them.
Consider
class C a b c | a -> b, a -> c
instance C a b b => C [a] [b] [b]
Suppose we encounter the constraint
C [x] y z
What results can we expect from type improvement?
1) Single-range non-full FDs in GHC following the FD-CHR formulation:
The first FD C a b c | a -> b in combination with the instance head C [a] [b] [b] will yield
C [x] y z improved by y = [b1] for some b1
A similar reasoning yields
C [x] y z improved by z = [b2] for some b2
So, overall we get
C [x] y z improved by y= [b1] and z = [b2]
Unfortunately, we couldn't establish that b1 and b2 are equal. Hence, we can *not* apply the instance.
2) Alternative design:
We could now argue that the improvement implied by the FD is only applicable if we are in the "right" context.
That is, C [x] y z doesn't yield any improvement because the context y is still underspecified (doesn't match the instance).
In case of C [x] [y] z we get z = [y] (and C [x] z [y] yields z = [y])
3) Multi-range FDs
Consider
class C a b c | a -> b c
instance C a b b => C [a] [b] [b]
This time it's straightforward.
C [x] y z yields the improvement y = [b] and z = [b] which then allows us to apply the instance.
4) Summary.
With multi-range FDs we can derive "more" improvement.
C [x] y z yields y = [b] and z = [b]
Based on the FD-CHR formulation, for the single-range FD case we get
C [x] y z yields y = [b1] and z = [b2]
which is clearly weaker.
The alternative design is even weaker, from C [x] y z we can derive any improvement.
So, I conclude that in the Haskell type improvement context there's clearly a difference among single-range and multi-range FDs.
Of course, we could define multi-range FDs in terms of single-range FDs which then trivially solves the "equivalence" problem (but some user may be disappointed that their multi-range FDs yield weaker improvement).
Thanks for your pointers below but I believe that FDs in the Haskell context can be quite different from FDs in the database context.
- Martin
While you're looking for unusual examples of fundeps, you
might also want to consider things like:
class C a b c | a -> b, b -> c
Note that this is subtly different from a -> b c because
{a -> b, b -> c} |= {a -> b c}
while the reverse does not hold. Instead of type classes, I'll give you some more down-to-earth examples of relations that satisfy these dependencies:
{Paper, Conference, Year} {Professor, University, Country} {Person, FavoriteFood, FoodGroup} ...
For further insight, you might want to take a look at the theory of relational databases to see how functional dependencies are used there. In that context, some sets of dependencies (such as {a -> b, b -> c}) can be interpreted as indicators of bad design. This, in turn, might give you some ideas about the kinds of dependencies you can expect to encounter in well-designed Haskell code. (Of course, you might still find examples in other Haskell code of dependencies that would make a database person wince :-)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Lennart Augustsson wrote:
To reuse a favorite word, I think that any implementation that distinguishes 'a -> b, a -> c' from 'a -> b c' is broken. :) It does not implement FD, but something else. Maybe this something else is useful, but if one of the forms is strictly more powerful than the other then I don't see why you would ever want the less powerful one.
Do you have any good examples, besides the contrived one class D a b c | a -> b c instance D a b b => D [a] [b] [b] where we want to have the more powerful form of multi-range FDs? Fixing the problem who mention is easy. After all, we know how to derive improvement for multi-range FDs. But it seems harder to find agreement whether multi-range FDs are short-hands for single-range FDs, or certain single-range FDs, eg a -> b and a -> c, are shorthands for more powerful multi-range FDs a -> b c. I clearly prefer the latter, ie have a more powerful form of FDs. Martin

I've never thought of one being shorthand for the other, really.
Since they are logically equivalent (in my interpretation) I don't really
care which one we regard as more primitive.
On Fri, Apr 18, 2008 at 9:26 AM, Martin Sulzmann
Lennart Augustsson wrote:
To reuse a favorite word, I think that any implementation that distinguishes 'a -> b, a -> c' from 'a -> b c' is broken. :) It does not implement FD, but something else. Maybe this something else is useful, but if one of the forms is strictly more powerful than the other then I don't see why you would ever want the less powerful one.
Do you have any good examples, besides the contrived one
class D a b c | a -> b c
instance D a b b => D [a] [b] [b]
where we want to have the more powerful form of multi-range FDs?
Fixing the problem who mention is easy. After all, we know how to derive improvement for multi-range FDs. But it seems harder to find agreement whether multi-range FDs are short-hands for single-range FDs, or certain single-range FDs, eg a -> b and a -> c, are shorthands for more powerful multi-range FDs a -> b c. I clearly prefer the latter, ie have a more powerful form of FDs.
Martin

BTW, here's a non-contrived example. It's pretty easy to come up with
examples when you try to use type classes instead of a proper module system.
Here we have expressions parametrized over how identifiers and literals are
represented. First a simple instance, and then one where all the types are
parametrized over the string representation. These are the plug-and-play
type of things I'd like to be able to do.
class IsExpr expr id lit | expr -> id lit where
eId :: id -> expr
eLit :: lit -> expr
eApply :: expr -> expr -> expr
data SimpleExpr = SId Char | SLit Int | SApply SimpleExpr SimpleExpr
instance IsExpr SimpleExpr Char Int where
eId = SId
eLit = SLit
eApply = SApply
data FancyExpr str = FId (Id str) | FLit (Lit str) | FApply (FancyExpr str)
(FancyExpr str)
data Id str = Id str
data Lit str = LString str | LInt Int
instance IsExpr (FancyExpr str) (Id str) (Lit str) where
eId = FId
eLit = FLit
eApply = FApply
On Fri, Apr 18, 2008 at 9:26 AM, Martin Sulzmann
Lennart Augustsson wrote:
To reuse a favorite word, I think that any implementation that distinguishes 'a -> b, a -> c' from 'a -> b c' is broken. :) It does not implement FD, but something else. Maybe this something else is useful, but if one of the forms is strictly more powerful than the other then I don't see why you would ever want the less powerful one.
Do you have any good examples, besides the contrived one
class D a b c | a -> b c
instance D a b b => D [a] [b] [b]
where we want to have the more powerful form of multi-range FDs?
Fixing the problem who mention is easy. After all, we know how to derive improvement for multi-range FDs. But it seems harder to find agreement whether multi-range FDs are short-hands for single-range FDs, or certain single-range FDs, eg a -> b and a -> c, are shorthands for more powerful multi-range FDs a -> b c. I clearly prefer the latter, ie have a more powerful form of FDs.
Martin

On Wed, Apr 16, 2008 at 04:30:27PM +0200, Tom Schrijvers wrote:
I'm looking for practical examples of non-full functional dependencies and would be grateful if anyone could show me some or point to applications using them.
A non-full functional dependency is one involves only part of the parameters of a type class. E.g.
class C a b c | a -> b
has a non-full functional dependency a -> b which does not involve c.
hackageDB has a substantial sample of code these days, which is handy for questions like this. There are examples of non-full FDs in the following packages: ArrayRef-0.1.2 arrows-0.4 OpenAFP-1.0 parsec-3.0.0 StrategyLib-4.0.0.0 Yampa-0.9.2.1 However for most of these there are indirect dependencies. The only exceptions I can find are those in ArrayRef, parsec and StrategyLib. On Wed, Apr 16, 2008 at 05:06:07PM +0200, Martin Sulzmann wrote:
We're also looking for (practical) examples of "multi-range" functional dependencies
class C a b c | c -> a b
Look in BerkeleyDB-0.3 CC-delcont-0.2 collections-0.3 HsJudy-0.2 yi-0.3 yi-gtk-0.2 yi-vty-0.2

hackageDB has a substantial sample of code these days, which is handy for questions like this.
Thanks, Ross. These examples are perfect! Cheers, Tom -- Tom Schrijvers Department of Computer Science K.U. Leuven Celestijnenlaan 200A B-3001 Heverlee Belgium tel: +32 16 327544 e-mail: tom.schrijvers@cs.kuleuven.be url: http://www.cs.kuleuven.be/~toms/
participants (13)
-
Bulat Ziganshin
-
Claus Reinke
-
Dan Weston
-
Hans Aberg
-
Iavor Diatchki
-
Lennart Augustsson
-
Mark P Jones
-
Martin Sulzmann
-
Ross Paterson
-
Ryan Ingram
-
Sittampalam, Ganesh
-
Tom Schrijvers
-
Tom Schrijvers