RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-05 Thread Simon Peyton-Jones
| From: Ross Paterson [mailto:[EMAIL PROTECTED]
| 
| On Thu, Mar 04, 2004 at 09:21:23AM -, Simon Peyton-Jones wrote:
|  My personal view is this: we should have adopted the ML view of
records.
|  It solves the immediate problem, and no more elaborate scheme seems
|  sufficiently right to be declared the winner.Alas, like all
other
|  proposals, it's not backward compatible, and hence not likely to
fly.
| 
| About a year ago, you were toying with a simple polymorphic system
with
| just has predicates.  If these were automatically derived, it seems
| you'd get something quite close to backward compatible, except for the
| pesky extra lifting in record types, and not being able to omit fields
| when constructing the record.  (And update might not statically check
| that all fields belong to the same constructor, for the simple version
| of the type system.)  Is that just too clunky?

It's possible, but I don't know.  Speaking for myself, I've rather lost
motivation on the records front, because the design space does not seem
to have a clear optimum point.  Adding has predicates in full glory
seems overkill to get re-use of labels.  Ah, but they also give you
polymorphic record operations!  Yes, but so do other versions, with
different and rather subtle technical tradeoffs.  That's why I've backed
up to something extremely simple: either (a) disambiguate record labels
by qualifying with the type constructor or (b) go the ML route. 

None of this is to discourage people from experimenting with variants --
quite the reverse.  That's how we may find out what a good system is. 

Simon
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-05 Thread Tom Pledger
Conor McBride wrote:
[...]
There's a catch, of course. When you write

 r | e

you give the typechecker no clue as to the type of r: it just
has to infer the type of r and hope it's a datatype. 

This is reminiscent of an issue I encountered a year or so ago, when 
designing a language. The main example  I used was a function for 
calculating the magnitude of a two dimensional vector. It would be nice 
to simplify this

   magnitude v = sqrt ((v | x)*(v | x) + (v | y)*(v | y))

to this

   magnitude v = v | sqrt (x*x + y*y)

but how was the compiler to know that x and y are fields of v, but sqrt 
and (+) and (*) aren't?

What I ended up doing was making a rule that if the record expression 
(the part to the left of the |) could not be statically tracked to 
something which revealed the field names, then the right hand side (of 
the |) must contain exactly one free variable. This static tracking 
took place before type inference, so it was in line with Simon PJ's 
preference for keeping scope and type inference separate.

I also used some syntactic sugar for explicit record narrowing, so the 
final version of the magnitude function was

   magnitude v = v(.x, .y) | sqrt (x*x + y*y)

which was quite similar to Cayenne's open ... use ... in ... feature.

Regards,
Tom Pledger
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-04 Thread Simon Peyton-Jones
| detail, of course ;).  What I'm secretly hoping is that the
| GHC/hugs/HBC people will see what I'm trying to achieve, tell me I'm
| totally nuts, and then suggest an alternative, much simpler approach
| which gives us exactly the same goal ...

As I implied earlier, I am thus far unconvinced that the complexity cost
justifies the benefit.  Let me suggest two simpler alternatives.

Alternative 1

Given 
import FiniteMap( FM, add {- :: FM a b - a - b - FM a b -} )
and fm :: FM Int Bool, 
you want
fm.add x y
to mean the same as
add fm x y
(but in addition allow lots of unrelated 'add' functions)

My objection is that the type of 'fm' is a matter of inference, whereas
in Java it'd be a matter of explicit declaration.  But you could adapt
your story to be more explicit, thus

FM.add fm x y

The qualifier here is the *type* not the *module*.  (Let's assume they
share a name space for now.)  This would work for record selectors too:
data T = T { x::Int, y::Int }
data S = S { x::Int, y::Int }

Now
f p q = T.x p + S.y q

I guess the rule is that you can qualify a function by the name of the
outermost type constructor of its first argument.

I would restrict this only to functions with explicitly-declared types,
so that there's no interaction with inference.

Alternative 2

If the big bug-bear is record selectors, let's focus on them
exclusively.  I now think that ML got it right. ML records are simply
labelled tuples.  So just as (Bool,Int) is an anonymous type, so is
{x::Bool, y::Int}.  Indeed (Bool,Int) is just shorthand for {#1::Bool,
#2::Int}.

In Haskell, a function with a tuple argument takes exactly that tuple:
f :: (Bool,Int) - Bool
f (x,y) = x
Here, f cannot take a 3-tuple or a 89-tuple.  In ML it's the same with
records (I'm not getting the ML syntax right, but you'll get the idea):
f :: {x::Bool, y::Int} - Bool
f r = r.x
Here f cannot take a record of shape other than {x::Bool,y::Int}.  You
are allowed to write
f {x, ...} = x
but you must then explain f's argument type separately.  For example you
can write
f :: {x::Bool, p::String, q::Bool} - Bool
f {x, ...} = x

So there is no sub-typing, no row polymorphism, no attempt to give
f r = r.x
a fancy type that makes f applicable to any record with an x field.  

On the other hand, there is also no problem with many records having the
same field name either, which is the problem we started with.  There are
no implicitly-defined record selectors either: you have to use pattern
matching for that.


My personal view is this: we should have adopted the ML view of records.
It solves the immediate problem, and no more elaborate scheme seems
sufficiently right to be declared the winner.Alas, like all other
proposals, it's not backward compatible, and hence not likely to fly.

Simon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-04 Thread Simon Peyton-Jones
| So there is no sub-typing, no row polymorphism, no attempt to give
|   f r = r.x
| a fancy type that makes f applicable to any record with an x field.
| 
| On the other hand, there is also no problem with many records having
the
| same field name either, which is the problem we started with.  There
are
| no implicitly-defined record selectors either: you have to use pattern
| matching for that.

Andreas says:

| Actually, #l is just syntactic sugar for (\{l=x,...}-x), which
implies
| that you might need type annotations.


Yes I was wrong to say that there are no implicitly-defined record
selectors; (#l r) is exactly that.  Syntactically I'd prefer (r.l); but
regardless, it's a syntactic construct distinct from function
application, which must be monomorphic.  Yes, that's a kind of
interaction between binding and type system (of the kind I objected to)
but a very weak and well-behaved kind of interaction. 

Simon
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-04 Thread Andreas Rossberg
Simon Peyton-Jones wrote:
If the big bug-bear is record selectors, let's focus on them
exclusively.  I now think that ML got it right. ML records are simply
labelled tuples.
Note that this is true only for SML, not for Caml.

So just as (Bool,Int) is an anonymous type, so is
{x::Bool, y::Int}.  Indeed (Bool,Int) is just shorthand for {#1::Bool,
#2::Int}.
A bit of nitpicking: (Bool,Int) would be shorthand for {1::Bool,2::Int}. 
In SML, labels may be numeric or alpha-numeric. OTOH, the hash is the 
projection operator (ASCII art for \pi), which can be used for both 
kinds of labels:

  #2 (x,y,z)
  #b {a=x, b=y, c=z}
Actually, #l is just syntactic sugar for (\{l=x,...}-x), which implies 
that you might need type annotations.

There are
no implicitly-defined record selectors either: you have to use pattern
matching for that.
Or projection using #.

Cheers,

	- Andreas

--
Andreas Rossberg, [EMAIL PROTECTED]
Let's get rid of those possible thingies!  -- TB

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-04 Thread Andreas Rossberg
Simon Peyton-Jones wrote:
| Actually, #l is just syntactic sugar for (\{l=x,...}-x), which
implies
| that you might need type annotations.
Yes I was wrong to say that there are no implicitly-defined record
selectors; (#l r) is exactly that.  Syntactically I'd prefer (r.l); but
regardless, it's a syntactic construct distinct from function
application, which must be monomorphic.
I'm not sure I parsed your sentence correctly, but in SML, (#l r) indeed 
*is* a function application, and #l is a perfectly normal function, as 
its desugared form reveals. It just fails to have a principal type (due 
to the lack of row polymorphism), so its type must be derivable from 
context - which might involve a type annotation.

BTW, I'd prefer r.l as well. A section like (.l) could then give you the 
equivalent of #l.

	- Andreas

--
Andreas Rossberg, [EMAIL PROTECTED]
Let's get rid of those possible thingies!  -- TB

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-04 Thread Ross Paterson
On Thu, Mar 04, 2004 at 09:21:23AM -, Simon Peyton-Jones wrote:
 My personal view is this: we should have adopted the ML view of records.
 It solves the immediate problem, and no more elaborate scheme seems
 sufficiently right to be declared the winner.Alas, like all other
 proposals, it's not backward compatible, and hence not likely to fly.

About a year ago, you were toying with a simple polymorphic system with
just has predicates.  If these were automatically derived, it seems
you'd get something quite close to backward compatible, except for the
pesky extra lifting in record types, and not being able to omit fields
when constructing the record.  (And update might not statically check
that all fields belong to the same constructor, for the simple version
of the type system.)  Is that just too clunky?
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-04 Thread Conor McBride
Hi

While we're talking about SML, I think there are a few other things
worth stealing...


1) I still miss multiline pattern matching in lambda

  (fn p1 = e1 | p2 = e2 | ...)

not strictly necessary, but often less disruptive of the text than
either a let/where-introduced helper-function or \ x - case x of ...
especially when there's more than one argument.

Doubtless there's some deep reason why Haskell doesn't have these
that I'm too young to remember.


2) I miss local implementation-decls in interface-decls end

Is there some fabulous layout rule for `where' clauses that means
the same thing?


3) I miss `open' from the module system. This allows

  let open Structure in expression end
  local open Structure in declarations end

reducing your program's acne. I often wonder why the OO world has
no room for Pascal's lovely old `with ... do ...'. [Pascal even
had variant records with case expressions: it wasn't remotely
type-safe, but it looked like datatypes. What happened to them?
Programmers like sums, but software engineers like products...]


Haskell already has per-module namespaces; everything has a unique
long name; good start. Now what we need is more control over the
meaning of short names. Could we have local opening of (already
imported) modules, simply rebinding the relevant short names in
their scope? You'd get the localized namespace you might want
at the cost of one scoped declaration, rather than a zillion
projections.

And while we're at it...

 Simon Peyton-Jones wrote:
 
  If the big bug-bear is record selectors, let's focus on them
  exclusively.  I now think that ML got it right. ML records are simply
  labelled tuples.

The pattern-matching was always dreadful, especially if you just
wanted to tweak one field, but I expect that could be dealt with.

Andreas Rossberg wrote:
 
 Note that this is true only for SML, not for Caml.
 
  So just as (Bool,Int) is an anonymous type, so is
  {x::Bool, y::Int}.  Indeed (Bool,Int) is just shorthand for {#1::Bool,
  #2::Int}.
 
 A bit of nitpicking: (Bool,Int) would be shorthand for {1::Bool,2::Int}.
 In SML, labels may be numeric or alpha-numeric. OTOH, the hash is the
 projection operator (ASCII art for \pi), which can be used for both
 kinds of labels:
 
#2 (x,y,z)
#b {a=x, b=y, c=z}
 
 Actually, #l is just syntactic sugar for (\{l=x,...}-x), which implies
 that you might need type annotations.

That's a neat piece of syntax, but if you're willing to look at types,
you might be able to introduce an opening operator for records,
| say, at the cost of restricting field labels to being valid names.
ie if

  r :: {a::A, b::B, c::C}

  r | e   means let {a=a,b=b,c=c} = r in e

Again, the usual projection is a special case.

No reason why you couldn't use this opening notation for the existing
field-labelled datatypes. OK, you'd be shadowing projection functions
with field names, but that's not so shocking.

This opens a further, if questionable, possibility, viz

  data MyQuad = MyQuad {a::Int, b::Int, c::Int} |
  f x = (a * x + b) * x + c

declaring a computed field f for that constructor. As usual, only your
conscience prevents you misusing this facility in a multi-constructor
type. For backward compatibility, you'd need to leave a, b and c as
global names, but you could choose to make f accessible only on opening.
That leaves open the possibility of

  data MyQuad = MyQuad {globa::Int, globb::Int, globc::Int} |
  a = globa
  b = globb
  c = globc
  f :: Int - Int
  f x = (a * x + b) * x + c

which I'm sure could be sugared to

  data MyQuad = MyQuad {| a::Int, | b::Int, | c::Int} |
  f :: Int - Int
  f x = (a * x + b) * x + c

meaning that the fields should not have global names, only local
names on opening.

Or one could add `methods' to the whole type, being functions
on that type, defined by pattern matching, but with one argument
left of |

  data Fred = F1 | F2 | F3
with cycle :: Fred
 F1 | cycle = F2
 F2 | cycle = F3
 F3 | cycle = F1

Again, cycle wouldn't be globally declared.

Goodness me, it's a per-type namespace, but not for `ordinary'
application.

There's a catch, of course. When you write

  r | e

you give the typechecker no clue as to the type of r: it just
has to infer the type of r and hope it's a datatype. I suggest
this is perfectly sustainable, given that

  (1) your function already has a top-level type signature,
hasn't it?
  (2) this sort of thing happens all the time with ad-hoc
polymorphism anyway; when you have

  class Blah x where
blah :: x - x

  instance Blah (Maybe Int) where
blah Nothing = Just 0
blah (Just x) = Just (x + 1)

what's

  blah Nothing

?

Is this plausible?

Conor
___
Haskell mailing list
[EMAIL 

Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-03 Thread Andre Pang
On 28/02/2004, at 1:30 AM, Per Larsson wrote:

In my humble opionon explicit module prefixes are a feature, which 
enhance
code clarity, and not something you want get rid of using rather 
complex
namespace extensions. However, as Alastair Reid's mail in this thread
indicates there are weaknesses in haskell's export mechanism. But 
these would
be far more easy to fix than introducing the suggested per type 
namespace
extension.
Sorry, I don't buy this.  If there is effort made to improve the module 
system to cope with the problems Alastair mentioned, we still have to 
write 'import FiniteMap as FM' followed by 'FM.add fm', instead of 
simply 'fm.add'.  We fix the problems Alastair mentioned, but are still 
left with an less-than-optimal solution.

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-01 Thread oleg

Simon Peyton-Jones wrote:

 In Haskell today, you can at least tell what value is bound to each
 identifier in the program, *without* first doing type checking. 

I'm afraid I'm confused. In the following code

 data Z
 data S a

 class Card c where c2int:: c - Int

 instance Card Z where c2int _ = 0
 instance (Card c) = Card (S c) where c2int _ = 1 + c2int (undefined::c)

 foo = c2int (undefined::(S (S (S (S Z)

how can one tell the value of foo without first doing the
typechecking? Without typechecking, we can't use c2int and can't even
construct any meaningful value of class Card. For c2int, the type is
the ``value.'' Overlapping instances, polymorphic recursion -- all
seem to make the value determination even more uncertain.

Andre Pang wrote:

 1) now I have to manually declare a class definition for every single 
 function, and I have to declare it in advance before any module defines 
 that function (most serious problem; see below),

 However, declaring the instance first requires declaring the type
 class itself, and that _is_ a problem, because that's exactly what I'm
 trying to work around.  Without 20/20 hindsight, you cannot say with
 certainty what type signatures a generic function (like 'phase' or
 even 'add') can support, because it's not a generic function,

But in the solution posted previously, for each ad hoc overloadable
function, the corresponding class *always* has the same
signature:

class HasAdd a b | a-b where add:: a-b

Therefore, we don't need clairvoyance to define an overloadable
function that way. If I need an overloadable function add, I can go
ahead and define the above class, and then add an instance. I can do
that without knowing all possible overloadable instances of add,
present or future. What if somebody else did the same in some other
module? If that somebody else followed the conventions, he would
introduce exactly the same class declaration. If GHC or its developers
could somehow be persuaded to overlook _exact_ duplicate class
declarations, then that part of the problem can be solved. The class
declaration itself could perhaps be generated by Template Haskell.

The discussed solution is quite related to some of the Records
proposals (which have been discussed here half a year ago). There too
we have the inconvenience of choosing unique names for field labels.

 data Person = Person {_pname:: String, _paddress:: String}
 data Computer = Computer {_cname::[String], _caddress:: Int}

 class HasName a b | a-b where name:: a-b
 class HasAddress a b | a-b where address:: a-b

 instance HasName Person String where name = _pname
 instance HasAddress Person String where address = _paddress
 instance HasName Computer [String] where name = _cname

 instance (HasName n r) = HasName (Maybe n) (Maybe r) where
 name = fmap name

 -- Alas, the following will break the dependency...
 --instance (Num a) = HasName a String where name = show

 -- But the following works: overlapping instances at work
 instance (HasAddress a b) = HasName a b where name = address

 instance HasAddress Int (Int-String) where address x y = show (x+y)

 newtype W a = W a   
 instance (Num a) = HasAddress (W a) String where address (W a) = show a

 test2 = let p = Person  Anonymous  N/A
 c = Computer [FQDN,localhost] 10
   in person named  ++ (name p) ++  at a computer  ++ (head (name c))
  ++  and another  ++ (show$ name p1)
where p1 = (Nothing::Maybe Person)

The first few lines of the code is boilerplate and could be
automatically generated. As you can see, we can even handle a limited
form of polymorphism, and even do a hand off. For example, if some
thing doesn't have a name but has an address, we can use the address
as its name. Alas this ``backtracking'' isn't as general as we might
wish. At some point we have to introduce wrappers (like W a above) to
hand over the dispatch to another class. It's possible to do the
dispatch on a class, but it's a bit too painful. OTH, the wrappers
such as 'W' may be considered as an 'alternative view' of an object.
By wrapping an object, we can switch its behavior from the main one to
an alternative without any run-time penalty.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-01 Thread Simon Peyton-Jones
|  In Haskell today, you can at least tell what value is bound to each
|  identifier in the program, *without* first doing type checking.
| 
| I'm afraid I'm confused. In the following code
| 
|  data Z
|  data S a
| 
|  class Card c where c2int:: c - Int
| 
|  instance Card Z where c2int _ = 0
|  instance (Card c) = Card (S c) where c2int _ = 1 + c2int
(undefined::c)
| 
|  foo = c2int (undefined::(S (S (S (S Z)
| 
| how can one tell the value of foo without first doing the
| typechecking? 

What I meant was that you can always tell what executable code a value
is bound to, without type checking.  'foo' is bound to the code for
'c2int (undefined::(S (S (S (S Z)'. 
'c2int' is bound to code that extracts a method from it's first argument
(which is a dictionary for Card).

In any higher-order language, a function might invoke one of its
arguments
f x g = g x
but I still say that it's clear what code is executed when f is called!

It's true that with type classes the value of one of the dictionary
argument is dependent on type checking, which certainly muddies the
waters.  But at least the type of 'c2int' isn't affected by which method
is chosen, which is the real difficulty I was pointing out

Simon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-27 Thread Simon Peyton-Jones
 The idea that I've been throwing around is to be able to define a 
 separate namespace for each type; a function can either belong in a 
 global (default) namespace, or belong in a particular type's 
 namespace.  So, in the above example, instead of writing addToFM fm 
 ..., we could instead associate an 'add' function with the FiniteMap 
 type, so we could write fm.add ... instead.  Provided that fm's type

 is monomorphic, it should be possible to call the 'correct' add 
 function; if we defined another 'add' function that's associated with

Remember, too, that in OO languages the type of 'fm' is usually
declared, in advance, by the programmer.  In Haskell it isn't.   That
makes it much harder to figure out which 'add' function is going to be
used.

Which 'add' function is chosen depends on type type of 'fm'.  But the
add function that is chosen in turn influences the type of the other
arguments.  For example, in the call (fm.add foo), the type of 'foo' is
influenced by the choice of 'add'.  But the type of 'foo' might (by the
magic of type inference) affect the type of 'fm'

In Haskell today, you can at least tell what value is bound to each
identifier in the program, *without* first doing type checking.  And the
binding story, all by itself, is somewhat complicated.  The typing story
is also (very) complicated.  Winding the two into a single indissoluble
whole would make it far more complicated still.

My nose tells me that this way lies madness.  

But I've been wrong before.

Simon
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-27 Thread ozone
On 27/02/2004, at 9:51 AM, David Bergman wrote:

So at the moment, many Haskellers will append the type name to the
function to indicate that it only works on that particular data type.
In this respect, Haskell is at a disadvantage vs most object-oriented
languages, because in them, you can write x.add, and the type system
will perform object-oriented polymorphism for you and call the
correct add method, no matter if x is a FiniteMap or a Set.  Writing
addToFM fm ... or addToSet set ... is surely a lot more
inconvenient than writing fm.add or set.add, no?
Yes. But, you are refering to overloading, no? And, not subtype 
polymorphism
(which is what I denote with object-oriented polymorphism)? Just to 
make
things clear in my mind.
Yes, what I'm referring to is essentially overloading.  I called it 
object-oriented polymorphism because that's typically what OO people 
call such a thing :).  (I should know better to use OO terminology on a 
Haskell list; won't happen again ...).  However, it's form of 
overloading that Haskell cannot currently handle  well with type 
classes -- Oleg's post proves that you can do it, of course, but that's 
a (very good) hack rather than a long-term solution.

So, you have thought of automatically, but implicitly, introduce a 
namespace
for each data type, and then have Haskell employ Koenig Lookup, to 
decide
which function an expression is refering to?
It's a bit like Koenig lookup in that it has the same effect, although 
it's probably easier for the compiler to infer the namespace wanted, 
since we write expr.function ... rather than function expression 
  Writing function expression ... would work too, but then it 
looks like a standard function call rather than a function call 
associated with a particular type, and I think that causes more 
confusion.  Long-time Haskell users understand that writing foo.f 
means use f in namespace foo; changing around the language semantics 
to mean that f foo now means use f in namespace foo would make lots 
of people rather unhappy :).

You realize, of course, that mere intranamespacial parameter type 
lookup
(regular overloading) would achieve the same effect, without the 
(implicit)
namespaces?
I'm not sure what you mean by intranamespcial parameter type lookup 
-- can you explain?

There are a number of means by which the x in x.add can be
communicated to the actual function: it's similar to the hidden 'self'
or 'this'
variable that's present when you invoke a method on an object in OO.
Perhaps x is passed to the function as its first parameter, or maybe
it could be its last parameter, or even an arbitrary parameter (where
the parameter it's passed as could be defined in the type signature of
the function).  Perhaps 'self' or 'this' could be an implicit
parameter.
Any one of them will work just fine, I think.
Again, I think you are confusing the runtime dispatching subtype 
polymorpism
from overloading. Overloading would do what you want, while the subtype
polymorphism could (still) be handled by class, and instances of 
classes,
the Generic Programming way.
I (think I) understand the difference between dynamic binding vs 
overloading: here, all I'm after is trying to use the type system to 
give us a very simple form of overloading (e.g. based on the first 
argument to a function), that gives us the same effect as a per-type 
name space.

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-27 Thread ozone
On 27/02/2004, at 4:48 PM, Brandon Michael Moore wrote:

On Fri, 27 Feb 2004 [EMAIL PROTECTED] wrote:

On 27/02/2004, at 1:13 PM, [EMAIL PROTECTED] wrote:

1) now I have to manually declare a class definition for every single
function, and I have to declare it in advance before any module 
defines
that function (most serious problem; see below),

2) I then have to declare instances of that type class for every
function I define,
3) the type signature for phase reveals no clues about how to use that
function.
Declaring a type class instance is really no problem.
I agree that declaring a type class instance per function is not a huge 
deal (if it can be automatically done by the compiler).  However, 
declaring the instance first requires declaring the type class itself, 
and that _is_ a problem, because that's exactly what I'm trying to work 
around.  Without 20/20 hindsight, you cannot say with certainty what 
type signatures a generic function (like 'phase' or even 'add') can 
support, because it's not a generic function, it's a function which is

When you declare a type class, you are making a trade-off: you are 
saying that the interface for this function is forever set in stone, 
and it cannot be changed by any instances under any circumstances.  In 
return for saying that interface is immutable, you get two major 
benefits: (1) an immutable interface, i.e. so you can guarantee that 
whenever you use ==, you _know_ the type signature is :: Eq a = a - a 
- Bool, and no instance can try to subvert that (unless your name is 
Oleg ;), and (2) you get very powerful overloading capabilities.

However, the disadvantage of this tradeoff is that because the type 
signature is now set, you just used up another function name in the 
namespace.  So type classes are the wrong approach to solve this 
problem, because what I'm after is being able to clutter up a namespace 
as much as I like with whatever names I like, but I don't want a 
polymorphic function--I want a function which only operates on one 
specific, primary data type.

With the per-type namespace separation I'm advocating, you do not need
to know and declare in advance that each function will be 
overloaded,
you simply write a FiniteMap.add function and a Set.add function, and
you get a simpler form of namespace separation (or overloading) based
on the first parameter that's passed to it.  It is a solution which is
more _flexible_ than requiring type class definitions, and it is 
better
than having hungarian notation for functions.  In fact, I think that,
right now, if we replaced the current namespace separation offered by
the hierarchical module system, and instead only had this sort of
per-type namespace separation, things would still be better!
How much of the structure of the first paramater would you look at? 
Could
you an implementation for pairs that depended on the actual types in 
the
pair? I think you should try to take advantage of the existing type 
class
machinery as much as possible here, even if what you want are not 
exactly
(standard) type classes.
The idea is if you write fm.add, you look at the type of fm as much 
as possible.  If you see that fm is polymorphic, all bets are off, and 
the compiler raises an error and quits with prejudice.  If fm is 
monomorphic, you should be able to infer its type (which includes 
pairs/tuples) and thus know which namespace to select to find the 
correct add function.   So the main requirement for this to work is 
whether it's possible to infer the type of fm; since I'm not a type 
theorist, I have no idea if that is in fact possible at all.

I realise my idea isn't very general in that it only allows this
namespace lookup/overloading based on the type of a single argument
parameter, and I think it would be possible with a bit more thinking 
to
generalise it to work based on multiple arguments (e.g. via
argument-dependent lookup, or whatnot).  But even in its current form,
I honestly think it offers far more flexibility and would lead to
cleaner APIs than is currently possible.
Read the paper and see if you think something like that might be 
useful.
In any case, I think there's a decent chance that something useful for
this would also be useful for building interfaces to object-oriented
libraries, and vicea versa. I think there's probably something that 
covers
both cases nicely and uniformly.
I've had a read of both the SPJ/Shields paper on OO-style overloading 
in Haskell, and I've also had a skim over another paper called A 
Second Look at Overloading which describes another overloading 
calculus called System O.  I don't think either paper directly 
addresses the problem I'm trying to solve, although some elements in 
the paper (e.g. closed classes) may provide a framework which is 
capable of addressing the problem, if something like fm.add can be 
translated to such a framework via major syntactic sugar :).

--
% Andre Pang : trust.in.love.to.save

RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-27 Thread Graham Klyne
At 09:28 27/02/04 +, Simon Peyton-Jones wrote:
Which 'add' function is chosen depends on type type of 'fm'.  But the
add function that is chosen in turn influences the type of the other
arguments.  For example, in the call (fm.add foo), the type of 'foo' is
influenced by the choice of 'add'.  But the type of 'foo' might (by the
magic of type inference) affect the type of 'fm'
In Haskell today, you can at least tell what value is bound to each
identifier in the program, *without* first doing type checking. [...]
Nicely explained.  Until this, I had a feeling that the proposed 
type-directed value-binding resolution was potentially problematic for 
Haskell, but couldn't say why.

#g


Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-27 Thread Brandon Michael Moore


On Fri, 27 Feb 2004, Simon Peyton-Jones wrote:

  The idea that I've been throwing around is to be able to define a
  separate namespace for each type; a function can either belong in a
  global (default) namespace, or belong in a particular type's
  namespace.  So, in the above example, instead of writing addToFM fm
  ..., we could instead associate an 'add' function with the FiniteMap
  type, so we could write fm.add ... instead.  Provided that fm's type

  is monomorphic, it should be possible to call the 'correct' add
  function; if we defined another 'add' function that's associated with

 Remember, too, that in OO languages the type of 'fm' is usually
 declared, in advance, by the programmer.  In Haskell it isn't.   That
 makes it much harder to figure out which 'add' function is going to be
 used.

 Which 'add' function is chosen depends on type type of 'fm'.  But the
 add function that is chosen in turn influences the type of the other
 arguments.  For example, in the call (fm.add foo), the type of 'foo' is
 influenced by the choice of 'add'.  But the type of 'foo' might (by the
 magic of type inference) affect the type of 'fm'

 In Haskell today, you can at least tell what value is bound to each
 identifier in the program, *without* first doing type checking.  And the
 binding story, all by itself, is somewhat complicated.  The typing story
 is also (very) complicated.  Winding the two into a single indissoluble
 whole would make it far more complicated still.

I thought this wasn't the case if there are type classes invovled. What
value is + bound to in 1 + 1? All I can think is to say that the
appropriate value of + is selected based on the types, or to say that the
value here is the class member (subsuming several instances). Either way
I don't see a method for overloading individual function names having a
greatly different story either way.

Actually, picking a version of a function (from the versions in scope)
based on which type actually works might be useful. It seems to extend the
handling of overlapping names in a useful direction again, resolving
ambiguity by assuming you meant to write a typeable program.

We would probably want some special syntax with the imports to
request/flag this behaviour, like import A; import B; import C; resolve
foo. One heuristic would be typechecking with no information on the
name(s) and checking that there is a unique way to resolve the ambiguity
at each point.

 My nose tells me that this way lies madness.

I think the general principle of using types to capture and infer intent
is still sound. It would be nice to have ad-hoc overloading also in cases
where we don't see a common intent between several functions to capture
with a typeclass (intents that we can't capture are arguments for
improving the class system).

A lot of haskell already looks like madness already anyway :)
We just need to find things that look like good madness ;)


 But I've been wrong before.

 Simon

Brandon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-27 Thread Per Larsson
In my humble opionon explicit module prefixes are a feature, which enhance 
code clarity, and not something you want get rid of using rather complex  
namespace extensions. However, as Alastair Reid's mail in this thread 
indicates there are weaknesses in haskell's export mechanism. But these would 
be far more easy to fix than introducing the suggested per type namespace 
extension. The present export list is also rather ugly from an aesthetic 
point of view, clottering the module header. I would love to see an, 
repeatable, explicit 'export' directive with similar keywords as the import 
directive. Allowing for example:
'export [all] hiding (...)' with obvious semantics.

Per Larsson

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-27 Thread David Bergman
Andre Ozone wrote:

 On 27/02/2004, at 9:51 AM, David Bergman wrote:
 
  So at the moment, many Haskellers will append the type name to the 
  function to indicate that it only works on that particular 
 data type.
  In this respect, Haskell is at a disadvantage vs most 
 object-oriented 
  languages, because in them, you can write x.add, and the type 
  system will perform object-oriented polymorphism for you 
 and call 
  the correct add method, no matter if x is a FiniteMap or a Set.  
  Writing addToFM fm ... or addToSet set ... is surely a 
 lot more 
  inconvenient than writing fm.add or set.add, no?
 
  Yes. But, you are refering to overloading, no? And, not subtype 
  polymorphism (which is what I denote with object-oriented 
  polymorphism)? Just to make things clear in my mind.
 
 Yes, what I'm referring to is essentially overloading.  I 
 called it object-oriented polymorphism because that's 
 typically what OO people call such a thing :).

No, they do not. What they call polymorphism, we call subype polymorphism
or, if we are really hard-core and/or old school, even ad-hoc polymorphism.
They do not even realize that overloading falls in the category of
polymorphism at all...

 (I should 
 know better to use OO terminology on a Haskell list; won't 
 happen again ...).

I think it is good that you do. We need that touch of engineering realism
sometimes ;-)

 However, it's form of overloading that 
 Haskell cannot currently handle  well with type classes -- 
 Oleg's post proves that you can do it, of course, but that's 
 a (very good) hack rather than a long-term solution.

I personally use (Haskell) classes for that overloading purpose, but in a
sense that Generic Programmers would call concept modelling.
 
  So, you have thought of automatically, but implicitly, introduce a 
  namespace for each data type, and then have Haskell employ Koenig 
  Lookup, to decide which function an expression is refering to?
 
 It's a bit like Koenig lookup in that it has the same effect, 
 although it's probably easier for the compiler to infer the 
 namespace wanted, since we write expr.function ... rather 
 than function expression 

Whether it is prefix or postfix should not alter the complexity of the
lookup considerably.

 Writing function expression 
 ... would work too, but then it looks like a standard 
 function call rather than a function call associated with a 
 particular type, and I think that causes more confusion.  
 Long-time Haskell users understand that writing foo.f 
 means use f in namespace foo; changing around the language 
 semantics to mean that f foo now means use f in namespace 
 foo would make lots of people rather unhappy :).

I would want it to look as an ordinary function. The single biggest problem
with Haskell, in my extremely humble opinion, is the shared namespace for
all data type accessors, with which you probably agree. It is what irritated
me the most with Entity-Relationship Diagram, that all fields need to have
unique name globally. This in contrast to instance variables, methods and
general overloading, as often found in OO languages.
 
  You realize, of course, that mere intranamespacial parameter type 
  lookup (regular overloading) would achieve the same effect, without 
  the
  (implicit)
  namespaces?
 
 I'm not sure what you mean by intranamespcial parameter type lookup 
 -- can you explain?

ah, I meant regular overloading, i.e., have a function be identified not by
its name, but by its whole signature, including the arity and parameter
type(s) [yes, curry, curry...]

  There are a number of means by which the x in x.add can be 
  communicated to the actual function: it's similar to the 
 hidden 'self'
  or 'this'
  variable that's present when you invoke a method on an 
 object in OO.
  Perhaps x is passed to the function as its first 
 parameter, or maybe 
  it could be its last parameter, or even an arbitrary 
 parameter (where 
  the parameter it's passed as could be defined in the type 
 signature 
  of the function).  Perhaps 'self' or 'this' could be an implicit 
  parameter.
  Any one of them will work just fine, I think.
 
  Again, I think you are confusing the runtime dispatching subtype 
  polymorpism from overloading. Overloading would do what you want, 
  while the subtype polymorphism could (still) be handled by 
 class, and 
  instances of classes, the Generic Programming way.
 
 I (think I) understand the difference between dynamic binding vs
 overloading: here, all I'm after is trying to use the type 
 system to give us a very simple form of overloading (e.g. 
 based on the first argument to a function), that gives us the 
 same effect as a per-type name space.

When I read my own response, I know realize that it sounds harsh. Sorry
about that. That was not the intention. I also think you understand and
appreciate the difference between the two forms of polymorphisms.

You touch at one of the core problems of Haskell.

Thanks,

David


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread Gabriel Dos Reis
David Bergman [EMAIL PROTECTED] writes:

|  The idea that I've been throwing around is to be able to define a 
|  separate namespace for each type; a function can either belong in a 
|  global (default) namespace, or belong in a particular type's 
|  namespace.  So, in the above example, instead of writing addToFM fm 
|  ..., we could instead associate an 'add' function with the FiniteMap 
|  type, so we could write fm.add ... instead.  Provided that fm's type 
|  is monomorphic, it should be possible to call the 'correct' add 
|  function; if we defined another 'add' function that's associated with 
|  the Set type, that will only get called if the 'x' in x.add is of 
|  type :: Set.  So, like OO languages which inherently give separate 
|  namespaces to their different objects, here we give separate 
|  namespaces to different
|  (monomorphic) types.  In this case, if one simply writes add instead 
|  of x.add, the compiler throws an error, because there is no 'add' 
|  function defined in the default namespace; add is only defined when a 
|  programmer writes x.add where x :: FiniteMap or x ::
|  Set[1].
| 
| This overloading by namespace is usually called either ADL
| (Argument-Dependent Lookup) or Koenig Lookup (especially in C++.)

Actually in C++, it is called argument dependent name lookup, and
that is the way the C++ definition text calls it. As Andy Koenig has
himself pointed out, he did not invent that rule.  He mentionned it
when the C++ committee was solving a name look-up problem
posed by namespaces to operator functions.  That name look-up rule
was later generalized to non-operator to cover the function-call
syntax -- which is what is most known today and referred to above. 

This ends my C++ hour on Haskell list :-)

-- Gaby
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread ozone
I've had an idea stewing in my head to do with per-type function 
namespaces, that the current module namespace discussion reminded me 
about.  The problem is that there is a limited namespace for functions, 
so that if you define a new data type, it is unwise to call functions 
which work on that data type a very generic name such as 'add'.  An 
example of this is Data.FiniteMap and Data.Set: both data types define 
a function to add things to their respective data types.

addToFM :: Ord key = FiniteMap key elt - key - elt - FiniteMap key 
elt
addToSet :: Ord a = Set a - a - Set a

So at the moment, many Haskellers will append the type name to the 
function to indicate that it only works on that particular data type.  
In this respect, Haskell is at a disadvantage vs most object-oriented 
languages, because in them, you can write x.add, and the type system 
will perform object-oriented polymorphism for you and call the 
correct add method, no matter if x is a FiniteMap or a Set.  Writing 
addToFM fm ... or addToSet set ... is surely a lot more 
inconvenient than writing fm.add or set.add, no?

The idea that I've been throwing around is to be able to define a 
separate namespace for each type; a function can either belong in a 
global (default) namespace, or belong in a particular type's 
namespace.  So, in the above example, instead of writing addToFM fm 
..., we could instead associate an 'add' function with the FiniteMap 
type, so we could write fm.add ... instead.  Provided that fm's type 
is monomorphic, it should be possible to call the 'correct' add 
function; if we defined another 'add' function that's associated with 
the Set type, that will only get called if the 'x' in x.add is of 
type :: Set.  So, like OO languages which inherently give separate 
namespaces to their different objects, here we give separate namespaces 
to different (monomorphic) types.  In this case, if one simply writes 
add instead of x.add, the compiler throws an error, because there 
is no 'add' function defined in the default namespace; add is only 
defined when a programmer writes x.add where x :: FiniteMap or x :: 
Set[1].

There are a number of means by which the x in x.add can be communicated 
to the actual function: it's similar to the hidden 'self' or 'this' 
variable that's present when you invoke a method on an object in OO.  
Perhaps x is passed to the function as its first parameter, or maybe it 
could be its last parameter, or even an arbitrary parameter (where the 
parameter it's passed as could be defined in the type signature of the 
function).  Perhaps 'self' or 'this' could be an implicit parameter.  
Any one of them will work just fine, I think.

However, this scheme is only for functions which have such a 'primary' 
data type to be associated with, such as FiniteMap or Set.  For 
functions which are truly polymorphic (such as ==), you still leave 
them in the default namespace.  Perhaps it's sensible to even make it a 
requirement that functions in the default namespace must be 
polymorphic: if they are monomorphic, they are associated with 
operating on a specific data type, so they should belong in a 
type-specific namespace.  You then still guarantee that such 
commonly-used polymorphic functions cannot be 'hijacked' to have stupid 
type signatures; i.e. == is always guaranteed to be :: Eq a - a - 
Bool.

Anyhow, feedback is more than welcome; I would certainly welcome this 
addition if it's feasible.  It feels inferior to be typing in 'addToFM 
foo' all the time when our OO brethren type the simpler and more 
succinct 'foo.add', especially given that Haskell's type system is far 
more powerful!

1. I haven't thought hard enough about whether it would be possible to 
have the same function name in both the 'default' namespace as well as 
in per-type namespaces, but my gut feeling says it should be OK.

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread Keith Wansbrough
 I've had an idea stewing in my head to do with per-type function 
 namespaces, that the current module namespace discussion reminded me 
 about.  The problem is that there is a limited namespace for functions, 
 so that if you define a new data type, it is unwise to call functions 
 which work on that data type a very generic name such as 'add'.
[..]
 The idea that I've been throwing around is to be able to define a 
 separate namespace for each type; a function can either belong in a 
 global (default) namespace, or belong in a particular type's 
 namespace.

This feature would seem to be in competition with type classes; could
you elaborate on the relative advantages and disadvantages?  The type
class story has the advantage of being well understood and quite
effective, but there are certainly some limitations too.

--KW 8-)

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread ozone
On 27/02/2004, at 3:47 AM, Keith Wansbrough wrote:

I've had an idea stewing in my head to do with per-type function
namespaces, that the current module namespace discussion reminded me
about.  The problem is that there is a limited namespace for 
functions,
so that if you define a new data type, it is unwise to call functions
which work on that data type a very generic name such as 'add'.
[..]
The idea that I've been throwing around is to be able to define a
separate namespace for each type; a function can either belong in a
global (default) namespace, or belong in a particular type's
namespace.
This feature would seem to be in competition with type classes; could
you elaborate on the relative advantages and disadvantages?  The type
class story has the advantage of being well understood and quite
effective, but there are certainly some limitations too.
I don't think type classes can solve the problem I'm trying to tackle.  
As an example of why, check out the types of FiniteMap and Set's 'add' 
functions:

addToFM :: Ord key = FiniteMap key elt - key - elt - FiniteMap key 
elt
addToSet :: Ord a = Set a - a - Set a

Note that the type of addToFM takes in two parameters (besides the 
FiniteMap itself): a key and an element, whereas the type of addToSet 
only takes in one parameter, which is the thing to add.  So, how can 
you come up with a type class which provides a polymorphic 'add' 
function, considering you don't even know how many parameters each data 
type's individual add function uses?

Even if you could define such a type class (which I don't think is 
possible), you then have one less function in the namespace to use, 
which is another problem.  For example, say I'm writing the 
Data.Complex module; there's a function in that module phase :: 
RealFloat a = Complex a - a.  So, how do you put this phase function 
into a type class?  Perhaps you could abstract away from the RealFloat 
and Complex bits, so you have a phase function which is generalised to 
work over a Num and an arbitrary data type instead; e.g. class Phase c 
where phase :: Num a = c a - a.  But what happens if, say, somebody 
adds a Moon data type, and they want to write a phase function which 
returns the phase of such a moon?  Phases of the moon certainly aren't 
Nums, nevermind the fact that you probably want to supply your moon 
phase's function with some sort of date as an extra parameter, which 
means the Phase type class isn't flexible enough.

Type classes are designed to provide a type-consistent interface to 
functions which perform different behaviour, unifying them as one 
function like + or == -- but it's designed to work for arbitrary types. 
 What I'm after is an interface for a function which may change 
depending on a primary type it's working with, which is almost the 
opposite to type classes.

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread Abraham Egnor
I think that this is a problem that can be solved with a simple convention
change, rather than a language extension - instead of appending type
names, I think it would be much better if modules simply used the short,
convenient, common names and expected the user to import them qualified
where overlap is a problem - in short, do exactly what DData does.  It's
slightly more verbose than OO-style: Map.add map key value instead of
map.add(key, value); but I don't think that what OO does is a good
language design target.

Another random thought: what you describe sounds awfully similar to
typeclasses, just with a single function in each typeclass.

Abe

[EMAIL PROTECTED] writes:
I've had an idea stewing in my head to do with per-type function 
namespaces, that the current module namespace discussion reminded me 
about.  The problem is that there is a limited namespace for functions, 
so that if you define a new data type, it is unwise to call functions 
which work on that data type a very generic name such as 'add'.  An 
example of this is Data.FiniteMap and Data.Set: both data types define 
a function to add things to their respective data types.

addToFM :: Ord key = FiniteMap key elt - key - elt - FiniteMap key 
elt
addToSet :: Ord a = Set a - a - Set a

So at the moment, many Haskellers will append the type name to the 
function to indicate that it only works on that particular data type.  
In this respect, Haskell is at a disadvantage vs most object-oriented 
languages, because in them, you can write x.add, and the type system 
will perform object-oriented polymorphism for you and call the 
correct add method, no matter if x is a FiniteMap or a Set.  Writing 
addToFM fm ... or addToSet set ... is surely a lot more 
inconvenient than writing fm.add or set.add, no?

The idea that I've been throwing around is to be able to define a 
separate namespace for each type; a function can either belong in a 
global (default) namespace, or belong in a particular type's 
namespace.  So, in the above example, instead of writing addToFM fm 
..., we could instead associate an 'add' function with the FiniteMap 
type, so we could write fm.add ... instead.  Provided that fm's type 
is monomorphic, it should be possible to call the 'correct' add 
function; if we defined another 'add' function that's associated with 
the Set type, that will only get called if the 'x' in x.add is of 
type :: Set.  So, like OO languages which inherently give separate 
namespaces to their different objects, here we give separate namespaces 
to different (monomorphic) types.  In this case, if one simply writes 
add instead of x.add, the compiler throws an error, because there 
is no 'add' function defined in the default namespace; add is only 
defined when a programmer writes x.add where x :: FiniteMap or x :: 
Set[1].

There are a number of means by which the x in x.add can be communicated 
to the actual function: it's similar to the hidden 'self' or 'this' 
variable that's present when you invoke a method on an object in OO.  
Perhaps x is passed to the function as its first parameter, or maybe it 
could be its last parameter, or even an arbitrary parameter (where the 
parameter it's passed as could be defined in the type signature of the 
function).  Perhaps 'self' or 'this' could be an implicit parameter.  
Any one of them will work just fine, I think.

However, this scheme is only for functions which have such a 'primary' 
data type to be associated with, such as FiniteMap or Set.  For 
functions which are truly polymorphic (such as ==), you still leave 
them in the default namespace.  Perhaps it's sensible to even make it a 
requirement that functions in the default namespace must be 
polymorphic: if they are monomorphic, they are associated with 
operating on a specific data type, so they should belong in a 
type-specific namespace.  You then still guarantee that such 
commonly-used polymorphic functions cannot be 'hijacked' to have stupid 
type signatures; i.e. == is always guaranteed to be :: Eq a - a - 
Bool.

Anyhow, feedback is more than welcome; I would certainly welcome this 
addition if it's feasible.  It feels inferior to be typing in 'addToFM 
foo' all the time when our OO brethren type the simpler and more 
succinct 'foo.add', especially given that Haskell's type system is far 
more powerful!

1. I haven't thought hard enough about whether it would be possible to 
have the same function name in both the 'default' namespace as well as 
in per-type namespaces, but my gut feeling says it should be OK.


-- 
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell




___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread ozone
On 27/02/2004, at 8:28 AM, Abraham Egnor wrote:

I think that this is a problem that can be solved with a simple 
convention
change, rather than a language extension - instead of appending type
names, I think it would be much better if modules simply used the 
short,
convenient, common names and expected the user to import them qualified
where overlap is a problem - in short, do exactly what DData does.  
It's
slightly more verbose than OO-style: Map.add map key value instead of
map.add(key, value); but I don't think that what OO does is a good
language design target.
This is exactly what was discussed in the thread before I barged in 
with per-type function namespaces, and it's not a good solution because 
of what Alastair has mentioned.  It's also not a good solution because 
I still have to type Map.add map instead of map.add: the type 
system already knows that map of type Map, so why should I have to 
qualify it even more by sticking a module name in front, and also 
encode the type name into my function because the module/namespace 
system isn't good enough to deal with this issue?

I also agree that what OO does is not a good language design target, 
but I do think that leverage type system to make programming nicer for 
you is a good design target :).  We're using a form of hungarian 
notation for function names, which is necessary because of a global 
namespace; OO people abolished this a long time ago.

Another random thought: what you describe sounds awfully similar to
typeclasses, just with a single function in each typeclass.
It's not the same as a single-function type class, for the reasons that 
I pointed out to Keith Wansbrough in an earlier email.

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread David Bergman
Mr. Ozone wrote: 

[snip]
 So at the moment, many Haskellers will append the type name to the 
 function to indicate that it only works on that particular data type.
 In this respect, Haskell is at a disadvantage vs most object-oriented 
 languages, because in them, you can write x.add, and the type system 
 will perform object-oriented polymorphism for you and call the 
 correct add method, no matter if x is a FiniteMap or a Set.  Writing 
 addToFM fm ... or addToSet set ... is surely a lot more 
 inconvenient than writing fm.add or set.add, no?

Yes. But, you are refering to overloading, no? And, not subtype polymorphism
(which is what I denote with object-oriented polymorphism)? Just to make
things clear in my mind.

 The idea that I've been throwing around is to be able to define a 
 separate namespace for each type; a function can either belong in a 
 global (default) namespace, or belong in a particular type's 
 namespace.  So, in the above example, instead of writing addToFM fm 
 ..., we could instead associate an 'add' function with the FiniteMap 
 type, so we could write fm.add ... instead.  Provided that fm's type 
 is monomorphic, it should be possible to call the 'correct' add 
 function; if we defined another 'add' function that's associated with 
 the Set type, that will only get called if the 'x' in x.add is of 
 type :: Set.  So, like OO languages which inherently give separate 
 namespaces to their different objects, here we give separate 
 namespaces to different
 (monomorphic) types.  In this case, if one simply writes add instead 
 of x.add, the compiler throws an error, because there is no 'add' 
 function defined in the default namespace; add is only defined when a 
 programmer writes x.add where x :: FiniteMap or x ::
 Set[1].

This overloading by namespace is usually called either ADL
(Argument-Dependent Lookup) or Koenig Lookup (especially in C++.)

So, you have thought of automatically, but implicitly, introduce a namespace
for each data type, and then have Haskell employ Koenig Lookup, to decide
which function an expression is refering to?

You realize, of course, that mere intranamespacial parameter type lookup
(regular overloading) would achieve the same effect, without the (implicit)
namespaces?

The core problem in Haskell is to bypass the generics, i.e., make sure that
a certain definition is used for a certain type, or combination of types.
This can only be done by class instances, as of now, but there have been
discussions of non-class overloading.

 There are a number of means by which the x in x.add can be 
 communicated to the actual function: it's similar to the hidden 'self' 
 or 'this'
 variable that's present when you invoke a method on an object in OO.  
 Perhaps x is passed to the function as its first parameter, or maybe 
 it could be its last parameter, or even an arbitrary parameter (where 
 the parameter it's passed as could be defined in the type signature of 
 the function).  Perhaps 'self' or 'this' could be an implicit 
 parameter.
 Any one of them will work just fine, I think.

Again, I think you are confusing the runtime dispatching subtype polymorpism
from overloading. Overloading would do what you want, while the subtype
polymorphism could (still) be handled by class, and instances of classes,
the Generic Programming way.
 
/David

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread David Bergman
Gabriel wrote: 

 | This overloading by namespace is usually called either ADL 
 | (Argument-Dependent Lookup) or Koenig Lookup (especially in C++.)
 
 Actually in C++, it is called argument dependent name 
 lookup, and that is the way the C++ definition text calls 
 it. As Andy Koenig has himself pointed out, he did not invent 
 that rule.  He mentionned it when the C++ committee was 
 solving a name look-up problem posed by namespaces to 
 operator functions.  That name look-up rule was later 
 generalized to non-operator to cover the function-call syntax 
 -- which is what is most known today and referred to above. 
 
 This ends my C++ hour on Haskell list :-)

Yeah! Get back to that dark corner where people solve real problems! ;-)

/David

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread Brandon Michael Moore
On Fri, 27 Feb 2004 [EMAIL PROTECTED] wrote:

 On 27/02/2004, at 1:13 PM, [EMAIL PROTECTED] wrote:

 1) now I have to manually declare a class definition for every single
 function, and I have to declare it in advance before any module defines
 that function (most serious problem; see below),

 2) I then have to declare instances of that type class for every
 function I define,

 3) the type signature for phase reveals no clues about how to use that
 function.

Declaring a type class instance is really no problem. You just need to
write an instance Class (Type) instead of function :: Type on the line
before the function declaration. The type on phase itself wouldn't
provide much information, but the list of instances in each module defines
would be informative. Something like :info wouldn't be much help without
modification.

 So unfortunately, this is hardly a scalable solution.  The entire
 reason I came up with the idea is because if we use type classes to
 implement this sort of overloading, we have to know every single
 possible function that any module author will ever create, and declare
 classes for those functions in advance.  This is fine if you're
 declaring truly polymorphic functions which are designed from the start
 to be totally general, but it is not designed for functions which may
 do vastly different things and may contain totally different type
 signatures, but share the same name because that would be a sensible
 thing to do.  (e.g. the phase function mentioned above.)

In the paper Object-Oriented Style Overloading for Haskell, Mark Shields
and Simon Peyton-Jones. One of the things they propose is adding method
constraints to the type system which (as far as I can tell) basically
amounts to generating a type class for each funtion name, and letting
you write constraints like (foo :: Int - Int) on your function.

They would set up the type classes like class Has_foo a where foo :: a,
which can causes problems if your argument and return value are
polymorphic under a class constraint rather than concrete types. Making
the method classes implicitly closed would probably help here. (closed
classes are another suggestion). While making that closed world assumption
it would probably be nice if it only selected between the versions of the
function that were actually in scope at the moment (so these would act
kind of like methods that overload if you import several of them, rather
than conflicting like normal).

As long as we are integrating these special type classes into the language
we can make sure things like error messages and ghci give decent
information, maybe listing all the different types the function is
imported at, and where each version is defined.

 With the per-type namespace separation I'm advocating, you do not need
 to know and declare in advance that each function will be overloaded,
 you simply write a FiniteMap.add function and a Set.add function, and
 you get a simpler form of namespace separation (or overloading) based
 on the first parameter that's passed to it.  It is a solution which is
 more _flexible_ than requiring type class definitions, and it is better
 than having hungarian notation for functions.  In fact, I think that,
 right now, if we replaced the current namespace separation offered by
 the hierarchical module system, and instead only had this sort of
 per-type namespace separation, things would still be better!

How much of the structure of the first paramater would you look at? Could
you an implementation for pairs that depended on the actual types in the
pair? I think you should try to take advantage of the existing type class
machinery as much as possible here, even if what you want are not exactly
(standard) type classes.

 I realise my idea isn't very general in that it only allows this
 namespace lookup/overloading based on the type of a single argument
 parameter, and I think it would be possible with a bit more thinking to
 generalise it to work based on multiple arguments (e.g. via
 argument-dependent lookup, or whatnot).  But even in its current form,
 I honestly think it offers far more flexibility and would lead to
 cleaner APIs than is currently possible.

Read the paper and see if you think something like that might be useful.
In any case, I think there's a decent chance that something useful for
this would also be useful for building interfaces to object-oriented
libraries, and vicea versa. I think there's probably something that covers
both cases nicely and uniformly.

Brandon

 --
 % Andre Pang : trust.in.love.to.save
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread ozone
On 27/02/2004, at 1:13 PM, [EMAIL PROTECTED] wrote:

For example, say I'm writing the Data.Complex module; there's a
function in that module phase :: RealFloat a = Complex a - a.  So,
how do you put this phase function into a type class?  Perhaps you
could abstract away from the RealFloat and Complex bits, so you have a
phase function which is generalised to work over a Num and an
arbitrary data type instead; e.g. class Phase c where phase :: Num a
= c a - a.  But what happens if, say, somebody adds a Moon data
type, and they want to write a phase function which returns the phase
of such a moon?  Phases of the moon certainly aren't Nums, nevermind
the fact that you probably want to supply your moon phase's function
with some sort of date as an extra parameter, which means the Phase
type class isn't flexible enough.
Here's the code that does exactly as you wish:

{-# OPTIONS -fglasgow-exts #-}

import qualified Complex

class Phase a b | a - b where
  phase:: a - b
instance (RealFloat a) = Phase (Complex.Complex a) a where
phase = Complex.phase
data MoonPhase = P1 | P2 | P3 | P4 deriving Show

instance Phase Int MoonPhase where
phase x = if x `mod` 4 == 0 then P1 else P4
instance Phase MoonPhase (Int-Int) where
phase P1 x = x
phase P2 x = x+1
main = do
putStrLn $ show $ phase ( (1.0::Float) Complex.:+ 
(1.0::Float))
	  putStrLn $ show $ phase (0::Int)
	  putStrLn $ show $ phase P1 (2::Int)
Very, very nice Oleg :).  I'm glad to know that we can achieve such 
things using the existing type class mechanisms already.  However, this 
still doesn't solve the problem, because:

1) now I have to manually declare a class definition for every single 
function, and I have to declare it in advance before any module defines 
that function (most serious problem; see below),

2) I then have to declare instances of that type class for every 
function I define,

3) the type signature for phase reveals no clues about how to use that 
function.

So unfortunately, this is hardly a scalable solution.  The entire 
reason I came up with the idea is because if we use type classes to 
implement this sort of overloading, we have to know every single 
possible function that any module author will ever create, and declare 
classes for those functions in advance.  This is fine if you're 
declaring truly polymorphic functions which are designed from the start 
to be totally general, but it is not designed for functions which may 
do vastly different things and may contain totally different type 
signatures, but share the same name because that would be a sensible 
thing to do.  (e.g. the phase function mentioned above.)

With the per-type namespace separation I'm advocating, you do not need 
to know and declare in advance that each function will be overloaded, 
you simply write a FiniteMap.add function and a Set.add function, and 
you get a simpler form of namespace separation (or overloading) based 
on the first parameter that's passed to it.  It is a solution which is 
more _flexible_ than requiring type class definitions, and it is better 
than having hungarian notation for functions.  In fact, I think that, 
right now, if we replaced the current namespace separation offered by 
the hierarchical module system, and instead only had this sort of 
per-type namespace separation, things would still be better!

I realise my idea isn't very general in that it only allows this 
namespace lookup/overloading based on the type of a single argument 
parameter, and I think it would be possible with a bit more thinking to 
generalise it to work based on multiple arguments (e.g. via 
argument-dependent lookup, or whatnot).  But even in its current form, 
I honestly think it offers far more flexibility and would lead to 
cleaner APIs than is currently possible.

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread oleg

Hello!

 So, how can you come up with a type class which provides a polymorphic
 'add' function, considering you don't even know how many parameters
 each data type's individual add function uses?

Very easily: every Haskell function takes only one
argument. Always. Ever.

 For example, say I'm writing the Data.Complex module; there's a
 function in that module phase :: RealFloat a = Complex a - a.  So,
 how do you put this phase function into a type class?  Perhaps you
 could abstract away from the RealFloat and Complex bits, so you have a
 phase function which is generalised to work over a Num and an
 arbitrary data type instead; e.g. class Phase c where phase :: Num a
 = c a - a.  But what happens if, say, somebody adds a Moon data
 type, and they want to write a phase function which returns the phase
 of such a moon?  Phases of the moon certainly aren't Nums, nevermind
 the fact that you probably want to supply your moon phase's function
 with some sort of date as an extra parameter, which means the Phase
 type class isn't flexible enough.

Here's the code that does exactly as you wish:

 {-# OPTIONS -fglasgow-exts #-}

 import qualified Complex 

 class Phase a b | a - b where
   phase:: a - b
 

 instance (RealFloat a) = Phase (Complex.Complex a) a where
 phase = Complex.phase
   
 data MoonPhase = P1 | P2 | P3 | P4 deriving Show

 instance Phase Int MoonPhase where
 phase x = if x `mod` 4 == 0 then P1 else P4
   
 instance Phase MoonPhase (Int-Int) where
 phase P1 x = x
 phase P2 x = x+1

 main = do
 putStrLn $ show $ phase ( (1.0::Float) Complex.:+ (1.0::Float))
 putStrLn $ show $ phase (0::Int)
 putStrLn $ show $ phase P1 (2::Int)

You can evaluate a phase of a complex number, get a phase of the moon
corresponding to some integer, and even convert a phase of the moon to
a time (given another integer as a reference time). Whereas the first
two functions take one argument, the latter phase takes two
arguments. The class Phase takes the classical first-argument
overloading. Other overloading schemes are possible (e.g., the ones
that overload based on the result -- something that C++ just can't do:
e.g., Read). If we need to evaluate phases of Saturn moons (and we
overload on the first argument), we can resolve the overloading using
newtype:

 newtype SaturnTime a = ST a
 instance Phase (SaturnTime Int) (Int - MoonPhase) where
phase x moon_index = P1

newtypes add no run-time overhead, and actually help in making the
code more explicit.

Regarding Koening lookup: as I read in DDJ, it's just a hack! First
the committee added the namespaces, and then realized that using
operators like  became hugely inconvenient. So Koening came up with
a hack. Shouldn't a language be designed in a more systematic way?

Speaking of the language design, November 2003 issue of Dr.Dobbs
J. has an interesting article: C++ Compilers and ISO Conformance [by
Brian A. Malloy, James F. Power and Tanton H. Gibbs, pp. 54-60].

Here's a summary. C++ standard has been ratified by the ISO Committee
in September 1998. There is no conformance suite however. So, we
cannot tell how well a particular compiler complies with a
standard. The authors of an article decided to create an approximate
conformance suite -- from the examples given in the standard
itself. It's a hard job -- the examples aren't meant to be a compiled
code, so some declarations and other pieces have to be filled in. The
result cannot be considered a truly compliance suite because not all
features of the language are illustrated in examples, and the
distribution of the examples is uneven. Nevertheless, it's a start.

The authors of the article have tested several compilers. The bottom
line -- after five years, no single compiler fully complies with the
standard. The best compiler, from the Edison Group (a three-person
company) fails only 2 tests. Intel's compiler fails three. Visual C++
7.1 from Microsoft fails 12. Gcc 3.3 fails 26. The latter number shows
that a wide community participation and OpenSource do not necessarily
lead to a better product. Gcc 3.3 is also one of the slowest
compilers.

But there is worse news for C++. C++ Language Standard consists of 776
pages, describing C++ language and the C++ core library. At present,
411 points in the C++ language part and 402 points in the library
part have been identified as questionable or outright erroneous. 93
language issues have been already acknowledged as errors. That is,
EVERY page of the standard, on average, contains some issue! The
committee obviously didn't bother to check their examples. Well, even
now there isn't a compiler that complies with the standard -- whatever
the compliance may mean.

Not only programmers don't know what some C++
rules mean. Not only compiler writers are puzzled. Even the committee
itself obviously doesn't know how _many_ features are supposed to
work. Can you imagine more shoddy work? 

Incidentally, here's one questionable example 

Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread Ketil Malde
[EMAIL PROTECTED] writes:

 addToFM :: Ord key = FiniteMap key elt - key - elt - FiniteMap key
 elt

 addToSet :: Ord a = Set a - a - Set a

 So, how can you come up with a type class which provides a
 polymorphic 'add' function, considering you don't even know how many
 parameters each data type's individual add function uses?

Why, by chea^H^H^Hurrying, of course:

class Collection a b | a - b where
add :: a - b - a

instance Collection Set a where
add = addToSet

instance Collection FiniteMap k e where
add fm (k,e) = addToFM fm k e

But I take your point, this could be hard to do in the general case.
E.g. 'delete' would probably only want a key.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell