[Haskell-cafe] Overlapping Instances with Functional Dependencies

2005-07-07 Thread Daniel Brown

I have the following three programs:

  class Foo a b
  instance Foo (a -> b) (a -> [b])
  instance Foo a a

  class Bar a b | a -> b
  instance Bar (a -> b) (a -> b)
  instance Bar a a

  class Baz a b | a -> b
  instance Baz (a -> b) (a -> [b])
  instance Baz a a

When compiled in ghc 6.4 (with -fglasgow-exts
-fallow-overlapping-instances -fallow-undecidable-instances) Foo
and Bar compile fine, but Baz fails with this error:

  Baz.hs:2:0:
  Functional dependencies conflict between instance declarations:
Baz.hs:2:0: instance Baz (a -> b) (a -> [b])
Baz.hs:3:0: instance Baz a a

This is how I interpret the error: The fundep says "a uniquely 
determines b", but if you have `Baz (Int -> Int) b`, b is `Int -> [Int]` 
according to the first instance and `Int -> Int` according to the second 
instance. b isn't uniquely determined by a, so the functional dependency 
isn't functional -- thus the conflict.


When confronted with overlapping instances, the compiler chooses the 
most specific one (if it is unique), e.g. `Baz (a -> b) (a -> [b])` is 
more specific than `Baz a a`.


But it seems that the combination of the two features is broken: if the 
most specific instance is chosen before checking the functional 
dependency, then the fundep is satisfied; if the fundep is checked 
before choosing the most specific instance, then it isn't.


Is this a bug, or am I confused?

 Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Overlapping Instances with Functional Dependencies

2005-07-07 Thread Martin Sulzmann
Hi,

I wouldn't call this a bug, overlapping instances 
and in particular the combination with functional dependencies
are something which is not well studied yet.
Hence, GHC is very conservative here.

I feel like you, this program should work.
As you correctly point out, there's a conflict among the
two improvement rules (resulting from the instances and FD).
A sensible decision is to apply the same "ad-hoc"
mechanism to improvement rules that is currently
applied to overlapping instances. Of course, we need some
formal system to express such conditions precisely.
You find some hints how to achieve this in

G. J. Duck, S. Peyton-Jones, P. J. Stuckey, and M. Sulzmann. 
Sound and decidable type inference for functional dependencies. 
In Proc. of ESOP'04

Martin


Daniel Brown writes:
 > I have the following three programs:
 > 
 >class Foo a b
 >instance Foo (a -> b) (a -> [b])
 >instance Foo a a
 > 
 >class Bar a b | a -> b
 >instance Bar (a -> b) (a -> b)
 >instance Bar a a
 > 
 >class Baz a b | a -> b
 >instance Baz (a -> b) (a -> [b])
 >instance Baz a a
 > 
 > When compiled in ghc 6.4 (with -fglasgow-exts
 > -fallow-overlapping-instances -fallow-undecidable-instances) Foo
 > and Bar compile fine, but Baz fails with this error:
 > 
 >Baz.hs:2:0:
 >Functional dependencies conflict between instance declarations:
 >  Baz.hs:2:0: instance Baz (a -> b) (a -> [b])
 >  Baz.hs:3:0: instance Baz a a
 > 
 > This is how I interpret the error: The fundep says "a uniquely 
 > determines b", but if you have `Baz (Int -> Int) b`, b is `Int -> [Int]` 
 > according to the first instance and `Int -> Int` according to the second 
 > instance. b isn't uniquely determined by a, so the functional dependency 
 > isn't functional -- thus the conflict.
 > 
 > When confronted with overlapping instances, the compiler chooses the 
 > most specific one (if it is unique), e.g. `Baz (a -> b) (a -> [b])` is 
 > more specific than `Baz a a`.
 > 
 > But it seems that the combination of the two features is broken: if the 
 > most specific instance is chosen before checking the functional 
 > dependency, then the fundep is satisfied; if the fundep is checked 
 > before choosing the most specific instance, then it isn't.
 > 
 > Is this a bug, or am I confused?
 > 
 >   Dan
 > ___
 > 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


RE: [Haskell-cafe] Overlapping Instances with Functional Dependencies

2005-07-08 Thread Simon Peyton-Jones
Martin's dead right.  GHC uses a less sophisticated mechanism to do
matching when it's thinking about functional dependencies than when it's
doing straight instance matching.  Maybe something cleverer for fundeps
would make sense, as you point out.  I hadn't thought of that before;
it's a good point.

