Re: Unique Types in haskell (was Re: OO in Haskell)

1999-10-13 Thread Paul Hudak

I should clarify my comment:

> If Clean has faster arrays than monadic arrays in
> Haskell, it is probably due to other issues, such as laziness.

I did not mean to imply that Haskell directly supports monadic arrays. 
But it would be easy to add them in a library, and I believe one is
floating around somewhere, although it is not one of the Standard
Libraries...

  -Paul






Re: Unique Types in haskell (was Re: OO in Haskell)

1999-10-13 Thread Paul Hudak

> So maybe, as you say, uniqueness typing would be useful in Haskell.
> It seems to give Clean a speed advantage for number/array crunching at
> present (or so I've heard, though I must confess I've never tried it
> in either language).

Unique types do not provide any efficiency advantage over a monadic
approach to arrays or other mutable data structure.  Both approaches
allow one to express the single-threaded property needed to allow
in-place update, and thus this is not typically called an "optimzation"
since no analysis (other than type inference) is needed to enable it. 
More at issue is the style of program that results, and there are pros
and cons to this.  If Clean has faster arrays than monadic arrays in
Haskell, it is probably due to other issues, such as laziness.

A connection between linear types (the basis of unique types) and monads
can be found in the paper:
  http://www.cs.yale.edu/~hudak-paul/hudak-dir/popl97.ps

  -Paul






Re: Unique Types in haskell (was Re: OO in Haskell)

1999-10-13 Thread Adrian Hey

On Tue 12 Oct, Kevin Atkinson wrote:
> I have been meaning to bring this up for quite some time.  I think
> Haskell could really benefit from a uniqueness typing system as it would
> really simplify many things, such as fast array updates.

I have mixed feelings about uniqueness typing. The idea of unique values
seems a strange and unnatural to me. But it also seems essential if you're
going to treat IO as purely functional computation.

> Also it opens
> the door for TONES of optimization opportunities if the compiler can
> also mark standard types of being unique, even if the user did not. 
> Eventually the compiler could become so good at uniqueness identifying
> that the user will never have to explicitly mark anything as unique
> except in the case where its communication to the outside work.

My own feeling is that unless uniqueness typing is semantically necessary,
(as I understand it is in Clean) it should be kept out. But I can't see
any reason why Haskell compilers shouldn't exploit optimisations based on
uniqueness analysis. Ideally I would prefer to have the effeciency problem
fixed by designing better compilers instead of further complexification
of the type system.

However, I suspect that in practice a good programmer will be able to do
this better than compilers can for some time yet. This is really why C is
'faster' than Haskell (although code effeciency or lack of it is really a
property of compilers and programmers of course, not languages).
So maybe, as you say, uniqueness typing would be useful in Haskell.
It seems to give Clean a speed advantage for number/array crunching at
present (or so I've heard, though I must confess I've never tried it in
either language).

Regards
-- 
Adrian Hey







Re: OO in Haskell

1999-10-13 Thread Fergus Henderson

On 07-Oct-1999, Michael T. Richter <[EMAIL PROTECTED]> wrote:
> At 05:12 PM 10/7/99 , you wrote:
> > Sorry that I really can't explain well why I think that this concept
> > does not fit into Haskell. I must have heard that such "typecase"
> > is most often a bad design.
> 
> In most situations, type-casting is a symptom of bad design.  The only C++
> situation, for example, where some form of casting from a base class to a
> derived class isn't symptomatic of a bad design is the situation of the
> so-called "virtual constructor" -- building objects from a persistent
> store, say.  In most to all other situations, use of dynamic_cast or
> equivalent is just plain sucky design.

I have to say I disagree with that.

Firstly, the "virtual constructor" idiom, at least as this term is
commonly used, e.g. in the C++ FAQ list
,
does not involve any use of dynamic cast.  Nor should building objects
from a persistent store necessarily require any dynamic casts.

Secondly, there are many possible uses of `dynamic_cast' other than for
the "virtual constructor" idiom or for building objects from a
persistant store which would not constitute bad design in my book.
Among other things, `dynamic_cast' can be used to improve efficiency by
optionally taking advantage of operations which might not be present.
For example, you could use a `dynamic_cast' to check if some iostream
is a file, and if so, you can obtain the file descriptor and then try
using the OS's memory mapping facilities rather than reading it in byte
by byte.

Likewise `dynamic_cast' can also be used to improve properties other
than efficiency, for example user-friendliness.  Again the technique
involves taking advantages of certain operations, which might not be
present in all objects, in those cases where the operations _are_ present.
But the point is that this technique is not limited to improving
just efficiency.

Templates with traits classes are an alternative solution to the same
kind of problems.  That solution is becoming very popular in C++.
But it only works for homogenous collections or other situations where
the type is known at link time, and there are efficiency considerations
and modularity considerations that result from template code expansion
(templates in DLLs or shared libraries pose particular problems).
For heterogenous collections or other situations where the type will
only be known at runtime, if you want to apply these kinds of techniques,
then it is eminently reasonable to use `dynamic_cast'.

Note that `catch' in C++ involves the equivalent of `dynamic_cast'...
do you consider code using `catch' to be "just plain sucky design"?

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.






Unique Types in haskell (was Re: OO in Haskell)

1999-10-12 Thread Kevin Atkinson

Lars Lundgren wrote:
> 
> On Mon, 11 Oct 1999, Adrian Hey wrote:
> 
> > On Mon 11 Oct, Lars Lundgren wrote:
> > > I'm sure a lot of poeple have gotten this wrong. I would be surprised if
> > > not all the experienced haskellers has this view though.
> >
> > Probably so, but this view seems in complete contradiction to
> > that of the Clean world. So I'm still confused :-)
> >
> 
> I just took a glance at Clean. (Glanced through "The Ins and Outs of Clean
> I/O" by Peter Achten and Rinus Plasmeijer.) I think their solution with
> unique types is really neat.
> 
> One downside may be that they have made the type system more complex
> since it has to handle all the uniqness tags.
> 
> They deal with side effects (IO) by tagging the values with * and calling
> them unique. Haskell deals with side effects (IO) by using an abstract
> data type IO a which denotes an action [with clean type *World ->
> (a,*World) ]. In both cases, the compiler is notified that it is not ok to
> change order of evaluation.
> 
> In the Related work section, they mention Monadic IO and writes "To our
> knowledge combining monads of different type is a rather tedious task..."
> 
> I'm reluctant to say that I agree. I have written a few programs using
> monad transformers and while everything works in principle, it is, well -
> tedious...
> 
> I also do not like the tendency to put more things in the IO monad (I'm
> thinking about the extensions with IORef). I like stToIO better, but
> somehow it still feels like a hack. Maybe some library support for monad
> transformers and maybe even some syntactig sugar would do the trick.
> 
> They also wrote "[The monadic IO approach] over determines order of
> evaluation". I'm a bit puzzled about that statement. Is it true? Comments
> anyone?

I have been meaning to bring this up for quite some time.  I think
Haskell could really benefit from a uniqueness typing system as it would
really simplify many things, such as fast array updates.  Also it opens
the door for TONES of optimization opportunities if the compiler can
also mark standard types of being unique, even if the user did not. 
Eventually the compiler could become so good at uniqueness identifying
that the user will never have to explicitly mark anything as unique
except in the case where its communication to the outside work.  Ie IO
etc. Thus one can write non-destructive array updating programs that
would without an uniqueness type system be horribly inefficient (but
easy to verify as being correct) but with a uniqueness type system will
fast and easy to verify.  Can you ask for more?

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






Re: OO in Haskell

1999-10-11 Thread Adrian Hey

On Mon 11 Oct, Lars Lundgren wrote:
> They also wrote "[The monadic IO approach] over determines order of
> evaluation". I'm a bit puzzled about that statement. Is it true? Comments
> anyone?

I think (but could be wrong) that it was a reference to the the
multiple environments approach, where the world is conceptually composed
of independent sub-worlds which may be manipulated concurrently
but maintain deterministic behaviour.
e.g. a file is a sub-world which can be opened from the main world
something like this..
 fopen  :: String -> Int -> *World -> (Bool,*File,*World)
and closed..
 fclose :: *File -> *World -) (Bool,*World)

so in a 'let before' expression (a bit like haskell do)..
# (_,myfile,world) = fopen "myfile.txt" FWriteText world
  myfile   = do_something_to_file   myfile
  world= do_something_to_world  world
  (_,world)= fclose myfile world
  ..

do_something_to_file and do_something_to_world can be performed
concurrently, but we still have a deterministic program (assuming
the sub-worlds really are independent).

So, I think..
 Clean is good for deterministic concurrency.
 Haskell is good for deterministic sequentiality.
 Concurrent Haskell is good for non-deterministic concurrency.

Regards
-- 
Adrian Hey







Re: OO in Haskell

1999-10-11 Thread Lars Lundgren

On Mon, 11 Oct 1999, Adrian Hey wrote:

> On Mon 11 Oct, Lars Lundgren wrote:
> > I'm sure a lot of poeple have gotten this wrong. I would be surprised if
> > not all the experienced haskellers has this view though.
> 
> Probably so, but this view seems in complete contradiction to 
> that of the Clean world. So I'm still confused :-)
> 

I just took a glance at Clean. (Glanced through "The Ins and Outs of Clean
I/O" by Peter Achten and Rinus Plasmeijer.) I think their solution with
unique types is really neat. 

One downside may be that they have made the type system more complex
since it has to handle all the uniqness tags.

They deal with side effects (IO) by tagging the values with * and calling
them unique. Haskell deals with side effects (IO) by using an abstract
data type IO a which denotes an action [with clean type *World ->
(a,*World) ]. In both cases, the compiler is notified that it is not ok to
change order of evaluation.


In the Related work section, they mention Monadic IO and writes "To our
knowledge combining monads of different type is a rather tedious task..."

I'm reluctant to say that I agree. I have written a few programs using
monad transformers and while everything works in principle, it is, well -
tedious... 

I also do not like the tendency to put more things in the IO monad (I'm
thinking about the extensions with IORef). I like stToIO better, but
somehow it still feels like a hack. Maybe some library support for monad
transformers and maybe even some syntactig sugar would do the trick.

They also wrote "[The monadic IO approach] over determines order of
evaluation". I'm a bit puzzled about that statement. Is it true? Comments
anyone?

/Lars L









Re: OO in Haskell

1999-10-11 Thread Adrian Hey

On Mon 11 Oct, Lars Lundgren wrote:
> I'm sure a lot of poeple have gotten this wrong. I would be surprised if
> not all the experienced haskellers has this view though.

Probably so, but this view seems in complete contradiction to 
that of the Clean world. So I'm still confused :-)

Regards
-- 
Adrian Hey







Re: OO in Haskell

1999-10-11 Thread Lars Lundgren

On Fri, 8 Oct 1999, Adrian Hey wrote:

> On Fri 08 Oct, Lars Lundgren wrote:
> > A value (IO a) *denotes* a program possibly interacting with the world.
> > *That* program is of course not referentially transparent. A haskell
> > program generating an (IO a) on the other hand *is* referetially
> > transparent. 
> 
> So a value of type (IO a) is _not_ a function, if I understand you
> correctly.
> 

>From haskell point of view, it's a value, end of story. The value denotes
an action possibly doing IO. When this action is executed, it will
probably have side effects (thus, it is not a pure function), after all
thats the sole purpose of IO.

> I think this is really the correct interpretation, but I'm not sure
> if there's any real enthusiasm for this view in the FP community at
> large. (When I suggested a similar approach on another list it didn't
> seem to go down to well.)
> 

I'm sure a lot of poeple have gotten this wrong. I would be surprised if
not all the experienced haskellers has this view though.

> Also, the fact that the machine which executes values of type (IO a)
> is not regarded as part of Haskell is also not widely understood
> I think. (Well, at least I had not understood this before.)  
> 

I agree with this.

/Lars L







Re: OO in Haskell

1999-10-08 Thread Marcin 'Qrczak' Kowalczyk

Thu, 07 Oct 1999 19:13:34 -0400, Kevin Atkinson <[EMAIL PROTECTED]> pisze:

> One think I really think it needs is the ability to group a
> collection of functions with a tag.  And then when importing a
> module you can ask to only import that tag.  For example:
> 
> module A
>   list: head tail foldr foldl
>   array: index (!!) foldr foldl
> 
> ...
> 
> import A(list)

You could simply divide it into smaller modules, and maybe provide
a module that only reexports things from all the other modules for
people that prefer having everything in a single piece.

The problems could arise from mutual dependencies, which are not
handled well in current ghc. Also I am a bit worried about the
possibility of module name clashes.

> Also, Haskell currently allows you to explicitly import one module with
> another.  However, I think that this should be extended to be able to
> import part of the module for example:
> 
> module Mod1(module Mod2 hiding foo, module Mod3(foo))
> 
> and the like.

Doesn't suffice importing Mod2 hiding foo, so reexporting module Mod2
should export it without foo? You can qualify Mod2.foo if you want
to use it in Mod1. (I'm not sure if it in fact works this way.)

> Right now when ever a module uses a prelude function you have to
> import it like so:
> 
> import Prelude hiding head
> import Mod1
> 
> which can be VERY annoying when a module overrides a lot of the
> prelude functions.

It would be VERY dangerous if importing some module could hide names
from other modules without a piece of warning. And now you don't
have to hide it from Prelude if you can stand qualifying the name
everywhere. BTW, there should be a good reason to hide a well-known
name from Prelude, because people will be confused.

-- 
 __("+++$ UL++>$ P+++ L++>$ E-
  ^^W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP->+ t
QRCZAK  5? X- R tv-- b+>++ DI D- G+ e> h! r--%>++ y-







Re: OO in Haskell

1999-10-08 Thread Adrian Hey

On Fri 08 Oct, Lars Lundgren wrote:
> A value (IO a) *denotes* a program possibly interacting with the world.
> *That* program is of course not referentially transparent. A haskell
> program generating an (IO a) on the other hand *is* referetially
> transparent. 

So a value of type (IO a) is _not_ a function, if I understand you
correctly.

I think this is really the correct interpretation, but I'm not sure
if there's any real enthusiasm for this view in the FP community at
large. (When I suggested a similar approach on another list it didn't
seem to go down to well.)

Also, the fact that the machine which executes values of type (IO a)
is not regarded as part of Haskell is also not widely understood
I think. (Well, at least I had not understood this before.)  

Regards
-- 
Adrian Hey







Re: Referential Transparency (was Re: OO in Haskell)

1999-10-08 Thread Fergus Henderson

On 08-Oct-1999, Adrian Hey <[EMAIL PROTECTED]> wrote:
> I think it's important
> to understand whether or not we really do have referential transparency
> with monadic IO, if other models of interaction between program and
> outside world are (like those in Concurrent Haskell) going to be rejected
> because we 'lose referential transparency'.

The models of interaction between programs and the outside world
in Concurrent Haskell are not going to be rejected for that reason.

Some _other_ attempts to add concurrency to languages like Haskell
will be or have been rejected because the violated referential transparency,
and thus invalidated certain proofs or program transformations that one could
apply to programs.  But AFAIK Concurrent Haskell does not invalidate any
of those proofs or program transformations which we can apply to Haskell.

I haven't studied Concurrent Haskell in any great detail, so I could
well be wrong about that.  But the point is that invalidating existing
proofs or program transformations is (one of) the criteria we should
to decide whether to reject proposals for new features.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.






Re: Referential Transparency (was Re: OO in Haskell)

1999-10-08 Thread Fergus Henderson

On 08-Oct-1999, Adrian Hey <[EMAIL PROTECTED]> wrote:
> Reaction to my recent suggestion regarding IO (a concurrent non-deterministic
> machine) on the Clean discussion list was somewhat less than enthusiastic.
> One of the reasons was that apparently this would result in loss of
> referential transparency. (I never believed we had this anyway, so I
> didn't see this as a problem:-) Yet Concurrent Haskell is also based on a
> non-deterministic concurrent machine, with mutable variables shared
> by independent threads, but this preserves referential transparency?

Several previous concurrent extensions to Haskell did _not_ preserve
referential transparency, but Concurrent Haskell does, I believe.

Your suggestion on the Clean discussion list was quite vague, so perhaps
those who responded that it would result in a loss of referential transparency
were simply making a (pessimistic) assumption about what you meant,
thinking it would be like the concurrent extensions to Haskell that did
not preserve referential transparency.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.






Re: Referential Transparency (was Re: OO in Haskell)

1999-10-08 Thread Fergus Henderson

On 07-Oct-1999, Adrian Hey <[EMAIL PROTECTED]> wrote:
> This is another reason I'm sceptical about referential transparency in
> any functional system of IO (streams, monads, continuations, world as value..)
> It is hard to sensibly define interaction between a timeless universe
> of pure functions and values and a real universe which continually evolves
> in real time. A state transformer method is about as good as you'll
> get, but this requires that somehow the times of future events is
> information which is embedded in the whatever state the program last left
> the universe in. Perhaps some people believe this, but I don't think
> the world works this way. (And even if this were true, unless we had
> some systematic way of extracting this information and predicting the
> future, it won't help us at all.) 

Whether or not the world "really" works that way, the point is that we
can model it that way, and the world's behaviour matches the predictions
of our model.

Modelling it this way does help, even if we don't know the full contents
of the "StateOfUniverse" argument in any particular case,
because it allows us to apply mathematical reasoning to the behaviour
of our programs and their effects on the world.

When we say that something is _not_ referentially transparent, it means
that we can't reason about it directly using the usual techniques of
equational reasoning.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.






RE: OO in Haskell

1999-10-08 Thread R.S. Nikhil

> -Original Message-
> From: Lars Lundgren [mailto:[EMAIL PROTECTED]]
> Sent: Friday, October 08, 1999 3:45 AM
> To: Adrian Hey
> Cc: [EMAIL PROTECTED]
> Subject: Re: OO in Haskell
> 
> ...
> 
> I'm really confused about all the fuzz about The IO monad not 
> providing
> referential transparency. As I understand it, this is really simple.
> 
> A value (IO a) *denotes* a program possibly interacting with 
> the world.
> *That* program is of course not referentially transparent. A haskell
> program generating an (IO a) on the other hand *is* referetially
> transparent. 


Lars is exactly right-- this is the nub of the confusion
floating around.  People are confusing two distinct levels.

If you write a Haskell program that produces a Fortran
program, the Haskell program is referentially transparent (RF),
but the Fortran program (of course) is not.   When you use
the IO Monad, you have a Haskell program that is producing
an IO program.  The latter program happens to be interpreted
by the Haskell runtime system, but that is outside the scope
of Haskell semantics.

This also means that you should be clear about what
RF buys you, and what it doesn't buy you.  If
you have a Haskell program H that produces a Fortran
program F, then referential transparency is a powerful
tool that allows you to transform H into an equivalent Haskell
program H' (that may look very different), that produces
exactly the same Fortran program F.  But referential transparency
in Haskell will give you no help in producing another
Fortran program F' that is equivalent to F.  Getting
back to IO Monads, referential transparency in Haskell will
not help you in transforming a program that reads byte X and
then byte Y of a file into an equivalent program that reads
byte Y and then byte X.

Often, transforming the denoted imperative program is a far
more interesting and useful exercise than transforming the
Haskell program that denotes it.  And to do that, you have
to use the traditional reasoning models on imperative
programs.  There is no magic bullet here.

Nikhil






Re: Referential Transparency (was Re: OO in Haskell)

1999-10-08 Thread Fergus Henderson

On 07-Oct-1999, Adrian Hey <[EMAIL PROTECTED]> wrote:
> On Thu 07 Oct, Michael Hobbs wrote:
> > Michael Hobbs wrote:
> > > > Consider this:
> > > > > type IO a = StateOfUniverse -> (a, StateOfUniverse)
> > > > > -- Not syntactically correct, but you know what I mean.
> > > >
> > > > So anything that is declared, say `IO Int', means that it is actually a
> > > > function that reads in the state of the universe, potentially modifies
> > > > it, and then returns an Int value along with the new state of the
> > > > universe. The interesting thing to note is that the state of the
> > > > universe never changes between calls that are strung together using the
> > > > `>>=' operator. That is, the StateOfUniverse that is returned by the
> > > > first monad is exactly same state that is fed into the second. Whether
> > > > or not you want to call this "referentially transparent", well I guess
> > > > that's up to your own philosophic bias.
> > > 
> > > I rescind the statement that "the state of the universe never changes
> > > between calls that are strung together using the `>>=' operator". After
> > > further consideration, I believe that that's incorrect.

You can fix that by defining each primitive IO operation to
wait some unspecified amount of time (the amount of time being
determined by the StateOfUniverse argument passed) before
performing its action.

> > The problem is a function like `getChar' that is declared `IO Char'. If
> > the user has not typed a character when this monad is invoked, it will
> > sit and wait for the event. That is, the current StateOfUniverse that is
> > passed to getChar has absolutely nothing in it to indicate what
> > character will be returned, unless it also contains future events.

Fine, so let it contain future events, or at least sufficient information
to determine those future events.  What's the problem?

> > However, if we define `getChar' like this, we might get around the nasty
> > issue of future events:
> > > getChar = do
> > >   c <- peekKbdBuffer :: IO [Char]  -- length of 0 or 1
> > >   if null c then getChar else return head c
> > In this case, `getChar' will continue looping until StateOfUniverse
> > changes such that the keyboard buffer actually has a value in it. Of
> > course, this means that the StateOfUniverse must be able to alter itself
> > somehow between the function calls.

No, see above: each primitive IO operation, including `peekKbdBuffer',
waits some period of time.  So the StateOfUniverse returned from each
primitive IO operation is not going to be the same as the one that 
was passed, because the new state will include the side effects of
any concurrent processes or user input in that time.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.






Re: OO in Haskell

1999-10-08 Thread Fergus Henderson

On 07-Oct-1999, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote:
> Tue, 5 Oct 1999 14:10:26 -0400 (EDT), Kevin Atkinson <[EMAIL PROTECTED]> pisze:
> 
> > 1) Dynamic types.  You can't cast up.  That is you can't recover the
> > original type from an object in a existential collection.  You need to
> > use a dynamic type library for that.  And the library proved with hugs
> > and ghc leaves a lot to be desired.  In an OO langauge all classes
> > automatically cary dynamic typing information.
> 
> Please, no. Don't require existentials to carry dynamic type
> information.

Well, existentials need to carry dynamic type information for
debugging purposes anyway.  And they may need it for GC too (though
there are other techniques that work too, such as tagging all data with
a bit indicating whether it is a pointer or not, or using conservative
collection).  So from an implementation complexity or efficiency
perspective, your argument here is very weak, IMHO.

> IMHO it's as ugly as Dynamic.

IMHO the concept of Dynamic is not at all ugly, although certainly the
realization of this concept in Hugs/ghc has a number of flaws.

> The concept of existentials works well without it. The essence of
> existential is that you don't care what type is inside as long as it
> has the stated properties. If you need it, I think this is either
> wrong design (e.g. the operation that would use the cast should be
> put inside the existential as a method) or some more fundamental lack
> in the Haskell's type system. Don't break existentials.

This is a much better argument.  I agree that we should not break
the current properties of polymorphic types, such as the
"Theorems For Free".  But we can supply support for dynamic type
class casts which should satisfy Kevin Atkinson (and others of similar
inclinations) without breaking those properties, by using the
`Typeable' type class.

> If you like this, you must also like Dynamic, so simply require the
> type under the existential to be Typeable and cast it through Dynamic.
> The effect would be the same, without a penalty to those that don't
> use it.

I strongly agree that the type should be required to be an
instance of `Typeable' for dynamic type casting to be used.

But `Dynamic' does not provide sufficient functionality.
There needs to be some way of performing casts to polymorphic
types and to class-constrained polymorphic types.
That is not possible with the current `Dynamic' interface in
Hugs/ghc.

Perhaps you would like to comment on my recent proposal
posted to this list for a `class_cast' function?

Another important difference is that currently in Hugs/ghc you need
to write instance declarations for `Typeable' manually.

> Sorry that I really can't explain well why I think that this concept
> does not fit into Haskell. I must have heard that such "typecase"
> is most often a bad design.

Doing a typecase on individual types is often a bad design, because
the typecase will often need to be modified to deal with new types
that come along later.  But doing a dynamic cast to a class-constrained
type won't suffer from the same problem, in general.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.






Re: OO in Haskell

1999-10-08 Thread Lars Lundgren

On Thu, 7 Oct 1999, Adrian Hey wrote:

> On Thu 07 Oct, Manuel M. T. Chakravarty wrote:
> > Check out the type signatures of the `MVar'-related
> > operations and you will find that they are all nicely
> > encapsulated in the `IO' monad.  
> 
> This is true, but I think the point of contention is does the IO monad
> itself provide referential transparency. My opinion is that even thinking
> in such terms for IO is pretty meaningless. I am aware of various
> attempts to fix up the IO semantics with world models, but none of these
> accurately model the world. How could they?
> 
> So what difference does it make if you regard unpredictablity in the result
> of IO operations as caused by non-deterministic world models or Side
> Effect Goblins? Both theories seem equally valid, and both tell us
> very little about the nature or behaviour of the real world.
> 

I'm really confused about all the fuzz about The IO monad not providing
referential transparency. As I understand it, this is really simple.

A value (IO a) *denotes* a program possibly interacting with the world.
*That* program is of course not referentially transparent. A haskell
program generating an (IO a) on the other hand *is* referetially
transparent. 

This is analogous to a state monad that you yourself can create using the
subset of haskell that everybody agrees on preserving referential
transparency. You can see the operations you create on your state monad 
as a language embedded in haskell. A program in *that embedded language*
need not be referentially transparant, but that does not affect the
properties of haskell, the host language. So:

Of course the state monad - a construct in haskell - 
preserves referential transparency.

Of course the IO monad - a construct in haskell -
preserves referential transparency. 


One could question whether or not haskell preserves referential
transparency. The reason for this is that when you compile and execute a
haskell program, it does not only evaluate to an IO value - *The program
that the value denotes is actually executed* sort of automagically. 


/Lars L








Re: Referential Transparency (was Re: OO in Haskell)

1999-10-08 Thread Adrian Hey

On Fri 08 Oct, Fergus Henderson wrote:
> > It is hard to sensibly define interaction between a timeless universe
> > of pure functions and values and a real universe which continually evolves
> > in real time. A state transformer method is about as good as you'll
> > get, but this requires that somehow the times of future events is
> > information which is embedded in the whatever state the program last left
> > the universe in. Perhaps some people believe this, but I don't think
> > the world works this way. (And even if this were true, unless we had
> > some systematic way of extracting this information and predicting the
> > future, it won't help us at all.) 

> Whether or not the world "really" works that way, the point is that we
> can model it that way, and the world's behaviour matches the predictions
> of our model.

But unless the model is exact in _every_ detail, there will be discrepencies
between the observations of the behaviour of the model and those of reality.
 How do you account for these discrepencies?
 Who decides if they are significant or not?
 Why is imprecise specification of these models tolerable for IO but
 not for other parts of a Haskell program?
 
> When we say that something is _not_ referentially transparent, it means
> that we can't reason about it directly using the usual techniques of
> equational reasoning.

Yes, I agree with this, but as a consequence I would say that in general
we don't have referential transparency with IO. (Though we may have it
for a few systems which can be modelled exactly.)  
 
> Several previous concurrent extensions to Haskell did _not_ preserve
> referential transparency, but Concurrent Haskell does, I believe.
 
That wasn't my impression when I read the paper, but maybe I misunderstood.

> Your suggestion on the Clean discussion list was quite vague, so perhaps
> those who responded that it would result in a loss of referential transparency
> were simply making a (pessimistic) assumption about what you meant,
> thinking it would be like the concurrent extensions to Haskell that did
> not preserve referential transparency.

Well I won't elaborate that proposal any more, other than I consider it
to be essentially the same as Concurrent Haskell (as described in the
Concurrent Haskell paper), except that with concurrency as the norm
forks would be implicit whereas in Concurrent Haskell they would have
to be explicit. So anything that is or isn't true about Concurrent Haskell
would also be true (or not) about that proposal.

And yes, we wouldn't have referential transparency with regard to the
interactions of Actions with the outside world. That's why they're
Actions, not functions. But in all other respects (I.E. anything not
related to IO) the language would have been every bit as functional
as Concurrent Haskell is (or isn't). (E.G. It's impossible for
a function to invoke an action, only actions can invoke actions.)

> > I think it's important
> > to understand whether or not we really do have referential transparency
> > with monadic IO, if other models of interaction between program and
> > outside world are (like those in Concurrent Haskell) going to be rejected
> > because we 'lose referential transparency'.
> 
> The models of interaction between programs and the outside world
> in Concurrent Haskell are not going to be rejected for that reason.

Are you sure about that? I get the impression that Concurrent Haskell
is regarded very much as 'fringe Haskell'. It rarely gets a mention on
this list (in fact I cannot recall a single post re. it).
 
> Some _other_ attempts to add concurrency to languages like Haskell
> will be or have been rejected because the violated referential transparency,
> and thus invalidated certain proofs or program transformations that one could
> apply to programs.

I think that if invalidating some transformations regarding IO 'functions'
is the price to be paid for providing a language with what we need to 
write real programs, then that's OK. I don't recall anybody rejecting
non-strict semantics because it invalidated a && b = b && a :-)

But I would agree that we don't want to do anything that turns functions
into notfunctions. That's really why I kept insisting that actions
_weren't_ functions (although everyone else seems to think they are, for
reasons I'm still unable to fathom.)

Regards
-- 
Adrian Hey







Re: Referential Transparency (was Re: OO in Haskell)

1999-10-08 Thread Adrian Hey

Hello again Fergus,

For some reason you have sent this message to me despite the fact that
all the words you appear to disagree with are those of Michael Hobbs:-)

However, I assume you also disagree with my words so I'll try to respond.
Unfortunately we've been over this ground before on another list so I
doubt we'll see eye to eye, but here goes anyway..

> > > The problem is a function like `getChar' that is declared `IO Char'. If
> > > the user has not typed a character when this monad is invoked, it will
> > > sit and wait for the event. That is, the current StateOfUniverse that is
> > > passed to getChar has absolutely nothing in it to indicate what
> > > character will be returned, unless it also contains future events.
> 
> Fine, so let it contain future events, or at least sufficient information
> to determine those future events.  What's the problem?

Apart from the fact that this just isn't reality, no problem at all :-)

I also object to this argument because I don't think it's sufficient
that the state of the universe contains sufficient information to
determine those future events. If we are to legitimise our claim that
the behaviour of the universe is deterministic and computable then I think
we also need a function which can observe the current state of the universe
and predict all future events.

Of course this function also needs to account for the effect of it's
own observations. But that shouldn't be a problem, because we can always
use Haskell to model it if necessary. Thats why monadic IO is purely
functional and referential transparency is guaranteed. Right? 

Otherwise I can see no difference in the predictive power of a deterministic
(but indeterminable) model of the universe and one which simply says the
results of IO actions may be subject to unknown side effects.

So aren't we just really arguing about words, not facts?
 
