Re: To all those who don't like ad-hoc overloading

1999-10-05 Thread Carlos Camarao de Figueiredo


Levent, 

thanks for your explanation. I liked it. 

There are a few things I would like to comment.

1) My previous message was mistaken. Sorry. Forget it. I will try
again.

So suppose again the simpler map:: (a - b) - [a] - [b]. 

Then (in fact) system CT infers that the only possible definition of
union that can be used in "union . map fst" is the first one: that
with type [a]-[a]-[a].

The second one, with type (a-a-Bool)-[a]-[a]-[a], cannot, since,
in system CT, [b] and (a-a-Bool) do not match (unification fails). 

So, the type of "union . map fst" is simply [(a, b)] - [a] - [a].

(Again, sorry for my mistake in the previous message.)

2) So now let us consider the more general map, that is overloaded for
lists and functions. In System CT, this would be done by giving
definitions (instances, no class declaration required) of map,
including:

 map:: (a-b) - [a] - [b]and
 map:: (a-b) - (c-a) - (c-b)

and "union . map fst" could be used with each of these. 

If it is applied to a list of pairs, the first map will be used
(together with union::[a]-[a]-[a]).

If it is applied to a function, of type a - (a-Bool, b), the second
map will be used (together with union::(a-a-Bool)-[a]-[a]-[a]). 

3) I think that if the type system allows unifications like, say, 

c b  with a-a-Bool

things get (unnecessarily) more complicated. 

Yours,

Carlos










Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Manuel M. T. Chakravarty

Kevin Atkinson [EMAIL PROTECTED] wrote,

 "Manuel M. T. Chakravarty" wrote:
  
  Kevin Atkinson [EMAIL PROTECTED] wrote,
  
   I take it that you are happy with names such as:
  
  [long list of names deleted]
  
   I *hate* languages that try to keep things too simple.  Which is one of
   the reasons I *hate* java.  Please don't make me *hate* Haskell for the
   same reason.
  
  The problem with excessive overloading is that
 
 The key word here is excessive.   If you are confusing your self by
 using the same name for everthing than you need to use seperate function
 names.  So you are saying that haskell should avoid all featurs that can
 be abused. 

Excessive by my definitions if the use of one function name
for `union' and `unionBy'.  What's the harm in using two
function names here?  Where overloading makes sense `union'
uses it already.  If you have to use `unionBy', this is
because the elements of the set are not part of `Eq' or you
want to use something else than standard equality.  In other
words, there is a good reason for using `unionBy' contained
in the algorithm or at least the structure of your program
(otherwise, you have probably already made a mistake in your
class definitions).  As there is such a reason, you should
document it by using `unionBy' instead of `union' -
everything else is, frankly speaking, careless software
engineering.

Haskell encourages good software engineering practice -
that's something I very much like about the language.

  (2) it makes it harder for beginners.
  
  Re (1): Consider the usage of different function names as a
  form of additional documentation.
 
 Yes but many times excessively long function names can make code harder
 to read.

Come on - the two letters difference between `union' and
`unionBy' hardly make a program harder to read.

Manuel






Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Kevin Atkinson

"Manuel M. T. Chakravarty" wrote:
 
 Kevin Atkinson [EMAIL PROTECTED] wrote,
 
  I take it that you are happy with names such as:
 
 [long list of names deleted]
 
  I *hate* languages that try to keep things too simple.  Which is one of
  the reasons I *hate* java.  Please don't make me *hate* Haskell for the
  same reason.
 
 The problem with excessive overloading is that

The key word here is excessive.   If you are confusing your self by
using the same name for everthing than you need to use seperate function
names.  So you are saying that haskell should avoid all featurs that can
be abused. 
 
 (1) it is often cute in small programs, but bites you when
 software gets more complex, and

I have never yet hade this problem with my C++ functions and
overloading.  I only use overloading when it will be clear my the
context what it means.

 (2) it makes it harder for beginners.
 
 Re (1): Consider the usage of different function names as a
 form of additional documentation.