Nowadays, whenever a fundep question comes up I think "how would it show
up if we had associated type synonyms instead of fundeps?" (see the
paper on my home page).  In this case I think the answer is "GHC's
current instance-matching mechanism would work unchanged"; or to put it
another way, what ever mechanism is used for instance matching, the same
would be used for type dependencies.

Simon
  
| I wouldn't call this a bug, overlapping instances
| and in particular the combination with functional dependencies
| are something which is not well studied yet.
| Hence, GHC is very conservative here.
| 
| I feel like you, this program should work.
| As you correctly point out, there's a conflict among the
| two improvement rules (resulting from the instances and FD).
| A sensible decision is to apply the same "ad-hoc"
| mechanism to improvement rules that is currently
| applied to overlapping instances. Of course, we need some
| formal system to express such conditions precisely.
| You find some hints how to achieve this in
| 
| G. J. Duck, S. Peyton-Jones, P. J. Stuckey, and M. Sulzmann.
| Sound and decidable type inference for functional dependencies.
| In Proc. of ESOP'04
| 
| Martin
| 
| 
| Daniel Brown writes:
|  > I have the following three programs:
|  >
|  >class Foo a b
|  >instance Foo (a -> b) (a -> [b])
|  >instance Foo a a
|  >
|  >class Bar a b | a -> b
|  >instance Bar (a -> b) (a -> b)
|  >instance Bar a a
|  >
|  >class Baz a b | a -> b
|  >instance Baz (a -> b) (a -> [b])
|  >instance Baz a a
|  >
|  > When compiled in ghc 6.4 (with -fglasgow-exts
|  > -fallow-overlapping-instances -fallow-undecidable-instances) Foo
|  > and Bar compile fine, but Baz fails with this error:
|  >
|  >Baz.hs:2:0:
|  >Functional dependencies conflict between instance
declarations:
|  >  Baz.hs:2:0: instance Baz (a -> b) (a -> [b])
|  >  Baz.hs:3:0: instance Baz a a
|  >
|  > This is how I interpret the error: The fundep says "a uniquely
|  > determines b", but if you have `Baz (Int -> Int) b`, b is `Int ->
[Int]`
|  > according to the first instance and `Int -> Int` according to the
second
|  > instance. b isn't uniquely determined by a, so the functional
dependency
|  > isn't functional -- thus the conflict.
|  >
|  > When confronted with overlapping instances, the compiler chooses
the
|  > most specific one (if it is unique), e.g. `Baz (a -> b) (a -> [b])`
is
|  > more specific than `Baz a a`.
|  >
|  > But it seems that the combination of the two features is broken: if
the
|  > most specific instance is chosen before checking the functional
|  > dependency, then the fundep is satisfied; if the fundep is checked
|  > before choosing the most specific instance, then it isn't.
|  >
|  > Is this a bug, or am I confused?
|  >
|  >   Dan
|  > ___
|  > 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Overlapping Instances with Functional Dependencies

2005-07-08 Thread Martin Sulzmann

Simon's dead right, too :) The issue raised here is of general nature and
doesn't depend on the particular (syntactic) formalism used to specify
type dependencies (let it be FDs, ATs,...). The consequence is that
instances and type dependencies are closer linked to each other
then one might think (in case of instance/improvement overlap at least).

Martin


Simon Peyton-Jones writes:
 > Martin's dead right.  GHC uses a less sophisticated mechanism to do
 > matching when it's thinking about functional dependencies than when it's
 > doing straight instance matching.  Maybe something cleverer for fundeps
 > would make sense, as you point out.  I hadn't thought of that before;
 > it's a good point.
 > 
 > Nowadays, whenever a fundep question comes up I think "how would it show
 > up if we had associated type synonyms instead of fundeps?" (see the
 > paper on my home page).  In this case I think the answer is "GHC's
 > current instance-matching mechanism would work unchanged"; or to put it
 > another way, what ever mechanism is used for instance matching, the same
 > would be used for type dependencies.
 > 
 > Simon
 >   
 > | I wouldn't call this a bug, overlapping instances
 > | and in particular the combination with functional dependencies
 > | are something which is not well studied yet.
 > | Hence, GHC is very conservative here.
 > | 
 > | I feel like you, this program should work.
 > | As you correctly point out, there's a conflict among the
 > | two improvement rules (resulting from the instances and FD).
 > | A sensible decision is to apply the same "ad-hoc"
 > | mechanism to improvement rules that is currently
 > | applied to overlapping instances. Of course, we need some
 > | formal system to express such conditions precisely.
 > | You find some hints how to achieve this in
 > | 
 > | G. J. Duck, S. Peyton-Jones, P. J. Stuckey, and M. Sulzmann.
 > | Sound and decidable type inference for functional dependencies.
 > | In Proc. of ESOP'04
 > | 
 > | Martin
 > | 
 > | 
 > | Daniel Brown writes:
 > |  > I have the following three programs:
 > |  >
 > |  >class Foo a b
 > |  >instance Foo (a -> b) (a -> [b])
 > |  >instance Foo a a
 > |  >
 > |  >class Bar a b | a -> b
 > |  >instance Bar (a -> b) (a -> b)
 > |  >instance Bar a a
 > |  >
 > |  >class Baz a b | a -> b
 > |  >instance Baz (a -> b) (a -> [b])
 > |  >instance Baz a a
 > |  >
 > |  > When compiled in ghc 6.4 (with -fglasgow-exts
 > |  > -fallow-overlapping-instances -fallow-undecidable-instances) Foo
 > |  > and Bar compile fine, but Baz fails with this error:
 > |  >
 > |  >Baz.hs:2:0:
 > |  >Functional dependencies conflict between instance
 > declarations:
 > |  >  Baz.hs:2:0: instance Baz (a -> b) (a -> [b])
 > |  >  Baz.hs:3:0: instance Baz a a
 > |  >
 > |  > This is how I interpret the error: The fundep says "a uniquely
 > |  > determines b", but if you have `Baz (Int -> Int) b`, b is `Int ->
 > [Int]`
 > |  > according to the first instance and `Int -> Int` according to the
 > second
 > |  > instance. b isn't uniquely determined by a, so the functional
 > dependency
 > |  > isn't functional -- thus the conflict.
 > |  >
 > |  > When confronted with overlapping instances, the compiler chooses
 > the
 > |  > most specific one (if it is unique), e.g. `Baz (a -> b) (a -> [b])`
 > is
 > |  > more specific than `Baz a a`.
 > |  >
 > |  > But it seems that the combination of the two features is broken: if
 > the
 > |  > most specific instance is chosen before checking the functional
 > |  > dependency, then the fundep is satisfied; if the fundep is checked
 > |  > before choosing the most specific instance, then it isn't.
 > |  >
 > |  > Is this a bug, or am I confused?
 > |  >
 > |  >   Dan
 > |  > ___
 > |  > 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Overlapping Instances with Functional Dependencies

2005-07-11 Thread oleg

Daniel Brown wrote:

>class Baz a b | a -> b
>instance Baz (a -> b) (a -> [b])
>instance Baz a a
> ...but Baz fails with this error...
>
> When confronted with overlapping instances, the compiler chooses the
> most specific one (if it is unique), e.g. `Baz (a -> b) (a -> [b])` is
> more specific than `Baz a a`.
>
> But it seems that the combination of the two features is broken: if the
> most specific instance is chosen before checking the functional
> dependency, then the fundep is satisfied; if the fundep is checked
> before choosing the most specific instance, then it isn't.

There is a way to write your example in Haskell as it is. The key idea
is that functional dependencies can be given *per instance* rather than
per class. To assert such dependencies, you need the `TypeCast'
constraint, which is throughly discussed in the HList technical
report. 
http://homepages.cwi.nl/~ralf/HList/