Regards 
-- 
Adrian Hey







Referential Transparency (was Re: OO in Haskell)

1999-10-08 Thread Adrian Hey

On Thu 07 Oct, I wrote:
> On Wed 06 Oct, Johan Nordlander wrote:
> > Just to avoid any unfortunate misconceptions: O'Haskell definitely
> > preserves the property we commonly refer to as referential transparency,
> > and so does Concurrent Haskell, or any other sound monadic extension of
> > the language.
> 
> Hmm, I obviously don't understand what 'referential transparency' means.
> I must say I'm puzzled by statements like this. If the presence of
> mutable variables (and MVars in Concurrent Haskell) preserve referential
> transparency, then why _don't_ we have referential transparency in C?
> 
> Does it have something to do with denotational semantics and world
> models containing infinite trees of random numbers?

On Wed 06 Oct, Johan Nordlander replied:
> I'd say that an absolutely brilliant exposition of this topic is to be 
> found in Phil Wadler's paper "How to declare an imperative", available 
> on the web at
>
>  http://www.cs.bell-labs.com/who/wadler/topics/monads.html

I've read this paper, and it is good, but I still see no reason to 
change my opinion regarding referential transparency and IO.
But I am terribly confused about this issue, there seems to be no real
consensus about this in the FP world. I just can't see how if the
result of an action is dependent on unknown external world agents
(as it is with the IO monad) it could be described as referentially
transparent. I can accept that we have referential transparency for
user defined monads, but not the IO monad.   

Reaction to my recent suggestion regarding IO (a concurrent non-deterministic
machine) on the Clean discussion list was somewhat less than enthusiastic.
One of the reasons was that apparently this would result in loss of
referential transparency. (I never believed we had this anyway, so I
didn't see this as a problem:-) Yet Concurrent Haskell is also based on a
non-deterministic concurrent machine, with mutable variables shared
by independent threads, but this preserves referential transparency?

Unless I'm missing something, these two views are not consistent :-(

Regards
-- 
Adrian Hey







Re: Referential Transparency (was Re: OO in Haskell)

1999-10-08 Thread Adrian Hey

On Thu 07 Oct, Jan Skibinski wrote:
> I think that the monadic IO provides us with such a
> simplification. As long as we realize what are its limitations
> and as long as we stay within reasonable limits of the concept
> we should be fine here. The operative word here is "realize".
> Do we really know those limitations? 

Yes, I agree. As a pragmatic aproach to simple imperative IO I'm
content with IO monads and I don't really care if we have referential
transparency or not, just so long as I can do IO.

But, single threaded monadic IO is very restrictive. I think it's important
to understand whether or not we really do have referential transparency
with monadic IO, if other models of interaction between program and
outside world are (like those in Concurrent Haskell) going to be rejected
because we 'lose referential transparency'.

If we lose something we never had, then what's the problem I wonder?

Regards
-- 
Adrian Hey








Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Adrian Hey

On Thu 07 Oct, Joe English wrote:
> The way I understand the term "referntially transparent",
> it means that if you have
> 
> let x = y in z
> 
> then you can substitute all free occurrences of 'x' in 'z'
> with 'y', or vice versa, without changing the meaning of
> the expression.  This is true in Haskell even if 'y' has
> type 'IO a'.  (For example, "the action which, when performed,
> returns the contents of the file /var/log/messages" always
> _means_ the same thing, even though it may _do_ different things
> each time it's performed.)

As you say, I think the problem is predictability of the results of
_invoking_ actions. I'm quite happy with the idea of an action as a
value which does not damage referential transparency if it appears
in an expression.

Regards
-- 
Adrian Hey







Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Adrian Hey

On Thu 07 Oct, Marcin 'Qrczak' Kowalczyk wrote:
> In Haskell a `variable' can be meant to be either a name introduced
> by a let/where/lambda/case binding, or one of IORef/STRef/MVar (or
> even something in a custom monad). The first concept is referentially
> transparent, the second is not if we think about the contents of
> *Refs/MVars as `values of variables' and thus usages from different
> (>>=)-separated segments in the relevant monad.
> 
> (I'm not sure whether I understand the referential transparency issue
> correctly at all, sorry if it's all wrong.)

I agree with you. I think as far as this discussion is concerned
its the monadic mutable variables which are problematic.
 
> > I can accept that we have referential transparency for user defined
> > monads, but not the IO monad.
> 
> It is satisfied for both or for neither, depending on from what side
> we look at them and how we assign names to concepts.

I would opt for the 'both' option, _provided_ the world which the IO
monad is interacting with is closed, finite and deterministic. If this
is true we should be able to develop a model the world as a Haskell data
type and associated functions which reproduce the observable properties
of the world exactly, in every detail. For example, that world could
be a dedicated hardware array processor which interacted with nothing but
the Haskell program. In such cases I would aggree that computation by
IO monad is just another form of purely functional computation, with
referential transparency intact.

Unfortunately, we can't do this for the real world. So I'm still
sceptical about IO monads.  

Regards
-- 
Adrian Hey







Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Adrian Hey

On Thu 07 Oct, Michael Hobbs wrote:
> Michael Hobbs wrote:
> > > Consider this:
> > > > type IO a = StateOfUniverse -> (a, StateOfUniverse)
> > > > -- Not syntactically correct, but you know what I mean.
> > >
> > > So anything that is declared, say `IO Int', means that it is actually a
> > > function that reads in the state of the universe, potentially modifies
> > > it, and then returns an Int value along with the new state of the
> > > universe. The interesting thing to note is that the state of the
> > > universe never changes between calls that are strung together using the
> > > `>>=' operator. That is, the StateOfUniverse that is returned by the
> > > first monad is exactly same state that is fed into the second. Whether
> > > or not you want to call this "referentially transparent", well I guess
> > > that's up to your own philosophic bias.
> > 
> > I rescind the statement that "the state of the universe never changes
> > between calls that are strung together using the `>>=' operator". After
> > further consideration, I believe that that's incorrect.
> 
> Unless, of course, you consider StateOfUniverse to encapsulate all past,
> present, and future events (a 4-dimensional value). In which case, you
> don't need to return a new StateOfUniverse, since it will be exactly the
> same as the one given, except maybe with different `currentTime' value.
> But I'm getting way too deep here.
> 
> The problem is a function like `getChar' that is declared `IO Char'. If
> the user has not typed a character when this monad is invoked, it will
> sit and wait for the event. That is, the current StateOfUniverse that is
> passed to getChar has absolutely nothing in it to indicate what
> character will be returned, unless it also contains future events.
> 
> However, if we define `getChar' like this, we might get around the nasty
> issue of future events:
> > getChar = do
> >   c <- peekKbdBuffer :: IO [Char]  -- length of 0 or 1
> >   if null c then getChar else return head c
> In this case, `getChar' will continue looping until StateOfUniverse
> changes such that the keyboard buffer actually has a value in it. Of
> course, this means that the StateOfUniverse must be able to alter itself
> somehow between the function calls.

This is another reason I'm sceptical about referential transparency in
any functional system of IO (streams, monads, continuations, world as value..)
It is hard to sensibly define interaction between a timeless universe
of pure functions and values and a real universe which continually evolves
in real time. A state transformer method is about as good as you'll
get, but this requires that somehow the times of future events is
information which is embedded in the whatever state the program last left
the universe in. Perhaps some people believe this, but I don't think
the world works this way. (And even if this were true, unless we had
some systematic way of extracting this information and predicting the
future, it won't help us at all.) 

Regards
-- 
Adrian Hey







Re: OO in Haskell

1999-10-07 Thread Adrian Hey

On Thu 07 Oct, Manuel M. T. Chakravarty wrote:
> Check out the type signatures of the `MVar'-related
> operations and you will find that they are all nicely
> encapsulated in the `IO' monad.  

This is true, but I think the point of contention is does the IO monad
itself provide referential transparency. My opinion is that even thinking
in such terms for IO is pretty meaningless. I am aware of various
attempts to fix up the IO semantics with world models, but none of these
accurately model the world. How could they?

So what difference does it make if you regard unpredictablity in the result
of IO operations as caused by non-deterministic world models or Side
Effect Goblins? Both theories seem equally valid, and both tell us
very little about the nature or behaviour of the real world.

Regards
-- 
Adrian Hey







Re: OO in Haskell

1999-10-07 Thread Marcin 'Qrczak' Kowalczyk

Tue, 5 Oct 1999 14:10:26 -0400 (EDT), Kevin Atkinson <[EMAIL PROTECTED]> pisze:

> 1) Dynamic types.  You can't cast up.  That is you can't recover the
> original type from an object in a existential collection.  You need to
> use a dynamic type library for that.  And the library proved with hugs
> and ghc leaves a lot to be desired.  In an OO langauge all classes
> automatically cary dynamic typing information.

Please, no. Don't require existentials to carry dynamic type
information. IMHO it's as ugly as Dynamic.

The concept of existentials works well without it. The essence of
existential is that you don't care what type is inside as long as it
has the stated properties. If you need it, I think this is either
wrong design (e.g. the operation that would use the cast should be
put inside the existential as a method) or some more fundamental lack
in the Haskell's type system. Don't break existentials.

If you like this, you must also like Dynamic, so simply require the
type under the existential to be Typeable and cast it through Dynamic.
The effect would be the same, without a penalty to those that don't
use it.

In simple cases where the set of types that need to be casted is
fixed, there can be methods returning `Maybe ACastedType', with
obvious semantics.

Sorry that I really can't explain well why I think that this concept
does not fit into Haskell. I must have heard that such "typecase"
is most often a bad design.

> 2) More specific types, you can't _easilly_ call the more general type.
> For example in OO this is very commen:
> 
> class Base
>   virtual foo()
> do stuff
> 
> class Derived, extends Base
>   foo()
> call Base::foo()
> doo stuff

Yes, subtyping is an interesting issue that Haskell lacks that *may* be
good. It is not obvious however, what exactly it could mean in Haskell.

IMHO it is not as useful as in some imperative languages. In C++ or
Java you typically have methods mutating objects, where in functional
languages you have functions returning new objects. Analogous to
methods Base::foo(int) and Derived::foo(int) are functions of types
`Base -> Int -> Base' and `Derived -> Int -> Derived'. Here their
signatures differ not only on the first argument, as in imperative OO,
but also on the result. So you cannot say that the second function
is simply the first one specialized to the case of Derived.

They may however be methods of type `a -> Int -> a' in some class,
that is, where types are instances of an interface, not the other
type - because you don't have "values of type AHaskellClass" which
could be passed through such a function yielding another "value of
type AHaskellClass". Instead the types of argument and result are
constrained to be the same at the place of the usage, no matter what
the actual type is. In other words, it's good that Haskell makes
a difference between an interface and a concrete type, and in a
functional language instances of an interface make more sense than
instances of a type (i.e. subtypes).

It is also more general in the way that there may be more than
one argument of the "self" type (as (==) in Eq), or none (as pi
in Floating). Type inference makes the latter case convenient.

> 3) Encapsulation.  You can't have private and protected members.  Some
> of this can be done using modules.  However it is more work.

Please, no. C++'s friends are symptoms that this does not work well.
This belongs to the module system.

Functions does not "belong" to the type of objects they act on, which
is obvious when we consider functions working symmetrically on more
than one argument: which does it belong to? And what about constants:
in what sense does the emptySet belong to a Set type? I have never
accepted the OO way, where the first argument is distinguished as
the owner.

When thinking about whether the implementation details of something are
known to a function, it should be obvious that they are "more known"
to a function in the same file acting on different types than to some
function defined in other file, even acting on the same type.

Haskell's modules, unlike Pascal's, can reexport entities imported
from other modules, so there may be views of a family of entities
with various levels of visibility of the inner details.

> 4) Cleaner more natural syntax.

I know no other language that has cleaner and more natural syntax
than Haskell :-)

In particular I dislike typical OO syntax: object.method(args).
It's good that Haskell makes field selection functions look like
normal functions, because they _are_ normal functions that could be
defined elsewhere. Or else you could argue that fst and head should
look like pair.fst and list.head. Please, no.

*   *   *

I have escaped from the way to OO because I don't believe it is as
good as many people claim. Haskell designed surprisingly many things
in the way that I either have thought about before and liked (elegant
design, strong typing, parametric polymorphism, types 

Re: OO in Haskell

1999-10-07 Thread Kevin Atkinson

Marcin 'Qrczak' Kowalczyk wrote:
> 
> Tue, 5 Oct 1999 14:10:26 -0400 (EDT), Kevin Atkinson <[EMAIL PROTECTED]> pisze:
> 
> > 1) Dynamic types.  You can't cast up.  That is you can't recover the
> > original type from an object in a existential collection.  You need to
> > use a dynamic type library for that.  And the library proved with hugs
> > and ghc leaves a lot to be desired.  In an OO langauge all classes
> > automatically cary dynamic typing information.
> 
> Please, no. Don't require existentials to carry dynamic type
> information. IMHO it's as ugly as Dynamic.
> 

The types won't be required to carry dynamic type information.  It will
just be there if you need it.  It there will be a special function or
the like you can call to get information about the original object.  If
you don't won't to use it, you don't have to and you will NEVER know its
there.  Also if none of the code uses dynamic typing the compile will be
able to optimize away the dynamic type information.

> The concept of existentials works well without it. The essence of
> existential is that you don't care what type is inside as long as it
> has the stated properties. If you need it, I think this is either
> wrong design (e.g. the operation that would use the cast should be
> put inside the existential as a method) or some more fundamental lack
> in the Haskell's type system. Don't break existentials.
> 
> If you like this, you must also like Dynamic, so simply require the
> type under the existential to be Typeable and cast it through Dynamic.
> The effect would be the same, without a penalty to those that don't
> use it.
> 
> In simple cases where the set of types that need to be casted is
> fixed, there can be methods returning `Maybe ACastedType', with
> obvious semantics.
> 
> Sorry that I really can't explain well why I think that this concept
> does not fit into Haskell. I must have heard that such "typecase"
> is most often a bad design.
> 

I am not going to argue with you here but there are times where some
casting is unavoidable and I think haskell should provide a safe clean
way of allowing it and the Dynamic type library is not it.

> > 3) Encapsulation.  You can't have private and protected members.  Some
> > of this can be done using modules.  However it is more work.
> 
> Please, no. C++'s friends are symptoms that this does not work well.
> This belongs to the module system.
> 
> Functions does not "belong" to the type of objects they act on, which
> is obvious when we consider functions working symmetrically on more
> than one argument: which does it belong to? And what about constants:
> in what sense does the emptySet belong to a Set type? I have never
> accepted the OO way, where the first argument is distinguished as
> the owner.
> 
> When thinking about whether the implementation details of something are
> known to a function, it should be obvious that they are "more known"
> to a function in the same file acting on different types than to some
> function defined in other file, even acting on the same type.
> 
> Haskell's modules, unlike Pascal's, can reexport entities imported
> from other modules, so there may be views of a family of entities
> with various levels of visibility of the inner details.

Perhaps.  However I have also think Haskell's module system is a bit to
simple.  One think I really think it needs is the ability to group a
collection of functions with a tag.  And then when importing a module
you can ask to only import that tag.  For example:

module A
  list: head tail foldr foldl
  array: index (!!) foldr foldl

...

import A(list)

which will make using modules a LOT more convent.  

Also, Haskell currently allows you to explicitly import one module with
another.  However, I think that this should be extended to be able to
import part of the module for example:

module Mod1(module Mod2 hiding foo, module Mod3(foo))

and the like.  Right now when ever a module uses a prelude function you
have to import it like so:

import Prelude hiding head
import Mod1

which can be VERY annoying when a module overrides a lot of the prelude
functions.

> 
> > 4) Cleaner more natural syntax.
> 
> I know no other language that has cleaner and more natural syntax
> than Haskell :-)
> 
> In particular I dislike typical OO syntax: object.method(args).
> It's good that Haskell makes field selection functions look like
> normal functions, because they _are_ normal functions that could be
> defined elsewhere. Or else you could argue that fst and head should
> look like pair.fst and list.head. Please, no.

I guess its a matter of personal taste.


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






Re: OO in Haskell

1999-10-07 Thread Michael T. Richter

At 05:12 PM 10/7/99 , you wrote:
> Sorry that I really can't explain well why I think that this concept
> does not fit into Haskell. I must have heard that such "typecase"
> is most often a bad design.

In most situations, type-casting is a symptom of bad design.  The only C++
situation, for example, where some form of casting from a base class to a
derived class isn't symptomatic of a bad design is the situation of the
so-called "virtual constructor" -- building objects from a persistent
store, say.  In most to all other situations, use of dynamic_cast or
equivalent is just plain sucky design.

I don't know enough about Haskell's type system yet to form an opinion if
there is any point where such casts are necessary as opposed to being
merely expedient.  Haskell's type system is... well, I guess "quirky" and
"complex" leap to mind immediately.  I'm sure that at some point I will
grok it and will either go "Aha!" or "Ew!".  Until then I'll reserve opinions.

> Functions does not "belong" to the type of objects they act on, which
> is obvious when we consider functions working symmetrically on more
> than one argument: which does it belong to? And what about constants:
> in what sense does the emptySet belong to a Set type? I have never
> accepted the OO way, where the first argument is distinguished as
> the owner.

But this isn't "the" OO way.  It is "an" OO way.  Dylan, for example,
doesn't make any particular argument on a method as the "owner".

--
Michael T. Richter<[EMAIL PROTECTED]>http://www.igs.net/~mtr/
  PGP Key: http://www.igs.net/~mtr/pgp-key.html
PGP Fingerprint: 40D1 33E0 F70B 6BB5 8353 4669 B4CC DD09 04ED 4FE8 






Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Marcin 'Qrczak' Kowalczyk

Fri, 8 Oct 1999 01:22:43 +0100 (BST), Adrian Hey <[EMAIL PROTECTED]> pisze:

> I've read this paper, and it is good, but I still see no reason
> to change my opinion regarding referential transparency and IO.
> But I am terribly confused about this issue, there seems to be
> no real consensus about this in the FP world. I just can't see
> how if the result of an action is dependent on unknown external
> world agents (as it is with the IO monad) it could be described as
> referentially transparent.

I think that referential transparency simply depends on what entities
in the language we call `variables' and what methods of their usage
we call `referencing'.

Since languages can be very different and their concepts are not
mapped one-to-one between languages, there is no universal definition
of referential transparency that can be unambiguously applied to
any language.

In Haskell a `variable' can be meant to be either a name introduced
by a let/where/lambda/case binding, or one of IORef/STRef/MVar (or
even something in a custom monad). The first concept is referentially
transparent, the second is not if we think about the contents of
*Refs/MVars as `values of variables' and thus usages from different
(>>=)-separated segments in the relevant monad.

(I'm not sure whether I understand the referential transparency issue
correctly at all, sorry if it's all wrong.)

In other words, implementing an interpreter of a non-referentially
transparent language in the referentially transparent language does
not change the answer for the implementing language, because we start
talking about different concepts.

Similarly, matrices can be comutative or not, depending on whether
we talk about their addition or multiplication.

> I can accept that we have referential transparency for user defined
> monads, but not the IO monad.

It is satisfied for both or for neither, depending on from what side
we look at them and how we assign names to concepts.

-- 
 __("+++$ UL++>$ P+++ L++>$ E-
  ^^W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP->+ t
QRCZAK  5? X- R tv-- b+>++ DI D- G+ e> h! r--%>++ y-







Re: OO in Haskell

1999-10-07 Thread trb

Adrian Hey writes:
 > On Wed 06 Oct, Johan Nordlander wrote:
 > > Just to avoid any unfortunate misconceptions: O'Haskell definitely
 > > preserves the property we commonly refer to as referential transparency,
 > > and so does Concurrent Haskell, or any other sound monadic extension of
 > > the language.
 > 
 > Hmm, I obviously don't understand what 'referential transparency' means.
 > I must say I'm puzzled by statements like this. If the presence of
 > mutable variables (and MVars in Concurrent Haskell) preserve referential
 > transparency, then why _don't_ we have referential transparency in C?

I'm not surprised you are puzzled. Concurrent Haskell, as implemented in ghc,
does NOT preserve referential transparency, nor could it. The whole point of
multi-threading is to be able to respond asynchronously to events i.e. the
relative order of events in one thread versus another thread is undefined - if
the order were defined the program would be single-threaded. Take that together
with the ability to perform side-effects e.g. I/O or mutable state, and it is
clear that the results produced by the program will in general depend on the
particular relative order of events between threads, rather than on the
declarative semantics alone.

It is possible to achieve some of the effects of multi-threading using lazy
evaluation of stream processors - this approach does not violate referential
transparency, and is used in the Fudgets GUI (Haggis uses concurrent Haskell).
I ran some Haggis programs in the days before it rotted, and it performed
well. I haven't run Fudgets programs, but got the impression from the
documentation that the stream processors would not always provide as much
responsiveness as could be wished for.

Tim






Re: OO in Haskell

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

<[EMAIL PROTECTED]> wrote,

> Adrian Hey writes:
>  > On Wed 06 Oct, Johan Nordlander wrote:
>  > > Just to avoid any unfortunate misconceptions: O'Haskell definitely
>  > > preserves the property we commonly refer to as referential transparency,
>  > > and so does Concurrent Haskell, or any other sound monadic extension of
>  > > the language.
>  > 
>  > Hmm, I obviously don't understand what 'referential transparency' means.
>  > I must say I'm puzzled by statements like this. If the presence of
>  > mutable variables (and MVars in Concurrent Haskell) preserve referential
>  > transparency, then why _don't_ we have referential transparency in C?
> 
> I'm not surprised you are puzzled. Concurrent Haskell, as
> implemented in ghc, does NOT preserve referential
> transparency, nor could it. 

Of course it does!  If it wouldn't many of the optimisations
performed by GHC would be invalid and you would be doomed if
you compiled a Concurrent Haskell module with -O (actually,
you would most certainly already be doomed without -O).

Check out the type signatures of the `MVar'-related
operations and you will find that they are all nicely
encapsulated in the `IO' monad.  

Manuel

PS: We don't have referential transparency in C, because K&R 
didn't know Phil Wadler ;-)






Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Jan Skibinski


Here are some comments about the prevailing view that the
concept of the World or the Universe is safe to use in
any kind of arguments related to referential transparency.
I would be quite cautious here. I am not an expert on
these issues in relation to FP, but I have seen enough
tough examples in physics that make me a bit sceptical here.
I am not fighting the concept itself, but I would like
to see it well described first to know exactly the limits
of its applicability. 

In my view, once I have introduced the idea of the outside
Universe into my model I am bound to complicate things quite
dramatically, because now I need to consider the interactions
between the two subsystems A and B (Universe). And they are
often not so simple..

To rigorously describe, and -- what is much more difficult --
to solve such a system one has to treat the compound A+B
as a whole. There are many such examples in physics, where
it is absolutely necessary to think globally. We cannot,
for example describe the system of two interacting electrons
via individual (interfering or not) waveforms: psi(x1) and
psi(x2). We have to use a function psi(x1,x2), which is an
amplitude of probability that one (we do not know exactly
which one) electron is at x1 and another at x2.

But physics also teaches us how to simplify things by
isolating the subsystem A from B -- as long as such
simplification makes practical sense. It is not always
possible though, and often not quite acurate. When you
describe the free fall of a mass "m" in the Earth gravitational
field you do, in fact, simplify the rigorous model by replacing
the two-body problem by the one-body problem. Knowing that
the gravitational pull of mass "m" has practically no effect
on the movement of Earth mass "M", you can just ignore
the Earth as such and instead introduce "one-way" gravitational
force into your model. This methodology of removing
constraints and replacing them by reaction forces (and/or
torques) dates back to Newton and is the first thing
to do in solving countless problems of classical mechanics.

You can also apply it to a quantum model of the hydrogen atom,
because the proton is much, much heavier than the electron.
But you cannot exactly apply it to the model of helium, because
now you deal -- in addition to heavy nucleus -- with two
electrons of the same mass.
 
I think that the monadic IO provides us with such a
simplification. As long as we realize what are its limitations
and as long as we stay within reasonable limits of the concept
we should be fine here. The operative word here is "realize".
Do we really know those limitations? 

I have seen engineers nondiscriminantly applying simplified
engineering formulas to problems where such simplifications
were not valid at all. You know, formulas of the sort "beam
bending moment", taken from some engineering handbook. Such
formulas had been, of course, derived from some basic theory
-- but with a lot of simplifying assumptions: linearity, isotropy,
small deflections, limits put on ratio of dimensions, etc.
But, by the time the formula hit the handbook, all those
assumption have been long forgotten.

I am afraid that once we start taking the monadic concept
too far we are bound to find some obstacles (philosophical or
practical) sooner or later. Same applies to the concept of
the Universe, because we often do not know what is exactly our
model of Universe. How do we model interactions of unknown
or imprecise nature?


Jan








Re: OO in Haskell

1999-10-07 Thread Adrian Hey

On Wed 06 Oct, Johan Nordlander wrote:
> Just to avoid any unfortunate misconceptions: O'Haskell definitely
> preserves the property we commonly refer to as referential transparency,
> and so does Concurrent Haskell, or any other sound monadic extension of
> the language.

Hmm, I obviously don't understand what 'referential transparency' means.
I must say I'm puzzled by statements like this. If the presence of
mutable variables (and MVars in Concurrent Haskell) preserve referential
transparency, then why _don't_ we have referential transparency in C?

Does it have something to do with denotational semantics and world
models containing infinite trees of random numbers?

Regards
-- 
Adrian Hey







Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Michael Hobbs

Michael Hobbs wrote:
> > Consider this:
> > > type IO a = StateOfUniverse -> (a, StateOfUniverse)
> > > -- Not syntactically correct, but you know what I mean.
> >
> > So anything that is declared, say `IO Int', means that it is actually a
> > function that reads in the state of the universe, potentially modifies
> > it, and then returns an Int value along with the new state of the
> > universe. The interesting thing to note is that the state of the
> > universe never changes between calls that are strung together using the
> > `>>=' operator. That is, the StateOfUniverse that is returned by the
> > first monad is exactly same state that is fed into the second. Whether
> > or not you want to call this "referentially transparent", well I guess
> > that's up to your own philosophic bias.
> 
> I rescind the statement that "the state of the universe never changes
> between calls that are strung together using the `>>=' operator". After
> further consideration, I believe that that's incorrect.

Unless, of course, you consider StateOfUniverse to encapsulate all past,
present, and future events (a 4-dimensional value). In which case, you
don't need to return a new StateOfUniverse, since it will be exactly the
same as the one given, except maybe with different `currentTime' value.
But I'm getting way too deep here.

The problem is a function like `getChar' that is declared `IO Char'. If
the user has not typed a character when this monad is invoked, it will
sit and wait for the event. That is, the current StateOfUniverse that is
passed to getChar has absolutely nothing in it to indicate what
character will be returned, unless it also contains future events.

However, if we define `getChar' like this, we might get around the nasty
issue of future events:
> getChar = do
>   c <- peekKbdBuffer :: IO [Char]  -- length of 0 or 1
>   if null c then getChar else return head c
In this case, `getChar' will continue looping until StateOfUniverse
changes such that the keyboard buffer actually has a value in it. Of
course, this means that the StateOfUniverse must be able to alter itself
somehow between the function calls.

Philosophy Thursday,
- Michael Hobbs






Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Michael Hobbs

Michael Hobbs wrote:
> 
> Adrian Hey wrote:
> > I've read this paper, and it is good, but I still see no reason to
> > change my opinion regarding referential transparency and IO.
> > But I am terribly confused about this issue, there seems to be no real
> > consensus about this in the FP world. I just can't see how if the
> > result of an action is dependent on unknown external world agents
> > (as it is with the IO monad) it could be described as referentially
> > transparent. I can accept that we have referential transparency for
> > user defined monads, but not the IO monad.
> 
> Consider this:
> > type IO a = StateOfUniverse -> (a, StateOfUniverse)
> > -- Not syntactically correct, but you know what I mean.
> 
> So anything that is declared, say `IO Int', means that it is actually a
> function that reads in the state of the universe, potentially modifies
> it, and then returns an Int value along with the new state of the
> universe. The interesting thing to note is that the state of the
> universe never changes between calls that are strung together using the
> `>>=' operator. That is, the StateOfUniverse that is returned by the
> first monad is exactly same state that is fed into the second. Whether
> or not you want to call this "referentially transparent", well I guess
> that's up to your own philosophic bias.

I rescind the statement that "the state of the universe never changes
between calls that are strung together using the `>>=' operator". After
further consideration, I believe that that's incorrect.

- Michael Hobbs






Re: Referential Transparency (was Re: OO in Haskell)

1999-10-07 Thread Michael Hobbs

Adrian Hey wrote:
> I've read this paper, and it is good, but I still see no reason to
> change my opinion regarding referential transparency and IO.
> But I am terribly confused about this issue, there seems to be no real
> consensus about this in the FP world. I just can't see how if the
> result of an action is dependent on unknown external world agents
> (as it is with the IO monad) it could be described as referentially
> transparent. I can accept that we have referential transparency for
> user defined monads, but not the IO monad.

Consider this:
> type IO a = StateOfUniverse -> (a, StateOfUniverse)
> -- Not syntactically correct, but you know what I mean.

So anything that is declared, say `IO Int', means that it is actually a
function that reads in the state of the universe, potentially modifies
it, and then returns an Int value along with the new state of the
universe. The interesting thing to note is that the state of the
universe never changes between calls that are strung together using the
`>>=' operator. That is, the StateOfUniverse that is returned by the
first monad is exactly same state that is fed into the second. Whether
or not you want to call this "referentially transparent", well I guess
that's up to your own philosophic bias.

- Michael Hobbs






Re: OO in Haskell

1999-10-07 Thread Adrian Hey

On Wed 06 Oct, Alex Ferguson wrote:
> Me:
> > >  Your 'partial' list would appear, from a initial
> > > inspection, to leave little left of either type safety or referential
> > > transparency. 
> 
> KA:
> > I can not see how State encapsulation will
> > weaken any type system.
> 
> No, that's be the 'referential transparency' part of the above.
> (I assume you're talking about something considerably different
> from state-by-monads, here.)

Is referential transparency really such a sacred cow? Sometimes
side effects are useful IMHO e.g. for IO. (Though the Cleaners regard
IO as being referentially transparent for technical reasons which I
don't quite understand.)

I've been looking at Concurrent Haskell, and more recently Johan
Nordlanders O'Haskell. I think there's a good deal of sense in both
these dialects of Haskell (I especially like the idea of getting rid
of the evil I:-)

To me, the important thing is that it should be clear when we do and
when we don't have referential transparency. Where we don't, words
like 'operation' or 'action' should be used instead of 'function'.

So I can see nothing wrong with encapsulated (mutable) state, in principle,
just so long as the state is only mutated by 'actions'.

Regards 
-- 
Adrian Hey







Re: OO in Haskell

1999-10-06 Thread Juergen Pfitzenmaier

Kevin Atkinson wrote:
> Ok here is my partial list.
> [ . snip  snip]
> - A solution to the abilities arising from multi parameter type classes.

Yes some kind of cooking guide for multi parameter type classes would be
nice. Where to use and where *not*. Sometimes I think multiple parameters
are the right solution - only to discover that I overlooked some deeply
buried dependency between two parameters. This dependency has than to be
added as a kind of constraint when I give the implementation a second try.

Has anyone suggestion/guidelines for the design/use of multi parameter type ses ?

ciao pfitzen






Re: Re: OO in Haskell

1999-10-06 Thread Juergen Pfitzenmaier

Kevin Atkinson wrote:
> Java is an evern cleaner language for OO as 

questionable. Every *new* language should try to recycle the experience
gained from its predecessors. In the field of OO one thing springs to
my mind: The ability to extend/restrict the signature of a member function
in derived classes. Oh I can *do* it with Java by using composition but
I can't  do it with *style*. By _style_ I mean not breaking/twisting the
big picture of my project; these changes of the signatures should be
accessible to the compiler (or some other tool) in such a way that
they are reflected theoretically sound in the type system.

Some people behind Eiffel were aware of these needs and tried to meet
them but Eiffel is long gone (not really gone - just not seen anymore).

ciao pfitzen






Re: Re: OO in Haskell

1999-10-06 Thread Juergen Pfitzenmaier

Kevin Atkinson wrote:
> I don't like
> languages that try to stay simple because doing complex things in simple
> languages in well, frustrating.  Can you agree with me here?

What exactly do you mean ? I can put together simple things to get
a complex tool that I can view again as a simple thing etc etc in haskell.
If I try to do the same in C++ or Java I fall over design flaws in the
language or over my own unreadable code because it became impossible
to stick to some useful shape.
That last sentence is not just a saying -- I had to drop a project
in C++ together with somethings that really meant value for me -
only because of the braindamaged handling of templates in C++.

ciao pfitzen






Re: OO in Haskell

1999-10-06 Thread Fergus Henderson

On 06-Oct-1999, Frank A. Christoph <[EMAIL PROTECTED]> wrote:
> Kevin Atkinson wrote:
> > Ok here is my partial list.
> >
> > - True ad-doc polymorphism
> > - Built in dynamic typing system.
> > - State Encapsulation
> > - A solution to the abilities arising from multi parameter type classes.
> > - Syntactic sugar for supporting OO programming styles
> 
> What is the significance of dynamic typing being "built in"?

Well, instances of `Typeable' should be derived automatically by the compiler.
Furthermore that should be the _only_ way of creating instances of `Typeable';
the current approach in Hugs/ghc is unsafe in that if the user creates an
invalid instance of `Typeable' then the result may be a crash at runtime.
(ObMercuryPlug: Note that Mercury doesn't have those problems ;-)

Furthermore there should be support for dynamic type class casts.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.






RE: OO in Haskell

1999-10-06 Thread Frank A. Christoph

Kevin Atkinson wrote:
> Ok here is my partial list.
>
> - True ad-doc polymorphism
> - Built in dynamic typing system.
> - State Encapsulation
> - A solution to the abilities arising from multi parameter type classes.
> - Syntactic sugar for supporting OO programming styles

What is the significance of dynamic typing being "built in"?

What do you mean by "state encapsulation"?

What sort of syntactic sugar is it that you want?

--FAC







Re: OO in Haskell

1999-10-06 Thread Clifford Beshers


   On Wed, 6 Oct 1999, Simon Peyton-Jones wrote:

   > Kevin writes:
   > 

   I think it would be in Carlos interest to modify Marks sample
   implantation of the type system to support this.  Then we can really
   see if his system will indeed work with the rest of Haskell.

Personally, I'm against the implantation of a type system with or
without the consent of a trained physician.  The risk of side-effects
is just too great.




Sorry Kevin.  I don't usually jump on typos, but that was too good to
pass up.

Cliff

-- 
Clifford Beshers Computer Graphics and User Interfaces Lab
[EMAIL PROTECTED] Department of Computer Science
http://www.cs.columbia.edu/~beshersColumbia University






RE: OO in Haskell

1999-10-06 Thread Kevin Atkinson

On Wed, 6 Oct 1999, Simon Peyton-Jones wrote:

> Kevin writes:
> 
> | I strongly agree that Haskell can become a *much* more 
> | powerful language
> | with out losing any of clean syntax or semantics.  However, 
> | when ever I
> | bring up limitations of Haskell type system on this list I either get
> | ignorance or resistance.
> 
> I strongly agree that Haskell could be better.  But it is not easy
> to come up with clean designs for the sort of extensions you would like.
> - True ad-doc polymorphism
> - Built in dynamic typing system.
> - State Encapsulation
> - A solution to the abilities arising from multi parameter type classes.
> - Syntactic sugar for supporting OO programming styles
> 
> It is easier to identify the problem, that to identify a solution.
> It is easier to identify a solution than to describe that solution 
>   completely and precisely.
> It is easier to describe the solution precisely than to implement it.
> 
> I think some of the resistance Kevin feels may have something of
> the flavour of "lets wait to find a good solution, rather than 
> whip up a half-baked one".

What happens is that those few who think it is a good idea post one or
two messages expression they view points and perhaps giving a URL to
work they've done on the subject but don't really participate in the
discussion.  Meanwhile about a dozen other people post messages of why in
printable the idea is bad.  They don't say its a good idea but has
problems, they say how Haskell doesn't need it and they are happy with
the way things are.  So I reply to those dozen people and half the
time make a fool out of my self because I only half know what I am
taking about.  Thus because I received so much negative feedback I get
the impression that the Haskell community just doesn't *want* that
feature--even if those high up think is a good idea.

> Dynamic types is a good example.  There is a large design space of
> possible solutions, and it's not clear (to me) which is best.  I don't
> think any consensus has emerged.  
> 
> Ad hoc polymorphism is another good example.  Carlos's System CT
> goes a way towards a fairly fully-described solution; Mercury implements
> another variant.  I don't know how the two compare.  It is controversial
> whether the interaction of ad-hoc polymorphism with type-class overloading
> makes the whole thing unmanageably complex.

I think it would be in Carlos interest to modify Marks sample
implantation of the type system to support this.  Then we can really
see if his system will indeed work with the rest of Haskell.

> On the MPTC issues, a good solution does indeed seem to be emerging,
> as Mark mentions.

Yes it does, and because of this I am going to take another shot at my
abstraction library.  With Mark's solution I should not one into any
of the major barriers I did before.

> None of this is to say that dynamic types or ad-hoc polymorphism
> is a bad thing.  But I think it's a misconception to interpret the
> feedback Kevin has received as closed-mindedness. It's just a lot of work
> to work out to describe and implement these sort of extensions; even
> laying aside the expressiveness vs simplicity tradeoff, which itself
> is a real issue.
> 
> What can be done to hurry the process along?  One constructive thing
> would be for enthusiasts for a particular extension to move towards
> complete, precise descriptions of what they would like; and to 
> implement the feature in Mark's type checker (the one he's just released).
> Doing this doesn't guarantee that a feature will make it into Haskell,
> but it does make it more likely.  The way to guarantee that a feature
> will make it into a particular compiler is to implement it.  Both Hugs
> and GHC are open source, and work from a CVS repository you can get to
> over the network.
> 
> Haskell belongs to you. (Sound of violins.)

Thanks for some feedback from someone who doesn't think I want to
undermine Haskell.

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







Re: OO in Haskell

1999-10-06 Thread Johan Nordlander

Adrian Hey writes:

> Hmm, I obviously don't understand what 'referential transparency' means.
> I must say I'm puzzled by statements like this. If the presence of
> mutable variables (and MVars in Concurrent Haskell) preserve referential
> transparency, then why _don't_ we have referential transparency in C?


I'd say that an absolutely brilliant exposition of this topic is to be 
found in Phil Wadler's paper "How to declare an imperative", available 
on the web at

  http://www.cs.bell-labs.com/who/wadler/topics/monads.html

-- Johan






Re: OO in Haskell

1999-10-06 Thread Andreas Rossberg

Kevin Atkinson wrote:
> 
> On Tue, 5 Oct 1999, George Russell wrote:
> 
> > Perhaps I'm being stupid.  (It certainly wouldn't be the first time!)
> > But what does OO give me that I can't get with existential types (in
> > datatype definitions) and multiparameter type classes? The latter seem
> > to me much more powerful, since I can add dancing and singing methods
> > to objects without having to go back to the original class definition.
> 
> 1) Dynamic types.  You can't cast up.

You certainly mean to cast down (casting upwards corresponds to the
application of the existential constructor).

Down casts could be done. This would mean that each existential
constructor had to carry dynamic type information and there would be a
special pattern matching construct that checks this. One could argue
whether this feature is desirable or worthwhile in the presence of
parametric polymorphism and algebraic data types.

> 2) More specific types, you can't _easilly_ call the more general type.
> For example in OO this is very commen:
> 
> class Base
>   virtual foo()
> do stuff
> 
> class Derived, extends Base
>   foo()
> call Base::foo()
> doo stuff

I guess what you mean by "more specific types" is inheritance. This is
not directly related to types, though. You are right, Haskell does only
provide a very weak form of inheritance, namely default methods. On the
other hand, many people consider inheritance a doubtful feature.

> 3) Encapsulation.  You can't have private and protected members.  Some
> of this can be done using modules.  However it is more work.

Maybe, but I think it's good to have this separation of concepts:
classes provide a certain form of polymorphism, encapsulation is
something completely different that should be dealt with uniformingly,
i.e. by the module system. However, it would be nice if Haskell had a
more powerful module language.

> 4) Cleaner more natural syntax.

>From an abstract language point of view, there certainly is nothing
natural or even clean in having this special case syntax for the first
argument:

x.f y z

compared to

f x y z

In particular, it does not scale to methods where the first parameter
does not happen to be of the type to dispatch on (or where there
actually are zero or multiple such xs, cf. the binary method and multi
dispatch problems in OOP).

For certain problem domains however it might appear to be natural to
think in terms of objects that receive messages. But I'm not sure
whether this has to be reflected in syntax too much. Haskell is not an
object-oriented language. You can express most things that you can
express in OO languages but they will look a bit different. And
sometimes of course it will be more painful - but no single language can
be equally well-suited for every application.

> Unfortunately Haskell, like Java in some ways, is also a simple language.

Java is much more complex than most people realize. And Haskell is far
from being a simple language either. So adding even more features
requires compelling reasons, in particular, if there are already ways to
achieve the same effect without too much extra effort.

But of course, in comparison with C++ any language looks simple. ;-)

> I would like to be able to do the things in Haskell that I can do in C++
> but currently Haskell's type system is too simple to allow me to do
> them.

You are mixing up things a little bit. The Haskell type system
definitely is not simple. It is likely to be the most complex and
powerful type system of any major language around. The reason why there
are things that you can do in C++ but not in Haskell is that C++ does
not press typing that much. Templates for example are not really type
checked. That gives you flexibility at the price of safety or early
error detection.

Another aspect you mentioned in one of your postings is state. Again
this is not directly related to the expressiveness of Haskell's type
system. C++, like most other languages, simply ignores state in its type
system. So of course you won't have any problem as far as typing is
concerned. Haskell does capture the use of state in its types - being a
curse and a blessing.

Best regards,

- Andreas






Re: OO in Haskell

1999-10-06 Thread Johan Nordlander

Adrian Hey writes:

> Is referential transparency really such a sacred cow? Sometimes
> side effects are useful IMHO e.g. for IO. (Though the Cleaners regard
> IO as being referentially transparent for technical reasons which I
> don't quite understand.)
>
> I've been looking at Concurrent Haskell, and more recently Johan
> Nordlanders O'Haskell. I think there's a good deal of sense in both
> these dialects of Haskell (I especially like the idea of getting rid
> of the evil I:-)
>
> To me, the important thing is that it should be clear when we do and
> when we don't have referential transparency. Where we don't, words
> like 'operation' or 'action' should be used instead of 'function'.
>
> So I can see nothing wrong with encapsulated (mutable) state, in principle,
> just so long as the state is only mutated by 'actions'.


Just to avoid any unfortunate misconceptions: O'Haskell definitely
preserves the property we commonly refer to as referential transparency,
and so does Concurrent Haskell, or any other sound monadic extension of
the language.

But what I think Adrian is advertising here is the beauty of programming
with (state) monads in general -- a command producing a value has a 
different type from an expression denoting the same value.  O'Haskell
builds its object-oriented state encapsulation on top of this general
idea.

-- Johan






RE: OO in Haskell

1999-10-06 Thread Simon Peyton-Jones

Kevin writes:

| I strongly agree that Haskell can become a *much* more 
| powerful language
| with out losing any of clean syntax or semantics.  However, 
| when ever I
| bring up limitations of Haskell type system on this list I either get
| ignorance or resistance.

I strongly agree that Haskell could be better.  But it is not easy
to come up with clean designs for the sort of extensions you would like.
- True ad-doc polymorphism
- Built in dynamic typing system.
- State Encapsulation
- A solution to the abilities arising from multi parameter type classes.
- Syntactic sugar for supporting OO programming styles

It is easier to identify the problem, that to identify a solution.
It is easier to identify a solution than to describe that solution 
completely and precisely.
It is easier to describe the solution precisely than to implement it.

I think some of the resistance Kevin feels may have something of
the flavour of "lets wait to find a good solution, rather than 
whip up a half-baked one".

Dynamic types is a good example.  There is a large design space of
possible solutions, and it's not clear (to me) which is best.  I don't
think any consensus has emerged.  

Ad hoc polymorphism is another good example.  Carlos's System CT
goes a way towards a fairly fully-described solution; Mercury implements
another variant.  I don't know how the two compare.  It is controversial
whether the interaction of ad-hoc polymorphism with type-class overloading
makes the whole thing unmanageably complex.

On the MPTC issues, a good solution does indeed seem to be emerging,
as Mark mentions.

None of this is to say that dynamic types or ad-hoc polymorphism
is a bad thing.  But I think it's a misconception to interpret the
feedback Kevin has received as closed-mindedness. It's just a lot of work
to work out to describe and implement these sort of extensions; even
laying aside the expressiveness vs simplicity tradeoff, which itself
is a real issue.

What can be done to hurry the process along?  One constructive thing
would be for enthusiasts for a particular extension to move towards
complete, precise descriptions of what they would like; and to 
implement the feature in Mark's type checker (the one he's just released).
Doing this doesn't guarantee that a feature will make it into Haskell,
but it does make it more likely.  The way to guarantee that a feature
will make it into a particular compiler is to implement it.  Both Hugs
and GHC are open source, and work from a CVS repository you can get to
over the network.

Haskell belongs to you. (Sound of violins.)

Simon







Re: OO in Haskell

1999-10-06 Thread Alex Ferguson


Me:
> >  Your 'partial' list would appear, from a initial
> > inspection, to leave little left of either type safety or referential
> > transparency. 


KA:
> Could explain how they could.  There is a very nice paper written up on
> True ad-hoc polymorphism.  By a build in build in dynamic type system I
> mean being able to safely recover types from an existential collection
> using a runtime check. 

That's immediately weakening what Haskell understands by 'type safety'.
(Though not necessarily unacceptable, as Fergus Henderson says, if
I can tell by the top-level type of a program whether it's statically
of sound type, or not.)


> I can not see how State encapsulation will
> weaken any type system.

No, that's be the 'referential transparency' part of the above.
(I assume you're talking about something considerably different
from state-by-monads, here.)


> > [...] It's not clear from the above agenda,
> > though, that it wouldn't be easier to define (C++)++ (the second ++ being
> > lazy evaluation, HOFs, partial ap., GC).  Which don't get me wrong,
> > would be an entirely good thing, IMO.

> God NO, I like C++ because it is powerful but adding more features on an
> already ugly (but powerful languge) will make matters worse my making it
> more powerful but so ugly with so many pitfalls that no one will want to
> use it.

True;  my Secret Agenda is that at some point they might start taking
'features' back out...  (Case in point, Java:  add in one nice feature,
GC, take out several ugly ones...  resulting in a still pretty ugly
language, but there's more rejoicing in heaven, etc, etc... )

Cheers,
Alex.






Re: Limititions of Haskell Type System (was Re: OO in Haskell)

1999-10-06 Thread Alex Ferguson


Kevin Atkinson:

> I have a generic mutable array class which has a few basic methods:
> 
> class MArray ... where
>   newArray :: Int -> m (mutArray st el)
>   write :: mutArray st el -> Int -> el -> m ()
>   read :: mutArray st el -> Int -> m el
>   freeze :: m mutArray st el -> m array el 
>   thaw ::  m array el -> m mutArray st el
> 
> and it turns out that it is possible to create a full fledge
> non-mutable array based on the mutable array class with the help of
> this method:
> 
>   thawRunFreeze :: Array el 
> -> (m mutArray st el -> m ())
> -> Array el
> 
> Which will, as the signature suggests and name suggest, thaw an array,
> perform some actions on the mutable array, and then freeze it,
> returning the new array.
> 
> The only problem is that it is impossible to have a generic
> thawRunFreeze method in Haskell.  So I had to resort to some ugly code
> generation.

Thanks for the example.  If I understand you here, what you intend is
not that there always _should_ be a thawRunFreeze, for any type, but
that it should be possible to have an implemention, or semi-generic
hierarchy of implementations, of this which either uses or doesn't use
such a method, as appropriate/available.

I think this is certainly do-able, and I've seen it addressed, if
not necessarily entirely unqualifiedly solved, in a couple of papers.
If this is your main concern about the flexibility of Haskell types,
then be of good cheer as I'm certain this one is soluble, entirely
within the basic 'look and feel' of Haskell typing.

Which isn't to say that I'm not handwaving over a morass of technical
details, or expecting the language committee to agree on any such things
within the netx language revision or three. ;-)

Slán,
Alex.






Re: OO in Haskell

1999-10-06 Thread Alex Ferguson


Kevin Atkinson, replying to me...

> > I think it should be eminently possible to write a good generic
> > container class without resorting to either dynamic typing, or to
> > ad hoc polymorphism.  (I don't see how these would really help,
> > actually.)  
> 
> Neither of them will.  Sorry if I implied a connection.  What I DO need
> is a solution is a better solution to multi parameter classes. 

> Yes MPC is too limiting.  I have tried.  See my post "Limititions of
> Haskell Type System (was Re: OO in Haskell)".

I did, but I'd need to see a lot more details before I was any the
wiser as to what limitations you actually encountered.


> > > Ok here is my partial list.
> > >
> > > - True ad-doc polymorphism
> > > - Built in dynamic typing system.
> > > - State Encapsulation
> > > - A solution to the abilities arising from multi parameter type classes.
> > > - Syntactic sugar for supporting OO programming styles
> > 
> > You should try C++ sometime, some people _highly_ recommend it
> > for the above. ;-)
> 
> I take it what you really want me to do is just shut up and leave and
> to  stop trying to change the Haskell language into something you think
> its not.

No, I want you to try and change it into something that it might
plausibly become.  Your 'partial' list would appear, from a initial
inspection, to leave little left of either type safety or referential
transparency.  Either you, or someone of a like agenda, have a very
large number of technical tricks up your sleeve, or those will go
down like the proverbial lead balloon at the next (first?) committee
meeting on Haskell II, I would predict with a degree of confidence
you're at liberty to not share.  It's not clear from the above agenda,
though, that it wouldn't be easier to define (C++)++ (the second ++ being
lazy evaluation, HOFs, partial ap., GC).  Which don't get me wrong,
would be an entirely good thing, IMO.






Re: OO in Haskell

1999-10-06 Thread Alex Ferguson


Kevin Atkinson:
> I never, ever, said that I would like Haskell to be able to do
> everything C++ can.

No, that was my inference from the general drift of your comments.


  I also never said that I want Haskell to become a
> more type unsafe language.  If it was implied I'm sorry.  What I did say
> that I would like Haskell to support true ad-hoc overloading which you
> seam to bitterly oppose to spite its many benefits. 

Hardly 'bitterly'.  I just wish to observe that it:  involves a
considerable technical complication, at least, if one wishes to
preserve sensible typing properties;  adds no actual power to the
language, whatsoever;  is a _highly questionable_ practice from
a human factors POV;  and, well, what were the benefits, again?


> I am interested in using Haskell to come up with a really generic set of
> containers and libraries.   Haskell type system in its current state is
> not well suited for this task at all.  However, I fell that once it can
> do this task it will be able to do it better than any other language out
> there due to its type class system.

I think it should be eminently possible to write a good generic
container class without resorting to either dynamic typing, or to
ad hoc polymorphism.  (I don't see how these would really help,
actually.)  There are likely still 'issues' with doing this properly
with MPCs, I can well believe that:  the 'exploring the design
space' document, and some other papers, examine relaxing/generalising
the rules for class defaults and overlapping instances, in many 
reasonable-seeming, though also technically tricky, directions.
It may be worth looking at least, if you're certain existing MPC
implentations don't allow everything you want to do with containers.


> Ok here is my partial list.
> 
> - True ad-doc polymorphism
> - Built in dynamic typing system.
> - State Encapsulation
> - A solution to the abilities arising from multi parameter type classes.
> - Syntactic sugar for supporting OO programming styles

You should try C++ sometime, some people _highly_ recommend it
for the above. ;-)

Cheers,
Alex.






Re: OO in Haskell

1999-10-05 Thread Alex Ferguson


Kevin Atkinson and I argue about C++'s 'Cleaner more natural syntax':
> I would like to be able to do the things in Haskell that I can do in C++
> but currently Haskell's type system is too simple to allow me to do
> them.  There are also some things I can't do in C++ but really wish I
> could, I also wish I could do those things with Haskell.  I am not
> saying C++ is an elegant language, however it is a powerful one.  I
> would like to have that power in Haskell. 

I concur that there are places, due to its desire to maintain
strong typing properties that Haskell is 'less powerful' than C++.
But the consensus seems to be that strong typing is worth the
occassional pain (or at least we avoid the pain by not using Haskell
if the task isn't well-suited, perhaps), and that we _don't_ want
to abandon that in favour of C++'s inherent lack of type safety
(or that if we do, we go and write C++ programs).  Yes, there
are areas in which it appears to be possible to make Haskell-style
typing more general, without any basic loss of typing properties,
but as you say in a related context, it rapidly gets Rather
Technical, so the issues aren't as simple as 'Haskell's type
system should immediately be made to accept everything C++ would'.


And that says nothing about the desirability of Haskell syntax vs.
some other system's, in cases where their power is essentially
equivalent, which was the particular topic at hand.


> Haskell for *most* things has far cleaner syntax than just about any
> other language out there.  However, OO is not one of them.

"OO" is such a open-ended term, with such a lack of any simple
definition that I think it'd be best to avoid it entirely (I mean in
this sort of discussion, though 'ever' wouldn't be a bad plan either),
in favour of more specific, albeit more open-ended, features of same,
whether those be message-passing, ad hoc polymorphism, subtyping,
inheritance, state encapulation -- et cetera, et cetera.  Haskell takes
a decidedly 'cafeteria' approach to that shopping list, so blanket
statements like 'Haskell is good/bad for OOP' obscure more than they
reveal, IMO.

Slán,
Alex.






Re: OO in Haskell

1999-10-05 Thread Craig Dickson

Kevin Atkinson <[EMAIL PROTECTED]> wrote:

> God NO, I like C++ because it is powerful but adding more features on an
> already ugly (but powerful languge) will make matters worse my making it
> more powerful but so ugly with so many pitfalls that no one will want to
> use it.

Some would say this has been true for some time...

Craig








Re: Limititions of Haskell Type System (was Re: OO in Haskell)

1999-10-05 Thread Kevin Atkinson

Alex Ferguson wrote:
> 
> Kevin Atkinson:
> 
> > I have a generic mutable array class which has a few basic methods:
> >
> > class MArray ... where
> >   newArray :: Int -> m (mutArray st el)
> >   write :: mutArray st el -> Int -> el -> m ()
> >   read :: mutArray st el -> Int -> m el
> >   freeze :: m mutArray st el -> m array el
> >   thaw ::  m array el -> m mutArray st el
> >
> > and it turns out that it is possible to create a full fledge
> > non-mutable array based on the mutable array class with the help of
> > this method:
> >
> >   thawRunFreeze :: Array el
> > -> (m mutArray st el -> m ())
> > -> Array el
> >
> > Which will, as the signature suggests and name suggest, thaw an array,
> > perform some actions on the mutable array, and then freeze it,
> > returning the new array.
> >
> > The only problem is that it is impossible to have a generic
> > thawRunFreeze method in Haskell.  So I had to resort to some ugly code
> > generation.
> 
> Thanks for the example.  If I understand you here, what you intend is
> not that there always _should_ be a thawRunFreeze, for any type, but
> that it should be possible to have an implemention, or semi-generic
> hierarchy of implementations, of this which either uses or doesn't use
> such a method, as appropriate/available.
> 
> I think this is certainly do-able, and I've seen it addressed, if
> not necessarily entirely unqualifiedly solved, in a couple of papers.
> If this is your main concern about the flexibility of Haskell types,
> then be of good cheer as I'm certain this one is soluble, entirely
> within the basic 'look and feel' of Haskell typing.
> 
> Which isn't to say that I'm not handwaving over a morass of technical
> details, or expecting the language committee to agree on any such things
> within the netx language revision or three. ;-)

If you are so convinced than do it.  Sense a solution to MTC should be
in Hugs soon I don't wish to pursue this any farther until I get a copy
of Hugs with Mark's solution so that I can play with it some.  From his
web site his solution looks very promising.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

Jacob B Schwartz wrote:

> > - Built in dynamic typing system.
> 
> Huh?  Typing in Haskell is static.  Liek I said, this removes a lot
> of run time errors.  It also has performance benefits!! You don't have
> to store tags on all your data objects!  And you don't have to spend
> time checking them!  Time and space savings!  How can you beat that?
> 

As I told Alex:

By a built in dynamic type system I mean being able to safely recover
types from an existential collection using a runtime check. 

> - A solution to the abilities arising from multi parameter type classes.
> 
> I also think this is due to your not thinking like a Haskell programmer.
> Of course if you use the language like it were C++ then you're gonna
> hit a point where you ask why Haskell doesn't provide you with the
> C++ thing that you want.  Plus, there are tons of ways around this.
> I mean, you probably use this every day:
> 
> 5 + 1.0
> 
> and it works, even though one side is a Float and one side is an
> Integer, and the Eq class only works on one type.  It's called
> "fromInteger".

Um NO!  This is a servious problem that most people are very aware of. 
In fact Mark P. Jones just informed me that he has a solution that will
be appeating in Hugs VERY soon.

> 
> > - Syntactic sugar for supporting OO programming styles
> 
> Eh, syntactic sugar.  No one's going to argue over this.  If you
> can write a preprocessor to do the conversion, then it's up to
> the people who write the compilers to offer it or not.

Preprocessors are a mess and a good language will not need it.

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






Re: OO in Haskell

1999-10-05 Thread Johan Nordlander

Theo Norvell writes:
>
>On Tue, 5 Oct 1999, Kevin Atkinson wrote:
>
>> In case you have not figured out a couple of months ago I posted the
>> beginnings of a generic container and algorithm collection for
>> Haskell.
>
> This is exactly the sort of thing that OOP tends to be rather bad at.
> How many times have I written in Java
>  SomeType x = (SomeType)( a_vector.getElement( i ) ) ; 
> thus relying on run-time type checking?
>
> [...]
>
> ML and Haskell represent two approaches to doing "templates"
> right.  Each has their advantages, but both seem to be clearly
> superior to the OOP approach. 

Subtyping based on records and parametric polymorphism with algebraic 
datatypes are in fact orthogonal language features.  OO languages
have preferred the former, functional ones the latter.  There's no
reason why you can't have them both, though.  Check out O'Haskell at
   
   http://www.cs.chalmers.se/~nordland/ohaskell/

Cheers,
Johan






Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

Alex Ferguson wrote:
> 
> Kevin Atkinson, replying to me...
> 
> > > > - True ad-doc polymorphism
> > > > - Built in dynamic typing system
> > > > - State Encapsulation
> > > > - A solution to the abilities arising from multi parameter type classes.
> > > > - Syntactic sugar for supporting OO programming styles

...

> > I take it what you really want me to do is just shut up and leave and
> > to  stop trying to change the Haskell language into something you think
> > its not.
> 
> No, I want you to try and change it into something that it might
> plausibly become.  Your 'partial' list would appear, from a initial
> inspection, to leave little left of either type safety or referential
> transparency. 

Could explain how they could.  There is a very nice paper written up on
True ad-hoc polymorphism.  By a build in build in dynamic type system I
mean being able to safely recover types from an existential collection
using a runtime check.  I can not see how State encapsulation will
weaken any type system. And a better solution to MPC is the one thing I
think we all agree on.

> Either you, or someone of a like agenda, have a very
> large number of technical tricks up your sleeve, or those will go
> down like the proverbial lead balloon at the next (first?) committee
> meeting on Haskell II, I would predict with a degree of confidence
> you're at liberty to not share.  It's not clear from the above agenda,
> though, that it wouldn't be easier to define (C++)++ (the second ++ being
> lazy evaluation, HOFs, partial ap., GC).  Which don't get me wrong,
> would be an entirely good thing, IMO.

God NO, I like C++ because it is powerful but adding more features on an
already ugly (but powerful languge) will make matters worse my making it
more powerful but so ugly with so many pitfalls that no one will want to
use it.

Haskell on the other hand is a modern language which is not based on
something which came out of the 70's (C) which got it popularity because
it was easy to implement and good for system programming as it has
virtual no type safety.

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






Re: OO in Haskell

1999-10-05 Thread Alex Ferguson


Kevin Atkinson:
> > > 3) Encapsulation.  You can't have private and protected members.  Some
> > > of this can be done using modules.  However it is more work.
> > 
> > What exactly can't be done with classes, and how, substantively, is
> > it more work?

> class Foo
>   private: -- only members of the Foo class can see this
> ...
>   protected: -- only mebers of the Foo class and those derived from foo
>  -- can see it.
>   public: -- anyone can see it

Well, the only problem I can see with doing this with modules is if
you wanted 'private' and a 'protected' members of the _same_ class,
which I confess I've never been mortally offended by lack of a capability
to cope with.


> > > 4) Cleaner more natural syntax.
> > 
> > More like C++, you mean?
> 
> Or Java.  Although many OO things can be done in Haskell C++ and Java
> syntax is more natural more doing OO.

If I sound a tad skeptical about some of your suggestions, it may be
because you do seem to have something of the running undercurrent
in your posts that what Haskell _really_ needs to be is C++ with some
functional bits and bobs added on, which instantly gets my defensive
instincts going, as it sounds, without wanting to provoke Language
Wars here, like a truly alarming prescription for a language design,
and not one very compatible with Haskell as it's currently constituted.

In short, I'm unaware of any way in which C++ syntax is 'more natural',
other than in the sense of 'for a C++ programmer', or 'cleaner' -- at all.

Slán,
Alex.






Re: Re: OO in Haskell

1999-10-05 Thread Juergen Pfitzenmaier

Kevin Atkinson wrote:
> Even through most problems don't truly fit in the OO paradigm, OO
> still is extremely useful.  GUI are a prime example of what OO is good
> for.
point given. GUI are an area where OO is good.

> ... [OO] can greatly
> simplify complex problems into something manageable.

point partly given. If OO solves your problem nicely than nobody
gets out to see if something other -- say functional, declarative ... --
would solve it even better. The one thing I have against OO is the hype
- some sell it as a swiss army knife and others believe that. And so
they miss the real point about programming: Programming is the quest
for the insight. Insight into a problem and understanding what tools
are there to solve it.
If I use OO without looking for other ways just because it works I'm
doing my job but I'm not doing *good* work. If I use OO because I know
it is justified compared to the other ways than I'm in the position
to do a good work (there's still room to fail but it's less likely).

ciao pfitzen






Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

Alex Ferguson wrote:
> 
> Kevin Atkinson:
> > I never, ever, said that I would like Haskell to be able to do
> > everything C++ can.
> 
> No, that was my inference from the general drift of your comments.
> 
>   I also never said that I want Haskell to become a
> > more type unsafe language.  If it was implied I'm sorry.  What I did say
> > that I would like Haskell to support true ad-hoc overloading which you
> > seam to bitterly oppose to spite its many benefits.
> 
> Hardly 'bitterly'.  I just wish to observe that it:  involves a
> considerable technical complication, at least, if one wishes to
> preserve sensible typing properties;  adds no actual power to the
> language, whatsoever;  is a _highly questionable_ practice from
> a human factors POV;  and, well, what were the benefits, again?

I listed some of them in previous posts which you chose to ignore.

> I think it should be eminently possible to write a good generic
> container class without resorting to either dynamic typing, or to
> ad hoc polymorphism.  (I don't see how these would really help,
> actually.)  

Neither of them will.  Sorry if I implied a connection.  What I DO need
is a solution is a better solution to multi parameter classes. 

> There are likely still 'issues' with doing this properly
> with MPCs, I can well believe that:  the 'exploring the design
> space' document, and some other papers, examine relaxing/generalising
> the rules for class defaults and overlapping instances, in many
> reasonable-seeming, though also technically tricky, directions.
> It may be worth looking at least, if you're certain existing MPC
> implentations don't allow everything you want to do with containers.

Yes MPC is too limiting.  I have tried.  See my post "Limititions of
Haskell Type System (was Re: OO in Haskell)".

> > Ok here is my partial list.
> >
> > - True ad-doc polymorphism
> > - Built in dynamic typing system.
> > - State Encapsulation
> > - A solution to the abilities arising from multi parameter type classes.
> > - Syntactic sugar for supporting OO programming styles
> 
> You should try C++ sometime, some people _highly_ recommend it
> for the above. ;-)

I take it what you really want me to do is just shut up and leave and
to  stop trying to change the Haskell language into something you think
its not.
  
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: OO in Haskell

1999-10-05 Thread Alex Ferguson


Kevin Atkinson:
> 2) More specific types, you can't _easilly_ call the more general type.
> For example in OO this is very commen:
> 
> class Base
>   virtual foo()
> do stuff
> 
> class Derived, extends Base
>   foo()
> call Base::foo()
> doo stuff

You can certainly do this in Haskell;  the only difference (and here we
return to a well-worn point) you can't _overload_ the name of a different
method between two different classes.


> 3) Encapsulation.  You can't have private and protected members.  Some
> of this can be done using modules.  However it is more work.

What exactly can't be done with classes, and how, substantively, is
it more work?


> 4) Cleaner more natural syntax.

More like C++, you mean?

Slán,
Alex.






Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

Alex Ferguson wrote:
> 
> Kevin Atkinson and I argue about C++'s 'Cleaner more natural syntax':
> > I would like to be able to do the things in Haskell that I can do in C++
> > but currently Haskell's type system is too simple to allow me to do
> > them.  There are also some things I can't do in C++ but really wish I
> > could, I also wish I could do those things with Haskell.  I am not
> > saying C++ is an elegant language, however it is a powerful one.  I
> > would like to have that power in Haskell.
> 
> I concur that there are places, due to its desire to maintain
> strong typing properties that Haskell is 'less powerful' than C++.
> But the consensus seems to be that strong typing is worth the
> occassional pain (or at least we avoid the pain by not using Haskell
> if the task isn't well-suited, perhaps), and that we _don't_ want
> to abandon that in favour of C++'s inherent lack of type safety
> (or that if we do, we go and write C++ programs).  Yes, there
> are areas in which it appears to be possible to make Haskell-style
> typing more general, without any basic loss of typing properties,
> but as you say in a related context, it rapidly gets Rather
> Technical, so the issues aren't as simple as 'Haskell's type
> system should immediately be made to accept everything C++ would'.

I never, ever, said that I would like Haskell to be able to do
everything C++ can.  I also never said that I want Haskell to become a
more type unsafe language.  If it was implied I'm sorry.  What I did say
that I would like Haskell to support true ad-hoc overloading which you
seam to bitterly oppose to spite its many benefits. 

Also, I strongly belove that if Haskell's type system is made more
powerful it can be suited to a great number of tasks.  The only thing it
won't really be well suited for is low level system takes as those by
there very nature require unsafe casts of raw memory.  However with some
low level extensions to be able to read and write to raw
memory--probably encapsulate with in a state monad of course--Haskell
could also be suited to those tasks.  However that is not really what I
am interested in.

I am interested in using Haskell to come up with a really generic set of
containers and libraries.   Haskell type system in its current state is
not well suited for this task at all.  However, I fell that once it can
do this task it will be able to do it better than any other language out
there due to its type class system.


> > Haskell for *most* things has far cleaner syntax than just about any
> > other language out there.  However, OO is not one of them.
> 
> "OO" is such a open-ended term, with such a lack of any simple
> definition that I think it'd be best to avoid it entirely (I mean in
> this sort of discussion, though 'ever' wouldn't be a bad plan either),
> in favour of more specific, albeit more open-ended, features of same,
> whether those be message-passing, ad hoc polymorphism, subtyping,
> inheritance, state encapulation -- et cetera, et cetera.  Haskell takes
> a decidedly 'cafeteria' approach to that shopping list, so blanket
> statements like 'Haskell is good/bad for OOP' obscure more than they
> reveal, IMO.

Ok here is my partial list.

- True ad-doc polymorphism
- Built in dynamic typing system.
- State Encapsulation
- A solution to the abilities arising from multi parameter type classes.
- Syntactic sugar for supporting OO programming styles

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






Re: OO in Haskell

1999-10-05 Thread George Russell

Perhaps I'm being stupid.  (It certainly wouldn't be the first time!)
But what does OO give me that I can't get with existential types
(in datatype definitions) and multiparameter type classes? The latter
seem to me much more powerful, since I can add dancing and singing methods
to objects without having to go back to the original class definition.






Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

Alex Ferguson wrote:

> > > > 4) Cleaner more natural syntax.
> > >
> > > More like C++, you mean?
> >
> > Or Java.  Although many OO things can be done in Haskell C++ and Java
> > syntax is more natural more doing OO.
> 
> If I sound a tad skeptical about some of your suggestions, it may be
> because you do seem to have something of the running undercurrent
> in your posts that what Haskell _really_ needs to be is C++ with some
> functional bits and bobs added on, which instantly gets my defensive
> instincts going, as it sounds, without wanting to provoke Language
> Wars here, like a truly alarming prescription for a language design,
> and not one very compatible with Haskell as it's currently constituted.

I would like to be able to do the things in Haskell that I can do in C++
but currently Haskell's type system is too simple to allow me to do
them.  There are also some things I can't do in C++ but really wish I
could, I also wish I could do those things with Haskell.  I am not
saying C++ is an elegant language, however it is a powerful one.  I
would like to have that power in Haskell. 

> In short, I'm unaware of any way in which C++ syntax is 'more natural',
> other than in the sense of 'for a C++ programmer', or 'cleaner' -- at all.

For most things C++ is not.  However for representing OO in some areas
C++ is cleaner.  Java is an evern cleaner language for OO as that what
it is based around.   When I think of them I will send some examples to
this list.

Once again:

Haskell for *most* things has far cleaner syntax than just about any
other language out there.  However, OO is not one of them.

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






Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

"Hamilton Richards Jr." wrote:
> 
> One of the more clear-eyed (IMHO) and successful authors of C++ texts is
> Cay Horstmann. A feature of his text, "Mastering C++" (Wiley, 1991), which
> I like is the section, appearing at the end of each chapter, entitled
> "Pitfalls" (the idea comes from Andrew Koenig's book, "C Traps and
> Pitfalls").  Some of the pitfalls describe ordinary programming mistakes,
> but the majority are "gotchas" caused by shortcomings in C++'s design of
> (many of them faithful copies of mistakes in C). Horstmann gives a very
> entertaining lecture on the topic of C++ pitfalls; a full hour does not
> suffice to mention them all.

Yes I know C++ has many pitfalls I never said it was beautiful, however
it is powerful.  And this power is the reason I like C++ so.

> With time and patience, one can learn to think in C++, and it's quite
> possible to write beautiful and efficient code in it (I'm a bit partial to
> some of my own efforts). I believe, however, that one cannot fully
> appreciate a programming language's strengths amnd weaknesses until one has
> tried teaching it to a variety of students. Having done that, I'm here to
> attest that Haskell's syntax --to say nothing of its semantics-- is much
> cleaner, much simpler, and much easier to learn.

Yes Haskell syntax is MUCH nicer than just about ANY other language out
they.  That is what first drew me into Haskell.  Unfortunately Haskell,
like Java in some ways, is also a simple language.  I don't like
languages that try to stay simple because doing complex things in simple
languages in well, frustrating.  Can you agree with me here?

I strongly agree that Haskell can become a *much* more powerful language
with out losing any of clean syntax or semantics.  However, when ever I
bring up limitations of Haskell type system on this list I either get
ignorance or resistance.  I get the distant felling that most people on
this list like Haskell simplicity and fell that making it any more
powerful than it is will ruin it.  Well if that is truly how most people
fell I am just wasting my time with Haskell and should just go back to
using C++ with all its flaws, and never grace the presence of any
Haskell user again.

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






RE: OO in Haskell

1999-10-05 Thread Mark P Jones

Kevin,

| In case you have not figured out a couple of months ago I posted the
| beginnings of a generic container and algorithm collection for
| Haskell.  Duren the process of doing that I discovered the many
| limitations of Haskell current type system.  I simply could not do what
| I wanted to do in Haskell with out resorting to hideously complex
| types.  The biggest thing that was biting be was all the ambiguity
| caused from using multiple parameter classes.

I posted details about a new way to avoid these kinds of problems on
the Haskell list a few weeks ago by annotating class declarations with
information about "functional dependencies" between class parameters.
In case you missed it, here is a repeat of the web pointer:

   http://www.cse.ogi.edu/~mpj/fds.html

This extension has been implemented in Hugs 98 (and, for the most part,
in GHC), and seems to work well in practice.  The code fragment that
you posted for MArray was not complete, but I believe that your intentions
could probably be captured using something like the following:

  class MArray monad mutArray | mutArray -> monad where
newArray :: Int -> monad (mutArray st el)
...

Other interpretations would also be possible if you wanted to include
the index and element types as class parameters.

Other examples that you might want to consider, based on your messages
from several months ago, include:

  class Collection container element | container -> element where ...
  class Dictionary dict index element | dict -> index, element where ...

etc.

Please take a look at the web page above for more details.  You will
be able to play with the implementation very soon.

All the best,
Mark







Re: OO in Haskell

1999-10-05 Thread Juergen Pfitzenmaier

Kevin Atkinson wrote:
> Do you not like OO at all?

what good is OO for ? ;) OO gives me a framework/language to talk
about objects (read entities) and claims that with objects programmers
have the right tool to model real-world entities.
But the main thing in the real-world are *not* entities, the whole
thing is about applying some function to these - possibly nonexisting -
entities. And OO gives me no tools to handle these functions.

ok a bit provocative. I still see something good in OO. It provides
a level of abstraction that wasn't there before but it's not enough.

ciao pfitzen






Re: OO in Haskell

1999-10-05 Thread Juergen Pfitzenmaier

Alex Ferguson wrote:
> That C++ has a very poor type system.

and Kevin Atkinson wrote in response:
> You are going to have to justify it as I thing C++ and Java has a VERY
> good type system minus the implicit typing system. In fact I *like*  the
> C++ typeing system better than I do Haskell's in many cases.

C++ has no type *system*. At least I can see no *systematic* approach
to types in C++.

I like C++ but only for small one-shot programs there thinking about
a good long-term solution would take me longer than hacking a dirty
solution in C++. The good thing in C++ is the broken type system --
I can twist it any way I like in case of a *minor* flaw in the
design of my program. That twisting can be very hard in strongly
typed languages.

ciao pfitzen






Re: OO in Haskell

1999-10-05 Thread Theo Norvell

On Tue, 5 Oct 1999, Kevin Atkinson wrote:

> In case you have not figured out a couple of months ago I posted the
> beginnings of a generic container and algorithm collection for
> Haskell.

This is exactly the sort of thing that OOP tends to be rather bad at.
How many times have I written in Java
SomeType x = (SomeType)( a_vector.getElement( i ) ) ; 
thus relying on run-time type checking?

C++ is an improvement because of its template mechanism, but of course,
and I hope all will agree, dispite being a part of C++, there is nothing
object oriented about that.  Now the problem with C++'s templates is that
they are just fancy macros.  E.g. if you write template code that uses =
on objects of a parametric type, you might assume that = does not throw an
exception and have bugs when it does.  To put it another way, the writer
of template code can not express enough restrictions on the types their
code may be applied to to guarantee that they are writing bug-free code. 

ML and Haskell represent two approaches to doing "templates"
right.  Each has their advantages, but both seem to be clearly
superior to the OOP approach.  ML's functors offer a typed version
of C++'s templates. Haskell, in a sense, adds convenience by making
the instantiation the template code implicet. With that convenience,
there seems to sometimes come a price, which I think you allude to
next.

>  During the process of doing that I discovered the many
> limitations of Haskell current type system.  I simply could not do what
> I wanted to do in Haskell with out resorting to hideously complex
> types.  The biggest thing that was biting be was all the ambiguity
> caused from using multiple parameter classes.
> 
> If there is enough interest I could repost this code as well as an
> explanation of the many "hacks" I had to due to get around ambiguity
> arising fro the use of multiple parameter classes and other
> limitations of Haskell.

Rather than repost all the code, could you post just enough to show the
source of the difficulty? 

Cheers,
Theo Norvell







Re: Re: OO in Haskell

1999-10-05 Thread Hamilton Richards Jr.

At 2:01 PM -0500 10/5/1999, Kevin Atkinson wrote:
...
>And I can't not agree with you more.

Delightful!

It's in the same league as Dwight Eisenhower's response (to a
press-conference question):

"I couldn't help failing to agree with you less."

--HR



--
Hamilton Richards Jr.Department of Computer Sciences
Senior Lecturer  Mail Code C0500
512-471-9525 The University of Texas at Austin
SHC 434  Austin, Texas 78712-1188
[EMAIL PROTECTED]
--








Re: OO in Haskell

1999-10-05 Thread Hamilton Richards Jr.

At 2:33 PM -0500 10/5/1999, Alex Ferguson wrote:
>... I'm unaware of any way in which C++ syntax is 'more natural',
>other than in the sense of 'for a C++ programmer', or 'cleaner' -- at all.

Having taught both C++ and Haskell for several years (each) to many
hundreds of undergraduate students from all over the world, I endorse that
sentiment enthusiastically.

One of the more clear-eyed (IMHO) and successful authors of C++ texts is
Cay Horstmann. A feature of his text, "Mastering C++" (Wiley, 1991), which
I like is the section, appearing at the end of each chapter, entitled
"Pitfalls" (the idea comes from Andrew Koenig's book, "C Traps and
Pitfalls").  Some of the pitfalls describe ordinary programming mistakes,
but the majority are "gotchas" caused by shortcomings in C++'s design of
(many of them faithful copies of mistakes in C). Horstmann gives a very
entertaining lecture on the topic of C++ pitfalls; a full hour does not
suffice to mention them all.

With time and patience, one can learn to think in C++, and it's quite
possible to write beautiful and efficient code in it (I'm a bit partial to
some of my own efforts). I believe, however, that one cannot fully
appreciate a programming language's strengths amnd weaknesses until one has
tried teaching it to a variety of students. Having done that, I'm here to
attest that Haskell's syntax --to say nothing of its semantics-- is much
cleaner, much simpler, and much easier to learn.

--HR



--
Hamilton Richards Jr.Department of Computer Sciences
Senior Lecturer  Mail Code C0500
512-471-9525 The University of Texas at Austin
SHC 434  Austin, Texas 78712-1188
[EMAIL PROTECTED]
--








Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

On Tue, 5 Oct 1999, Alex Ferguson wrote:

> > 3) Encapsulation.  You can't have private and protected members.  Some
> > of this can be done using modules.  However it is more work.
> 
> What exactly can't be done with classes, and how, substantively, is
> it more work?

class Foo
  private: -- only members of the Foo class can see this
...
  protected: -- only mebers of the Foo class and those derived from foo
 -- can see it.
  public: -- anyone can see it

> > 4) Cleaner more natural syntax.
> 
> More like C++, you mean?

Or Java.  Although many OO things can be done in Haskell C++ and Java
syntax is more natural more doing OO.

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







Re: Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

On Tue, 5 Oct 1999, Juergen Pfitzenmaier wrote:

> Kevin Atkinson wrote:
> > Even through most problems don't truly fit in the OO paradigm, OO
> > still is extremely useful.  GUI are a prime example of what OO is good
> > for.
> point given. GUI are an area where OO is good.
> 
> > ... [OO] can greatly
> > simplify complex problems into something manageable.
> 
> point partly given. If OO solves your problem nicely than nobody
> gets out to see if something other -- say functional, declarative ... --
> would solve it even better. The one thing I have against OO is the hype
> - some sell it as a swiss army knife and others believe that. And so
> they miss the real point about programming: Programming is the quest
> for the insight. Insight into a problem and understanding what tools
> are there to solve it.

I fully agree with you here.  However if someone speeds all there time
looking for the *perfect* solution no one will get any real work done.
There is always a better solution to the problem but sometimes you
just have to you with what works.  _My_ problem with many of my
programming projects is that I spend too much time looking for the
perfect solution and not enough time actually coding.

> If I use OO without looking for other ways just because it works I'm
> doing my job but I'm not doing *good* work. If I use OO because I know
> it is justified compared to the other ways than I'm in the position
> to do a good work (there's still room to fail but it's less likely).

And I can't not agree with you more.  You are preaching to the wrong
person here.

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







Limititions of Haskell Type System (was Re: OO in Haskell)

1999-10-05 Thread Kevin Atkinson

On Tue, 5 Oct 1999, Theo Norvell wrote:

> On Tue, 5 Oct 1999, Kevin Atkinson wrote:
> 
> > If there is enough interest I could repost this code as well as an
> > explanation of the many "hacks" I had to due to get around ambiguity
> > arising fro the use of multiple parameter classes and other
> > limitations of Haskell.
> 
> Rather than repost all the code, could you post just enough to show the
> source of the difficulty? 

Ok, here is the biggest one.

I have a generic mutable array class which has a few basic methods:

class MArray ... where
  newArray :: Int -> m (mutArray st el)
  write :: mutArray st el -> Int -> el -> m ()
  read :: mutArray st el -> Int -> m el
  freeze :: m mutArray st el -> m array el 
  thaw ::  m array el -> m mutArray st el

and it turns out that it is possible to create a full fledge
non-mutable array based on the mutable array class with the help of
this method:

  thawRunFreeze :: Array el 
-> (m mutArray st el -> m ())
-> Array el

Which will, as the signature suggests and name suggest, thaw an array,
perform some actions on the mutable array, and then freeze it,
returning the new array.

The only problem is that it is impossible to have a generic
thawRunFreeze method in Haskell.  So I had to resort to some ugly code
generation.

If I have time I will put together a more detailed report of exactly
Why Haskell can't do it.  However in the mean time this should give
you an idea of the sharp limitations of Haskell current type system.

The original post can be found at
http://www.dcs.gla.ac.uk/mail-www/haskell/msg01592.html.

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







Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

On Tue, 5 Oct 1999, George Russell wrote:

> Perhaps I'm being stupid.  (It certainly wouldn't be the first time!)
> But what does OO give me that I can't get with existential types (in
> datatype definitions) and multiparameter type classes? The latter seem
> to me much more powerful, since I can add dancing and singing methods
> to objects without having to go back to the original class definition.

1) Dynamic types.  You can't cast up.  That is you can't recover the
original type from an object in a existential collection.  You need to
use a dynamic type library for that.  And the library proved with hugs
and ghc leaves a lot to be desired.  In an OO langauge all classes
automatically cary dynamic typing information.

2) More specific types, you can't _easilly_ call the more general type.
For example in OO this is very commen:

class Base
  virtual foo()
do stuff

class Derived, extends Base
  foo()
call Base::foo()
doo stuff

3) Encapsulation.  You can't have private and protected members.  Some
of this can be done using modules.  However it is more work.

4) Cleaner more natural syntax.

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







Re: OO in Haskell

1999-10-05 Thread S. Alexander Jacobson

On Tue, 5 Oct 1999, George Russell wrote:
> Perhaps I'm being stupid.  (It certainly wouldn't be the first time!)
> But what does OO give me that I can't get with existential types
> (in datatype definitions) and multiparameter type classes? The latter
> seem to me much more powerful, since I can add dancing and singing methods
> to objects without having to go back to the original class definition.

Encapsulation of state.

-Alex-

___
S. Alexander Jacobson   Shop.Com
1-212-697-0184 voiceThe Easiest Way To Shop







Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

On Tue, 5 Oct 1999, Juergen Pfitzenmaier wrote:

> Alex Ferguson wrote:
> > That C++ has a very poor type system.
> 
> and Kevin Atkinson wrote in response:
> > You are going to have to justify it as I thing C++ and Java has a VERY
> > good type system minus the implicit typing system. In fact I *like*  the
> > C++ typeing system better than I do Haskell's in many cases.
> 
> C++ has no type *system*. At least I can see no *systematic* approach
> to types in C++.

Could you please elbeare here so that I can be sure of what you are
talking about.

> I like C++ but only for small one-shot programs there thinking about
> a good long-term solution would take me longer than hacking a dirty
> solution in C++. The good thing in C++ is the broken type system --
> I can twist it any way I like in case of a *minor* flaw in the
> design of my program. That twisting can be very hard in strongly
> typed languages.

What one person considers twisting is what another person considers
a very elegent solution.

In case you have not figured out a couple of months ago I posted the
beginnings of a generic container and algorithm collection for
Haskell.  Duren the process of doing that I discovered the many
limitations of Haskell current type system.  I simply could not do what
I wanted to do in Haskell with out resorting to hideously complex
types.  The biggest thing that was biting be was all the ambiguity
caused from using multiple parameter classes.

If there is enough interest I could repost this code as well as an
explanation of the many "hacks" I had to due to get around ambiguity
arising fro the use of multiple parameter classes and other
limitations of Haskell.


I plan on eventually getting back to it once there is a working
implementation of a better solution to multiple parameter classes.

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







Re: OO in Haskell

1999-10-05 Thread Kevin Atkinson

On Tue, 5 Oct 1999, Juergen Pfitzenmaier wrote:

> Kevin Atkinson wrote:
> > Do you not like OO at all?
> 
> what good is OO for ? ;) OO gives me a framework/language to talk
> about objects (read entities) and claims that with objects programmers
> have the right tool to model real-world entities.
> But the main thing in the real-world are *not* entities, the whole
> thing is about applying some function to these - possibly nonexisting -
> entities. And OO gives me no tools to handle these functions.
> 
> ok a bit provocative. I still see something good in OO. It provides
> a level of abstraction that wasn't there before but it's not enough.

Even through most problems don't truly fit in the OO paradigm, OO
still is extremely useful.  GUI are a prime example of what OO is good
for.  OO programs often tend to be very reusable in other cortexes--
something that Haskell scored lower than when compared to C++ and Ada
in the paper "Haskell vs. Ada vs. C++ vs. Awk vs. ..., An Experiment
in Software Prototyping Productivity" by Paul Hudak and Mark P. Jones
(http://www.haskell.org/practice.html).

And no I don't think OO is the solution to ALL problems and I
definitely do not think that everything belongs in a class (like Java
does).  However, in many real word situations, it can greatly
simplify complex problems into something manageable.

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







Re: OO in Haskell

1999-10-05 Thread Michael Hobbs

Juergen Pfitzenmaier wrote:
> 
> Kevin Atkinson wrote:
> > Do you not like OO at all?
> 
> what good is OO for ? ;) OO gives me a framework/language to talk
> about objects (read entities) and claims that with objects programmers
> have the right tool to model real-world entities.
> But the main thing in the real-world are *not* entities, the whole
> thing is about applying some function to these - possibly nonexisting -
> entities. And OO gives me no tools to handle these functions.
> 
> ok a bit provocative. I still see something good in OO. It provides
> a level of abstraction that wasn't there before but it's not enough.
> 
> ciao pfitzen

It's debatable whether or not a FP _really needs_ OO. But there are 2
things that come out of OO, which can be really nice: overloading and
inheritance. True, they aren't strictly necessary when you have
polymorphic types. But sometimes, syntactic sugar really is a Good
Thing. I don't have to retype or copy-and-paste. Neither do I have to
rework all the functions to be more "generic". It may not be good
programming practice, but hey, we can't always be perfect.

- Michael Hobbs






Re: OO in Haskell (was Re: What *I* thinks Haskell Needs.)

1999-09-29 Thread Fergus Henderson

On 28-Sep-1999, Andreas C. Doering <[EMAIL PROTECTED]> wrote:
> > The trickier part is putting different types into a heterogenous
> > collection, and then manipulating according to their _individual_ types.
> 
> If we are already at this point, a naive question:
> 
> Assume we add the type of all types. Hence we can declare a 
> function, say from type to string, we can manipulate types and 
> so forth. 
> This would us allow to deal with this situation. 
> What is the danger, what would it break?

The Hugs/ghc library already includes that.
See the "Type" type and the "Typeable" typeclass,
sections 5.1 and 5.2 in the Hugs/ghc extensions library documentation.

It's sufficient for doing dynamic type casts, but it's
not sufficient for doing dynamic type class casts.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.






Re: OO in Haskell (was Re: What *I* thinks Haskell Needs.)

1999-09-28 Thread Andreas C. Doering

> The trickier part is putting different types into a heterogenous
> collection, and then manipulating according to their _individual_ types.

If we are already at this point, a naive question:

Assume we add the type of all types. Hence we can declare a 
function, say from type to string, we can manipulate types and 
so forth. 
This would us allow to deal with this situation. 
What is the danger, what would it break?

Ex.: 

tuple_arity:: Type -> Maybe Int
tuple_arity () = Just 0
tuple_arity (a,b) = Just 1
...
tuple_arity [a] = Nothing

Of course we would have to add a huge amount 
of predefined functions to work with types, but I guess most of them are
already defined in the compiler/interpreter sources. 

Andreas
---
Andreas C. Doering
Medizinische Universitaet zu Luebeck
Institut fuer Technische Informatik
Ratzeburger Allee, Luebeck, Germany
Email: [EMAIL PROTECTED]
Home: http://www.iti.mu-luebeck.de/~doering 
"The fear of the LORD is the beginning of ... science" (Proverbs 1.7)







Re: OO in Haskell (was Re: What *I* thinks Haskell Needs.)

1999-09-28 Thread Alex Ferguson

> From [EMAIL PROTECTED]  Mon Sep 27 18:50:33 1999
> X-Authentication-Warning: sun00pg2.wam.umd.edu: kevina owned process doing -bs
> Date: Mon, 27 Sep 1999 13:50:59 -0400 (EDT)

Kevin Atkinson:
> You have a collection of Shapes.  Some of these shapes are circles,   
> however, others are rectangle.  Occasionally you will need to extract
> these specific shapes form the collection of generic shapes as there is no   
> way to find the length and width of a generic shape, only its area and
> circumference.  So I need to cast the objects in shapes that are *really*
> rectangles back up to rectangles.
> 
> 1) test for the true type of the object
> 2) cast it back up to its true type

There's no need for a 'cast' here, as Shape can be represented as a
class.  The trickier part is putting different types into a heterogenous
collection, and then manipulating according to their _individual_ types.
Unless you want to restrict yourself to a particular set of possible
types (in which case it's straightforward, anyway), this seems to me
like it _is_ a case of dynamic programming.


> > I'm aware that Haskell doesn't precisely ape that sorts of 'OOP
> > style' that the likes of C++ admits  What I've yet to see is any
> > argument that this is anything other than the wisest possible decision...

> And by this you mean...

That C++ has a very poor type system.

Slán,
Alex.






Re: OO in Haskell (was Re: What *I* thinks Haskell Needs.)

1999-09-27 Thread Kevin Atkinson

Alex Ferguson wrote:
> 
> Kevin Atkinson:
> > You have a collection of Shapes.  Some of these shapes are circles,
> > however, others are rectangle.  Occasionally you will need to extract
> > these specific shapes form the collection of generic shapes as there is no
> > way to find the length and width of a generic shape, only its area and
> > circumference.  So I need to cast the objects in shapes that are *really*
> > rectangles back up to rectangles.
> >
> > 1) test for the true type of the object
> > 2) cast it back up to its true type
> 
> There's no need for a 'cast' here, as Shape can be represented as a
> class.  The trickier part is putting different types into a heterogenous
> collection, and then manipulating according to their _individual_ types.
> Unless you want to restrict yourself to a particular set of possible
> types (in which case it's straightforward, anyway), this seems to me
> like it _is_ a case of dynamic programming.

Yes but it is ALSO a case of typical things one does with OO.  Except
with OO it is very natural as you just stick them all into a container
of Shapes.  When you need to access the identical type of an object you
use simply case up once you are sure what the REAL type of the object
is.  Also in OO you can
have a class heritage like this.

Shape
  Circler
Oval
Circle
  Polygon

Now than suppose the Circler has a method to find the maxim and minimum
radius of its shape.  Now you have a collection of Shapes.  For all
those that are Circler you would like to find this information.  In
these situation it is NOT necessary to recover the complete type of the
object, but merely to cast it up one level to Circler so that you can
find the this information.  Can dynamic programming handle this?  And
how?

> > > I'm aware that Haskell doesn't precisely ape that sorts of 'OOP
> > > style' that the likes of C++ admits  What I've yet to see is any
> > > argument that this is anything other than the wisest possible decision...
> 
> > And by this you mean...
> 
> That C++ has a very poor type system.

You are going to have to justify it as I thing C++ and Java has a VERY
good type system minus the implicit typing system. In fact I *like*  the
C++ typeing system better than I do Haskell's in many cases.

Do you not like OO at all?
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/