Yes but many times excessively long function names can make code harder
to read.
 
 Re (2): There was some overloading in Haskell 1.4, which was
 taken out in Haskell 98 exactly for this reason (usage of
 list comprehensions for other monads than list and the
 overloading of map and (++)).

That is a shame.

-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Jan de Wit

On Sat, 2 Oct 1999, Matt Harden wrote:

[snip]
   
   I like that, but I wish we had a way to get the "head" and "tail" of
   tuples, just as we do with lists, and combine them.  Maybe a (:,)
   operator that works like this:
   
   a :, (b :, ()) = (a,b)
   a :, () = UniTuple a
   a :, (b,c) = (a,b,c)
   a :, (UniTuple b) = (a,b)
   
   Also allow pattern matching on this operator.
   
[snip]
   
   This seems a little too obvious to me.  Has it been suggested and shot
   down before?
   
   Matt Harden
   
Well, you can define a class Splittable:

class Splittable a b c where
  spl :: a - (b,c)  -- split tuple
  lps :: (b,c) - a  -- reverse split

With fairly obvious instances for Splittable a a (), Splittable (a,b) a b,
Splittable (a,b,c) a (b,c) etc. The only problem with this kind of solution
is that when you type, e.g. spl (3,4,5), hoping to obtain (3,(4,5)), hugs
complains with:
ERROR: Unresolved overloading
*** Type   : (Num a, Num b, Num c, Splittable (c,b,a) d e) = (d,e)
*** Expression : spl (3,4,5)

However, it seems that Mark Jones has an extension to Hugs in the works
where you can specify that the types b and c in the class depend on a,
which would resolve this issue. See http://www.cse.ogi.edu/~mpj/fds.html
for details - I really hope the September release comes quickly !!!

Bye,

Jan de Wit
   








Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Adrian Hey

 On Sun 03 Oct, Manuel M. T. Chakravarty wrote: 
 The problem with excessive overloading is that
 
 (1) it is often cute in small programs, but bites you when
 software gets more complex, and
 (2) it makes it harder for beginners.

I can think of 2 more potential problems with overloading (ad-hoc or otherwise)

(3) It makes it hard to use Haskell as a target language for other
software tools, synthesizers etc unless they adopt essentially the
same type system as Haskell. It would be much easier, I think, if
the 'operational meaning' of a bit of Haskell code is unambiguous
without type checking. By this I mean you could turn type checking
off and still be able to compile the program.

(4) If you have 2 different methods to achieve the same thing (e.g.
2 different algorithms which are the most efficient in different
circumstances, or 2 criteria for comparing values of the same type).
Here you can't use type to select the appropriate method. Instead
you have to make values of the 'same type' look different just so
the correct method can be chosen, which complicates matters a lot.
Giving different names to different functions seems much easier to me.

Regards
-- 
Adrian Hey







Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Kevin Atkinson

On Mon, 4 Oct 1999, Manuel M. T. Chakravarty wrote:

 Kevin Atkinson [EMAIL PROTECTED] wrote,
 
  The key word here is excessive.   If you are confusing your self by
  using the same name for everthing than you need to use seperate function
  names.  So you are saying that haskell should avoid all featurs that can
  be abused. 
 
 Excessive by my definitions if the use of one function name
 for `union' and `unionBy'.  What's the harm in using two
 function names here?  Where overloading makes sense `union'
 uses it already.  If you have to use `unionBy', this is
 because the elements of the set are not part of `Eq' or you
 want to use something else than standard equality.  In other
 words, there is a good reason for using `unionBy' contained
 in the algorithm or at least the structure of your program
 (otherwise, you have probably already made a mistake in your
 class definitions).  As there is such a reason, you should
 document it by using `unionBy' instead of `union' -
 everything else is, frankly speaking, careless software
 engineering.


I am not going to argue with you any more.  We have a different
definitions of what is easy to read.  To me:

  union fun list1 list2

makes perfect sense to me.  To you it may not.  The union and unionBy
is not so much what I object to as having to write two definitions for
union when I should only really have to write one using a generic
comparison function.

Also I hate not being able to have emulations such as

  data Bool = True | False
  data Bool2 = True | False | DontCare

which true adhoc overloading will allow.

Also, sense Haskell does not support objects in the form 
  object-function parms
you have to use
  function object parms

Unfortunately this means that two different objects can not have the same
"method" name unless that method is a type class.  And type classes won't
always work.

Also I hate long complicated system calls with lots of parameters which
you have to explicitly specify in the order given.  True adhoc
overloading will allow me to write an open function such as.

open HANDLE filename ReadOnly
open HANDLE filename Append
open HANDLE filename Write (Overwrite := False)

true adhoc overloading will allow me to do this.

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Mariano Suarez Alvarez

On Mon, 4 Oct 1999, Kevin Atkinson wrote:

 On Mon, 4 Oct 1999, Joe English wrote:
 
  I don't quite see what algorithm you're using
  to decide how many arguments are passed
  to the function.
 
 Neither do I.  I meant to express a general idea.  Perhaps that is not the
 best way to do it but that is what I would like to be able to do.
 
  What would you get if you typed:
  
  foo = foldr union []
 
 since foldr expects the function to have the signature
 (a-b-b) it will use the union which matches it, which
 will be the union :: [a] - [a] - [a] and not
 union :: ( a - a - Bool) - [a] - [a] - [a].

The problem is the two might match! Consider the definitions

union :: [a] - [a] - [a]
unionBy :: (a - a - a) - [a] - [a] - [a]
union = error ""
unionBy = error ""

f = union . map fst

g = unionBy . map fst

(I have dropped the (Eq a) context in the signature for union for
simplicity.) This goes thru the typechecker, and hugs tells me that

f :: [(a,b)] - [a] - [a]
g :: (a - (a - a, b)) - [a] - [a] - [a]


If one were allowed to write union for both union and unionBy, so which
one should one choose?

-- m

---
Mariano Suarez Alvarez
Departamento de Matematica - Universidad Nacional de Rosario
Pellegrini 250 - Rosario 2000 - Argentina 

El autor no responde de las molestias que puedan ocasionar sus escritos:
Aunque le pese
El lector tendra que darse siempre por satisfecho.

Nicanor Parra, `Poemas y antipoemas' (Advertencia al lector)

---







Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Kevin Atkinson

On Mon, 4 Oct 1999, Joe English wrote:

 Kevin Atkinson wrote:
 
  "Generic comparison function" is not really what I mean here.  What I
  mean is a single generic union which will have its
  comparison function default to (==) if one is not specified.
 
  It COULD be written something like
 
  union (cmp = (==)) l1 l2
...
  where
union l1 l2
  means
union (==) l1 l2
 
 I don't quite see what algorithm you're using
 to decide how many arguments are passed
 to the function.

Neither do I.  I meant to express a general idea.  Perhaps that is not the
best way to do it but that is what I would like to be able to do.

 What would you get if you typed:
 
 foo = foldr union []

since foldr expects the function to have the signature
(a-b-b) it will use the union which matches it, which
will be the union :: [a] - [a] - [a] and not
union :: ( a - a - Bool) - [a] - [a] - [a].

---
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/







Re: Tuples (was: To all those who don't like ad-hoc overloading)

1999-10-04 Thread matth

Jan de Wit wrote:
 
 On Sat, 2 Oct 1999, Matt Harden wrote:
 
 [snip]
   
I like that, but I wish we had a way to get the "head" and "tail" of
tuples, just as we do with lists, and combine them.  Maybe a (:,)
operator that works like this:
   
a :, (b :, ()) = (a,b)
a :, () = UniTuple a
a :, (b,c) = (a,b,c)
a :, (UniTuple b) = (a,b)
   
Also allow pattern matching on this operator.
   
 [snip]
   
This seems a little too obvious to me.  Has it been suggested and shot
down before?
   
Matt Harden
   
 Well, you can define a class Splittable:
 
 class Splittable a b c where
   spl :: a - (b,c)  -- split tuple
   lps :: (b,c) - a  -- reverse split
 
 With fairly obvious instances for Splittable a a (), Splittable (a,b) a b,
 Splittable (a,b,c) a (b,c) etc. The only problem with this kind of solution
 is that when you type, e.g. spl (3,4,5), hoping to obtain (3,(4,5)), hugs
 complains with:
 ERROR: Unresolved overloading
 *** Type   : (Num a, Num b, Num c, Splittable (c,b,a) d e) = (d,e)
 *** Expression : spl (3,4,5)
 

Yes, I have been thinking of almost the same thing, except I would not
have any arbitrary (x) be a 1-tuple (unituple? monotuple?), because then
what is ((x,y))?  A 1-tuple, or a 2-tuple?  Also, under your scheme,

   spl (x,(y,z)) = spl (x,y,z) = (x,(y,z))

... which for some reason bothers me a lot.  That's why I use a UniTuple
datatype above.  Btw, the user would almost never actually *encounter* a
UniTuple.  Certainly zip', show, read, etc. can be defined without using
it.

Another option would be a class that converts tuples to/from a
"cascading pair":

   cascade   (a,b,c) = (a,(b,(c,(
   cascade   ()  = ()
   cascade   (a,b)   = (a,(b,()))
   uncascade (b,())  = UniTuple b  -- or this can be undefined

The un/cascade scheme allows us to avoid 1-tuples altogether.  Of course
un/cascade and spl/lps can be defined in terms of one another.

Btw. I still would want the compiler/interpreter to auto-generate these
class instances for all tuples the way it currently does for Eq, Ord,
Show, Read, Ix, etc...  The nice thing is, instances of those classes
can be created in terms of Splittable (or it's equivalent).  Same goes
for Zippable, of course, and I can think of more uses.

 However, it seems that Mark Jones has an extension to Hugs in the works
 where you can specify that the types b and c in the class depend on a,
 which would resolve this issue. See http://www.cse.ogi.edu/~mpj/fds.html
 for details - I really hope the September release comes quickly !!!

I'll look at the extension.  It seems to be sorely needed.  Without it,
I can't figure out a way to define Zippable (or Eq, Ord, etc.) in terms
of Splittable.  Can you?

 Bye,
 
 Jan de Wit
 

Thanks
Matt






Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Joe English


Kevin Atkinson wrote:

 "Generic comparison function" is not really what I mean here.  What I
 mean is a single generic union which will have its
 comparison function default to (==) if one is not specified.

 It COULD be written something like

 union (cmp = (==)) l1 l2
   ...
 where
   union l1 l2
 means
   union (==) l1 l2


I don't quite see what algorithm you're using
to decide how many arguments are passed
to the function.

What would you get if you typed:

foo = foldr union []

for example?


--Joe English

  [EMAIL PROTECTED]






Re: To all those who don't like ad-hoc overloading

1999-10-04 Thread Carlos Camarao de Figueiredo


Considering: 

foldr:: (a - b - b) - b - [a] - b
union:: [a] - [a] - [a]   and
union :: ( a - a - Bool) - [a] - [a] - [a]

Then:
f = union . map fst

where:

map:: (a - b) - [a] - [b]
(.):: (a - b) - (c - a) - c - b
fst :: (a,b) - a

has type (in System CT)

---
{ union:: b - [a] - c }. [(b, d)] - [a] - c
---

which comes from the generalisation of the two possibilities: 

 [(a, d)] - [a] - [a]
and
 [(a - a - Bool), d] - [a] - [a] - [a]

Here: 
 b is the generalisation of [a] and (a - a - Bool)
 c is the generalisation of [a] and [a] - [a]

By the way, I would appreciate if someone could explain the type

   g :: (a - (a - a,b)) - [a] - [a] - [a]
*
   (where g = unionBy . map fst)

given by Hugs (ghc behaves differently... ).

Yours,

Carlos








Re: To all those who don't like ad-hoc overloading

1999-10-02 Thread Matt Harden

Scott Turner wrote:
 
 Alex Ferguson:
 Kevin Atkinson:
  I take it that you are happy with names such as:  [long list]
 
 Yes.  Certainly I'm more than happy that types with completely different
 signatures have different names.
 
 I also prefer to keep the names distinct when the meanings are distinct.  I
 got to thinking about zip and unzip, zip2 and unzip2, etc. which gave a
 feeling of not being so distinct.  Turns out, it's currying which prevents
 their signatures from being combined.  Non-curried versions can be defined
 on general tuples, with just one pair of names:
 
 class Zippable tOfLists tsInList
   where
 zip' :: tOfLists - [tsInList]
 unzip' :: [tsInList] - tOfLists
 instance Zippable () ()
   where
 zip' () = repeat ()
 unzip' _ = ()
 instance Zippable ([t],[u],[v]) (t,u,v)
   where
 zip' (x:xs, y:ys, z:zs) = (x,y,z): (zap (xs, ys, zs))
 zip' _ = []
 unzip' ((x,y,z):more) = (x:xs, y:ys, z:zs)
   where
 (xs, ys, zs) = unzip' more
 instance Zippable ([t]) (t)
 instance Zippable ([t],[u]) (t,u)
 instance Zippable ([t],[u],[v],[w]) (t,u,v,w)
 etc. left as an exercise.
 
 Thus, the uglier cases on Kevin Atkinson's list can be addressed within
 Haskell's current overloading system.
 

I like that, but I wish we had a way to get the "head" and "tail" of
tuples, just as we do with lists, and combine them.  Maybe a (:,)
operator that works like this:

a :, (b :, ()) = (a,b)
a :, () = UniTuple a
a :, (b,c) = (a,b,c)
a :, (UniTuple b) = (a,b)

Also allow pattern matching on this operator.

Then we could define the following:

instance Zippable () ()   -- as defined by Scott above

instance (Zippable b' b) = Zippable ([a] :, b') (a :, b) where
   zip' (h :, t) =
  case (h :, (zip' t)) of
 ([] :, _) - []
 (_ :, []) - []
 (x:xs :, y:ys) - (x :, y) : zip' (xs :, ys)
   unzip' ((x :, y): more) = (x:xs :, unzip' (y:ys)) where
 (xs :, ys) = unzip' more
   unzip' [] = ([] :, unzip' [])  -- [] takes on three different types
here!

Thus we get Zippable instances for all tuples for free.

This also allows us to define Show, Read, Eq, and Ord instances for all
tuples in one fell swoop just as it allows for Zippable.

This seems a little too obvious to me.  Has it been suggested and shot
down before?

Matt Harden






Re: To all those who don't like ad-hoc overloading

1999-09-30 Thread Scott Turner

Alex Ferguson: 
Kevin Atkinson:
 I take it that you are happy with names such as:  [long list]

Yes.  Certainly I'm more than happy that types with completely different
signatures have different names.

I also prefer to keep the names distinct when the meanings are distinct.  I
got to thinking about zip and unzip, zip2 and unzip2, etc. which gave a
feeling of not being so distinct.  Turns out, it's currying which prevents
their signatures from being combined.  Non-curried versions can be defined
on general tuples, with just one pair of names:

class Zippable tOfLists tsInList
  where
zip' :: tOfLists - [tsInList]
unzip' :: [tsInList] - tOfLists
instance Zippable () ()
  where
zip' () = repeat ()
unzip' _ = ()
instance Zippable ([t],[u],[v]) (t,u,v)
  where
zip' (x:xs, y:ys, z:zs) = (x,y,z): (zap (xs, ys, zs))
zip' _ = []
unzip' ((x,y,z):more) = (x:xs, y:ys, z:zs) 
  where
(xs, ys, zs) = unzip' more
instance Zippable ([t]) (t)
instance Zippable ([t],[u]) (t,u)
instance Zippable ([t],[u],[v],[w]) (t,u,v,w)
etc. left as an exercise.

Thus, the uglier cases on Kevin Atkinson's list can be addressed within
Haskell's current overloading system.

--
Scott Turner
[EMAIL PROTECTED]   http://www.ma.ultranet.com/~pkturner






Re: To all those who don't like ad-hoc overloading

1999-09-28 Thread Alex Ferguson


Kevin Atkinson:
 I take it that you are happy with names such as:

[long list]

Yes.  Certainly I'm more than happy that types with completely different
signatures have different names.