The following is the complete code for the example, which runs on GHC
6.4. We see that the functional dependencies work indeed: the compiler
figures out the types of test1 and test2 and test3 (and thus resolved
overloading) without any type signatures or other intervention on our
part.


{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}
{-# OPTIONS -fallow-overlapping-instances #-}

module Foo where


{-
class Baz a b | a -> b
instance Baz (a -> b) (a -> [b])
instance Baz a a
-}

-- No functional dependencies here!
class Baz a b where baz :: a -> b

-- Rather, dependencies are here
instance TypeCast a r => Baz a r where
baz a = typeCast a

instance TypeCast (a -> [b]) r => Baz (a -> b) r where
baz f = let r = \a -> [f a] in typeCast r

-- Chooses the instance Baz a a
test1 = baz True
-- True

-- Chooses the instance Baz (a -> b) (a -> [b])
test2 = (baz show) (1::Int)
-- ["1"]

test3 x = (baz show) x
test3' = test3 (Just True)
-- ["Just True"]

-- copied verbatim from the HList library
class TypeCast   a b   | a -> b, b->a   where typeCast   :: a -> b
class TypeCast'  t a b | t a -> b, t b -> a where typeCast'  :: t->a->b
class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b
instance TypeCast'  () a b => TypeCast a b where typeCast x = typeCast' () x
instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast''
instance TypeCast'' () a a where typeCast'' _ x  = x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Overlapping Instances with Functional Dependencies

2005-07-11 Thread Martin Sulzmann

This is still an ad-hoc solution, cause you lose
the `most-specific' instance property. You really have to
impose a `fixed' ordering in which instance-improvement rules
fire.

Recap: 

The combination of overlapping instances
and type improvement leads to a `non-confluent' system, i.e.
there're too many (inconsistent) choices how to improve and reduce
constraints.

The standard approach to deal with overlapping instances is to
impose a fixed order among the resulting reduction rules
(the `most-specific' order can be seen as a special instance
of a fixed order).

FDs imply improvement rules. In case of overlapping instances these
improvement rules are immediately non-confluent.
As Simon pointed out:
"...what ever mechanism is used for instance matching, the same
would be used for type dependencies..."
Hence, combining instances and improvement rules is the obvious
`solution'. Hints can be found in my first two replies where I said:
1) "... You find some hints how to achieve this in ... ESOP'04".
2) "...instances and type dependencies are closer linked to each other
  then one might think..."
Concretely, the TypeCast trick already appears in the ESOP'04 paper
on p8 (mid-page). 

Conclusion:

I think it's wrong to explain a new feature in terms of an
implementation-specific encoding. We need something more principled
here. Otherwise, we'll face some unexpected behavior (eventually)
again.


Martin



[EMAIL PROTECTED] writes:
 > 
 > Daniel Brown wrote:
 > 
 > >class Baz a b | a -> b
 > >instance Baz (a -> b) (a -> [b])
 > >instance Baz a a
 > > ...but Baz fails with this error...
 > >
 > > When confronted with overlapping instances, the compiler chooses the
 > > most specific one (if it is unique), e.g. `Baz (a -> b) (a -> [b])` is
 > > more specific than `Baz a a`.
 > >
 > > But it seems that the combination of the two features is broken: if the
 > > most specific instance is chosen before checking the functional
 > > dependency, then the fundep is satisfied; if the fundep is checked
 > > before choosing the most specific instance, then it isn't.
 > 
 > There is a way to write your example in Haskell as it is. The key idea
 > is that functional dependencies can be given *per instance* rather than
 > per class. To assert such dependencies, you need the `TypeCast'
 > constraint, which is throughly discussed in the HList technical
 > report. 
 >  http://homepages.cwi.nl/~ralf/HList/
 > 
 > The following is the complete code for the example, which runs on GHC
 > 6.4. We see that the functional dependencies work indeed: the compiler
 > figures out the types of test1 and test2 and test3 (and thus resolved
 > overloading) without any type signatures or other intervention on our
 > part.
 > 
 > 
 > {-# OPTIONS -fglasgow-exts #-}
 > {-# OPTIONS -fallow-undecidable-instances #-}
 > {-# OPTIONS -fallow-overlapping-instances #-}
 > 
 > module Foo where
 > 
 > 
 > {-
 > class Baz a b | a -> b
 > instance Baz (a -> b) (a -> [b])
 > instance Baz a a
 > -}
 > 
 > -- No functional dependencies here!
 > class Baz a b where baz :: a -> b
 > 
 > -- Rather, dependencies are here
 > instance TypeCast a r => Baz a r where
 > baz a = typeCast a
 > 
 > instance TypeCast (a -> [b]) r => Baz (a -> b) r where
 > baz f = let r = \a -> [f a] in typeCast r
 > 
 > -- Chooses the instance Baz a a
 > test1 = baz True
 > -- True
 > 
 > -- Chooses the instance Baz (a -> b) (a -> [b])
 > test2 = (baz show) (1::Int)
 > -- ["1"]
 > 
 > test3 x = (baz show) x
 > test3' = test3 (Just True)
 > -- ["Just True"]
 > 
 > -- copied verbatim from the HList library
 > class TypeCast   a b   | a -> b, b->a   where typeCast   :: a -> b
 > class TypeCast'  t a b | t a -> b, t b -> a where typeCast'  :: t->a->b
 > class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b
 > instance TypeCast'  () a b => TypeCast a b where typeCast x = typeCast' () x
 > instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast''
 > instance TypeCast'' () a a where typeCast'' _ x  = x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe