Re: [Haskell] functional dependencies not satisfactory?

2007-09-04 Thread Manuel M T Chakravarty
lieve that we should use the type families mentioned by Stefan instead of functional dependencies. Type checker support for type synonym families (the flavour needed for your example) has been merged into GHC's development version a week ago. For more details, see http://h

Re: [Haskell] functional dependencies not satisfactory?

2007-09-04 Thread Stefan O'Rear
On Tue, Sep 04, 2007 at 11:11:00PM +0200, Wolfgang Jeltsch wrote: > Am Dienstag, 4. September 2007 22:00 schrieben Sie: > > […] > > > It should be emphasized that this program worked the very first time I > > typed it in. > > Which version of GHC are you using? I’m a bit confused since the lates

Re: [Haskell] functional dependencies not satisfactory?

2007-09-04 Thread Wolfgang Jeltsch
Am Dienstag, 4. September 2007 22:00 schrieben Sie: > […] > It should be emphasized that this program worked the very first time I > typed it in. Which version of GHC are you using? I’m a bit confused since the latest successful nightly build for i386-unknown-linux seems to be from August 20.

Re: [Haskell] functional dependencies not satisfactory?

2007-09-04 Thread Stefan O'Rear
endancies are Bad(tm) - the semantics generated by their typing derivations do not correspond to the naïve model. In particular, functional dependencies serve *only* to avoid ambiguity; they cannot be used to satisfy equality constraints. Type synonym families, the proposed alternative to functional

[Haskell] functional dependencies not satisfactory?

2007-09-04 Thread Wolfgang Jeltsch
Hello, I came across the following problem: I define a class with a functional dependency like so: class C a b | a -> b Then I want to define a datatype using the fact that the second argument of C is dependent on the first: data C a b => T a = MkT a b But unfortunately, this doesn’t

[Haskell] Re: Functional dependencies and type inference (2)

2005-12-06 Thread Stefan Monnier
>> > instance CpsForm t t where >> This can't be right, can it? > In general no: the CPS of a function certainly doesn't fit the above > pattern. So, if the source language has abstractions (the language in > the original message didn't), we have to add another instance for > CpsForm. But any othe

[Haskell] Re: Functional dependencies and type inference (2)

2005-12-04 Thread oleg
Stefan Monnier wrote: > > instance CpsForm t t where > > This can't be right, can it? In general no: the CPS of a function certainly doesn't fit the above pattern. So, if the source language has abstractions (the language in the original message didn't), we have to add another instance for CpsFor

[Haskell] Re: Functional dependencies and type inference (2)

2005-12-03 Thread Stefan Monnier
> instance CpsForm t t where This can't be right, can it? After CPS conversion a term of type "a -> b" won't have type "a -> b" but rather something like "a * (b -> c) -> c". Stefan ___ Haskell mailing list Haskell@haskell.org http://www.haske

[Haskell] Re: Functional dependencies and type inference (2)

2005-11-30 Thread oleg
Louis-Julien Guillemette wrote: > Say we are using a GADT to represent a simple language of boolean > constants and conditionals, > > data Term a where >B:: Bool -> Term Bool >Cnd :: Term Bool -> Term t -> Term t -> Term t > > and we would like to perform a type-safe CPS conversion ov

Re: [Haskell] Functional dependencies and type inference (2)

2005-11-30 Thread kahl
Louis-Julien Guillemette <[EMAIL PROTECTED]> wrote: > Say we are using a GADT to represent a simple language of boolean > constants and conditionals, > > data Term a where >B:: Bool -> Term Bool >Cnd :: Term Bool -> Term t -> Term t -> Term t > > and we would like to perfo

[Haskell] Functional dependencies and type inference (2)

2005-11-30 Thread Louis-Julien Guillemette
Say we are using a GADT to represent a simple language of boolean constants and conditionals, data Term a where B:: Bool -> Term Bool Cnd :: Term Bool -> Term t -> Term t -> Term t and we would like to perform a type-safe CPS conversion over this language. We encode the relationship

Re: [Haskell] generic currying (type classes and functional dependencies)

2004-05-13 Thread Ronny Wichers Schreur
Duncan Coutts writes (to the Haskell Mailing list): I'm trying to write a generic curry (& uncurry) function that works for functions of any arity. See where oleg presents a (ghc-specific) solution. Cheers, Ronny Wichers Schreur __

Re: [Haskell] generic currying (type classes and functional dependencies)

2004-05-11 Thread Esa Pulkkinen
In message <[EMAIL PROTECTED]>, Duncan Coutts writes: >I'm trying to write a generic curry (& uncurry) function that works for >functions of any arity. I have a couple solutions that nearly work, both >involving type classes. [SNIP] >Any insight or suggestions would be interesting. Here's one sol

Re: [Haskell] generic currying (type classes and functional dependencies)

2004-05-11 Thread Malcolm Wallace
Duncan Coutts <[EMAIL PROTECTED]> writes: > So I thought that functional dependencies might help because the curried > type should uniquely determine the uncurried type (and vice versa). > However if I change the class declaration to: > > class Curry tupled curried | tuple

[Haskell] generic currying (type classes and functional dependencies)

2004-05-11 Thread Duncan Coutts
t fails to be able to convince itself that a & b are Int, in which case there would be an instance. This can be solved by supplying enough type annotations, however this is annoying and part of the point of a generic curry is that we don't know the arity of the function to which we are apply

[Haskell] Re: Functional dependencies interfere with generalization

2004-01-28 Thread oleg
I'm sorry to open an old wound. I've just had an insight for a clarification. On Nov 26, 2003 Ken Shan wrote: > Consider the following code, which uses type classes with functional > dependencies: > > {-# OPTIONS -fglasgow-exts #-} > module Foo where >

Re: Functional dependencies interfere with generalization

2003-11-27 Thread Ken Shan
nferred but unquantified type P=>t, we would normally just calculate the set of type variables T = TV(P=>t), over which we might want to quantify, and the set of variables V = TV(A) that are fixed in the current assumptions A, and then quantify over any variables in t

Re: Functional dependencies interfere with generalization

2003-11-27 Thread Brandon Michael Moore
On Wed, 26 Nov 2003, Ken Shan wrote: > Hello, > > Consider the following code, which uses type classes with functional > dependencies: > > {-# OPTIONS -fglasgow-exts #-} > module Foo where > class R a b | a -> b where r :: a -> b > > -- 1 >

Functional dependencies interfere with generalization

2003-11-26 Thread Ken Shan
Hello, Consider the following code, which uses type classes with functional dependencies: {-# OPTIONS -fglasgow-exts #-} module Foo where class R a b | a -> b where r :: a -> b -- 1 rr :: (R a b1, R a b2) => a -> (b1, b2) rr a = (r a, r a) -- 2 data

RE: overlapping instances and functional dependencies

2003-08-21 Thread Simon Peyton-Jones
ink anyone has really worked through the interaction of overlapping instances (already swampy) with functional dependencies. What you say makes sense, but it's not what GHC or Hugs implement. Maybe they should Simon ___ Haskell mailing list [EM

RE: overlapping instances and functional dependencies

2003-08-21 Thread Simon Peyton-Jones
| class C a b c | a b -> c where | f :: a -> b -> c | | instance C a b c => C a (x,y,b) c where | f a (_,_,b) = f a b | | instance C a (a,c,b) c where | f _ (_,c,_) = c | ghci -fglasgow-exts -fallow-overlapping-instances compiles it without | complaint but hug

Re: overlapping instances and functional dependencies

2003-08-21 Thread Tom Pledger
C T McBride writes: : | but I'm not allowed | | class Bad x y z | x y -> z | | instance Functor f => Bad (f x) (f y) Bool | | instance Functor f => Bad x (f y) Int | | I don't quite see why. Naively, I imagine that if the OK instances are | effectively prioritized, then Bad's r

Re: overlapping instances and functional dependencies

2003-08-21 Thread C T McBride
Hi all With overlapping instances, I'm allowed class OK x y instance Functor f => OK (f x) (f y) instance Functor f => OK x (f y) but I'm not allowed class Bad x y z | x y -> z instance Functor f => Bad (f x) (f y) Bool instance Functor f => Bad x (f y) Int I don't quite see wh

Re: overlapping instances and functional dependencies

2003-08-20 Thread oleg
Wolfgang Jeltsch has observed: > I have this code: > class C a b c | a b -> c where > f :: a -> b -> c > > instance C a b c => C a (x,y,b) c where > f a (_,_,b) = f a b > > instance C a (a,c,b) c where > f _ (_,c,_) = c > ghci -fglasgow-exts -fallow-overlapping-

Re: overlapping instances and functional dependencies

2003-08-19 Thread Wolfgang Jeltsch
Hello, I think, I realized now what my mistake was. The handling of overlapping instances comes into play when the compiler has to decide which method definition to choose for a specific instance. It is not for choosing one of more possible instances. In my example, C Int (Int,Char,Bool) Int a

Re: overlapping instances and functional dependencies

2003-08-17 Thread Wolfgang Jeltsch
I wrote on Saturday, 2003-08-09, 01:32, CEST: > Hello, > > I have this code: > class C a b c | a b -> c where > f :: a -> b -> c > > instance C a b c => C a (x,y,b) c where > f a (_,_,b) = f a b > > instance C a (a,c,b) c where > f _ (_,c,_) = c > ghci -fglasgow-

RE: overlapping instances and functional dependencies

2003-08-14 Thread Hal Daume
Behalf Of Wolfgang Jeltsch > Sent: Friday, August 08, 2003 4:33 PM > To: The Haskell Mailing List > Subject: overlapping instances and functional dependencies > > > Hello, > > I have this code: > class C a b c | a b -> c where > f :: a -> b -> c &g

Re: overlapping instances and functional dependencies

2003-08-14 Thread Andrew J Bromage
G'day all. On Sat, Aug 09, 2003 at 01:32:49AM +0200, Wolfgang Jeltsch wrote: > ghci -fglasgow-exts -fallow-overlapping-instances compiles it without > complaint If it helps, ghci will complain the first time you actually try to use it. Cheers, Andrew Bromage ___

overlapping instances and functional dependencies

2003-08-10 Thread Wolfgang Jeltsch
Hello, I have this code: class C a b c | a b -> c where f :: a -> b -> c instance C a b c => C a (x,y,b) c where f a (_,_,b) = f a b instance C a (a,c,b) c where f _ (_,c,_) = c ghci -fglasgow-exts -fallow-overlapping-instances compiles it without complaint b

Re: Multiparameter class confusion (and functional dependencies)

2003-06-09 Thread Graham Klyne
lso spotted something in the implementation of Control.Monad.State, in which: [[ class (Monad m) => MonadState s m | m -> s where get :: m s put :: s -> m () ]] has 's' being declared as determined by m, without explicitly saying how. I haven't yet really learned about f

RE: Functional dependencies and Constructor Classes

2002-11-20 Thread Martin Sulzmann
Mark P Jones writes: > | The issue I want to raise is whether constructor classes are > | redundant in the presence of FDs > > No, they are not comparable. > Allow me to make the following bold claim. Assume we are given a program that uses the Haskell functor class as in class Functor f

Re: Functional dependencies and Constructor Classes

2002-11-19 Thread Yoann Padioleau
Martin Sulzmann <[EMAIL PROTECTED]> writes: > Yoann Padioleau writes: > > nevertheless i found constructor class more elegant for many problems. > > Your solution is less elegant that the one using constructor classes. > > > > Yes, the current presentation of constructor classes might be easi

RE: Functional dependencies and improvement

2002-11-18 Thread Mark P Jones
Martin, | In my previous example I employed FD's to | improve constraints. However, there are cases where FD's seem | to be overly restrictive. Yes, of course! So it will be for any extension of the type system that retains both decidability and soundness. The particular form of "improvement"

RE: Functional dependencies and Constructor Classes

2002-11-18 Thread Mark P Jones
Hi Martin, | The issue I want to raise is whether constructor classes are | redundant in the presence of FDs No, they are not comparable. Let fds = functional dependencies ccs = constructor classes Example of something you can do with ccs but not fds: data Fix f = In (f (Fix f

Re: Functional dependencies and Constructor Classes

2002-11-18 Thread Martin Sulzmann
Yoann Padioleau writes: > nevertheless i found constructor class more elegant for many problems. > Your solution is less elegant that the one using constructor classes. > Yes, the current presentation of constructor classes might be easier to comprehend. > I found too that type error message

Re: Functional dependencies and Constructor Classes

2002-11-18 Thread Yoann Padioleau
Martin Sulzmann <[EMAIL PROTECTED]> writes: > Hi, > > I was wondering whether other people made similiar observations. > Functional dependencies seem to be expressiveness enough to encode > some of the kinding rules required for Constructor Classes. read this page: http:/

Functional dependencies and improvement

2002-11-18 Thread Martin Sulzmann
ance Insert Int [Float] -- though this makes sense! Elements of value Int should allowed to be stored as Floats {- Reason: Improvement in case of FDs seems overly restrictive Consider Mark Jones paper "Type Classes with Functional Dependencies", page 12, Section 6.2. In case of the abov

Functional dependencies and Constructor Classes

2002-11-18 Thread Martin Sulzmann
Hi, I was wondering whether other people made similiar observations. Functional dependencies seem to be expressiveness enough to encode some of the kinding rules required for Constructor Classes. Take a look at the Haskell code below (runs under hugs -98 or ghci -fglasgow-exts-fallow

Re: A question concerning functional dependencies

2002-09-02 Thread Ashley Yakeley
At 2002-09-02 07:47, Dylan Thurston wrote: >GHC (and Hugs) check for potential conflicts like this unless you >explicitly allow overlapping instances. AFAIK, even with overlapping instances allowed, GHC will still complain if there's a fundep. See

Re: A question concerning functional dependencies

2002-09-02 Thread Dylan Thurston
On Mon, Sep 02, 2002 at 03:11:58AM -0700, Ashley Yakeley wrote: > At 2002-09-02 02:46, Jerzy Karczmarczuk wrote: > > >class Module v s | v->s . > ... > >instance Num s => Module (v->s) s > ... > >instance ...=> Module ((v->s)->(v->s)) s > ... > >But GHCi yells that two instances in view of the

Re: A question concerning functional dependencies

2002-09-02 Thread Ashley Yakeley
At 2002-09-02 02:46, Jerzy Karczmarczuk wrote: >class Module v s | v->s . ... >instance Num s => Module (v->s) s ... >instance ...=> Module ((v->s)->(v->s)) s ... >But GHCi yells that two instances in view of the functional >dependency declared are in conflict. GHCi is correct. Bear in mind G

A question concerning functional dependencies

2002-09-02 Thread Jerzy Karczmarczuk
I wanted to write a small package implementing vector spaces, etc. A part of it is class Module v s where (*>) :: s->v->v defining the multiplication of a vector by a scalar: w = a*>v Now, as in many other circumstances, concrete vectors are based on concrete scalars, and I defined really:

RE: functional dependencies

2002-07-24 Thread Ashley Yakeley
At 2002-07-23 09:06, Simon Peyton-Jones wrote: >Dead right! Imagine there was a method in class D: > > class C a b => D a where > op :: a -> b > >The type of 'op' is > > op :: D a => a -> b > >You can't really expect that the 'b' here is determined by 'a'! Agreed. If you we

RE: functional dependencies

2002-07-23 Thread Simon Peyton-Jones
I'm just catching up with some old mail here. Iavor writes: | class C a b | a -> b | class C a b => D a | | vs. | | class C a b | a -> b | class C a b => D a b | | Hugs accepts both of those, while GHC insists on the second. | The first example is a little shorter and one might argue that i

functional dependencies

2002-06-29 Thread Johannes Waldmann
Can I write dependencies like this: > class C x y z | x -> (y, z) > class D x y z | (x, y) -> z in hugs? in ghc? The ghc doc refers to Mark Jones: "Type Classes with Functional Dependencies", http://www.cse.ogi.edu/~mpj/pubs/fundeps.html where this seems to be allo

RE: Syntax of functional dependencies

2002-04-26 Thread Simon Marlow
> I errorneously specified categories as > > class (Eq object, Eq morphism) => > Category id object morphism | id ->, id -> morphism > where o :: id -> morphism -> morphism -> Maybe morphism > dom, cod :: id -> morphism -> object > > it should have been > > class (Eq object,

Syntax of functional dependencies

2002-04-25 Thread Till Mossakowski
I errorneously specified categories as class (Eq object, Eq morphism) => Category id object morphism | id ->, id -> morphism where o :: id -> morphism -> morphism -> Maybe morphism dom, cod :: id -> morphism -> object it should have been class (Eq object, Eq morphism) =>

functional dependencies

2002-02-03 Thread Iavor S. Diatchki
hello, there seems to be a difference between the way superclasses are handled in GHC and Hugs, and it would be nice if one of the choices was selected (i am not sure what other implementations do). here is what i mean: class C a b | a -> b class C a b => D a vs. class C a b | a -> b class C

Re: inference with functional dependencies

2001-08-14 Thread Ken Shan
On 2001-08-13T18:08:08-0400, Avi Pfeffer wrote: > Inferring equality between types when there are functional dependencies > seems to be less powerful than I expected. Here's a simple example: > > class Eq b => C a b | a -> b > > data T a = forall b . C a b => T

inference with functional dependencies

2001-08-13 Thread Avi Pfeffer
Inferring equality between types when there are functional dependencies seems to be less powerful than I expected. Here's a simple example: class Eq b => C a b | a -> b data T a = forall b . C a b => T b data U a = forall b . C a b => U b compare :: T a -> U a -> Bool

Functional Dependencies (Was RE: Dimensional analysis with fundeps)

2001-04-10 Thread Mark P Jones
Dear All, | 1) What is a fundep? Fundeps are "functional dependencies", which have long been used to specify constraints on the tables used in relational databases. In the current context, people are using "fundeps" to refer to the way that this idea has been adapted t

RE: Yet more on functional dependencies

2001-02-02 Thread Simon Peyton-Jones
| | I am finding functional dependencies confusing. (I suspect I am | | not alone.) Should the following code work? | | | | class HasConverter a b | a -> b where | |convert :: a -> b | | | | instance (HasConverter a b,Show b) => Show a where | |show value = show (conv

Re: Yet more on functional dependencies

2001-01-15 Thread Jeffrey R. Lewis
Mark P Jones wrote: > | I am finding functional dependencies confusing. (I suspect I am > | not alone.) Should the following code work? > | > | class HasConverter a b | a -> b where > |convert :: a -> b > | > | instance (HasConverter a b,Show b) => Show a

RE: Yet more on functional dependencies

2001-01-15 Thread Mark P Jones
| I am finding functional dependencies confusing. (I suspect I am | not alone.) Should the following code work? | | class HasConverter a b | a -> b where |convert :: a -> b | | instance (HasConverter a b,Show b) => Show a where |show value = show (convert value) It

Yet more on functional dependencies

2001-01-08 Thread Tom Pledger
George Russell writes: > I am finding functional dependencies confusing. (I suspect I am not alone.) > Should the following code work? > > class HasConverter a b | a -> b where >convert :: a -> b > > instance (HasConverter a b,Show b) => Show a where &

Yet more on functional dependencies

2001-01-08 Thread George Russell
I am finding functional dependencies confusing. (I suspect I am not alone.) Should the following code work? class HasConverter a b | a -> b where convert :: a -> b instance (HasConverter a b,Show b) => Show a where show value = show (conv

Re: Problem with functional dependencies

2001-01-04 Thread Marcin 'Qrczak' Kowalczyk
Thu, 4 Jan 2001 13:01:56 -0800, Mark P Jones <[EMAIL PROTECTED]> pisze: > I hope now that the problem is becoming clear: this instance > declaration is not consistent with the dependency; in the first > two lines above, for example, we see two rows that violate the > specification because they ha

RE: Problem with functional dependencies

2001-01-04 Thread Mark P Jones
Hi Marcin, | In particular, should the following be legal: | | class C a b c | a -> b c | instance C [a] b b | f:: C [a] b c => a | f = undefined | | ghc panics and Hugs rejects it. No, it is not legal. Even if you delete the definition of f, the code is still not legal because the class and

Re: Problem with functional dependencies

2001-01-03 Thread Marcin 'Qrczak' Kowalczyk
I don't fully understand fundeps. Would the following transform legal programs (without overlapping instances) into legal programs? I hope yes. Let's imagine a class with a set of instances and uses, without fundeps. - Add some additional type variables to the class header. - Add a fundep: all o

Re: Problem with functional dependencies

2001-01-03 Thread Fergus Henderson
On 03-Jan-2001, Mark P Jones <[EMAIL PROTECTED]> wrote: > ... the best way to deal with this is (probably): > (i) to infer simpler types whenever possible, but > (ii) to allow more polymorphic types when they are requested by > means of an explicit type signature. I agree. > (Incidental

RE: Problem with functional dependencies

2001-01-03 Thread Mark P Jones
| I think you can simplify the example. Given | | class HasFoo a b | a -> b where | foo :: a -> b | instance HasFoo Int Bool where ... | | Is this legal? | f :: HasFoo Int b => Int -> b | f x = foo x The theoretical foundation for functional depen

Re: Problem with functional dependencies

2000-12-21 Thread Lennart Augustsson
Simon Peyton-Jones wrote: > I think you can simplify the example. Given > > class HasFoo a b | a -> b where > foo :: a -> b > > instance HasFoo Int Bool where ... > > Is this legal? > > f :: HasFoo Int b => Int -> b > f x = foo x > > You might think so,

Re: Problem with functional dependencies

2000-12-21 Thread Marcin 'Qrczak' Kowalczyk
Thu, 21 Dec 2000 00:59:29 -0800, Jeffrey R. Lewis <[EMAIL PROTECTED]> pisze: > > class HasFoo a b | a -> b where > > f :: HasFoo Int b => Int -> b > > f x = foo x > This is the step where the reasoning goes wrong. The functional > dependency tells you that `b' isn't rea

Re: Problem with functional dependencies

2000-12-21 Thread Jeffrey R. Lewis
Simon Peyton-Jones wrote: > I think you can simplify the example. Given > > class HasFoo a b | a -> b where > foo :: a -> b > > instance HasFoo Int Bool where ... > > Is this legal? > > f :: HasFoo Int b => Int -> b > f x = foo x > > You might think so,

RE: Problem with functional dependencies

2000-12-20 Thread Simon Peyton-Jones
re here, but there's more to this functional dependency stuff than meets the eye. Even whether one type is more general than another has changed! Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]] | Sent: 17 December 2000 19:30 | To: [EMAIL PROTECTED] | S

Problem with functional dependencies

2000-12-17 Thread Marcin 'Qrczak' Kowalczyk
The following module is rejected by both ghc -fglasgow-exts -fallow-undecidable-instances and hugs -98 class HasFoo a foo | a -> foo where foo :: a -> foo data A = A Int data B = B A instance HasFoo A Int where

Re: Functional Dependencies

1999-09-14 Thread Ross Paterson
to define first, we need an isomorphism between f(b,c) and (f b,g b) for some functor g. Some examples: f g (,) s Id state transformers Stream Stream synchronous circuits (->) s (->) s a v

RE: Functional Dependencies

1999-09-14 Thread Mark P Jones
Hi Fermin, | Should redundant dependencies trigger an error or a warning? I'd | say that if I'm writing some haskell code, I wouldn't mind if a | redundancy is flagged as an error; most likely, it'd take a short | time to fix. However, if someone is generating haskell automatically | (maybe with

RE: Functional Dependencies

1999-09-13 Thread Fermin Reig Galilea
> > | Also, you say a dependency with zero variables on the right side is > | syntactically correct, but later you say it will be reported as an > | error because it says nothing. Why bother? > > Point taken. In fact that same database text I mentioned above >

RE: Functional Dependencies

1999-09-13 Thread Mark P Jones
er? Point taken. In fact that same database text I mentioned above prohibits functional dependencies in which either side is empty. But it turns out that the two extremes ("a ->" and "-> a") are rather interesting so I didn't want to exclude either as being syntacticall

Re: Functional Dependencies

1999-09-13 Thread Ross Paterson
Mark P Jones wrote: > A couple of months ago, I developed and implemented an extension to > Hugs that has the potential to make multiple parameter type classes > more useful. The key idea is to allow class declarations to be > annoted with `functional dependencies'---an idea th

RE: Functional Dependencies

1999-09-12 Thread Mark P Jones
type. The type of the corresponding collection would be: Array Int (outer (inner a)). This would work just fine with the functional dependencies version, but for the constructor classes version you'd have to introduce yet another newtype and instance: newtype Compose f g x = Comp

Re: Functional Dependencies

1999-09-12 Thread Heribert Schuetz
um x)) > member x c = testBit (unBS c) (fromEnum x) For the hash-table example I am pretty sure that the work-around works as well, even though I could not figure out your intended implementation. Of course this is just a work-around and does not make functional dependencies superfluous. Regards, Heribert.

Functional Dependencies

1999-09-11 Thread Mark P Jones
[Simon mentioned my work on `functional dependencies' in one of his messages a couple of days ago, so I thought I'd better post an explanation!] A couple of months ago, I developed and implemented an extension to Hugs that has the potential to make multiple parameter type classes m