Re: What *I* thinks Haskell Needs.

1999-09-29 Thread Fergus Henderson

On 28-Sep-1999, Alex Ferguson <[EMAIL PROTECTED]> wrote:
> 
> It would be interesting to investigate adding 'dynamic classes' to
> Haskell, but it introduces the issue of what type to give the resulting
> function:  I think I'd want to clearly distinguish between a genuine
> (boundedly) polymorphic function, and one which covertly does a case
> analysis of the (sub-)classes of its argument.

Agreed.  The current Hugs/ghc Dynamic library does that,
by prefixing the type of the latter kind of function with
constraints of the form `Typeable t =>'.
If some language extension were introduced for dynamic type
class casts, then the compiler should infer a type constraint
of that form (`Typeable t'), or something along those lines,
for any code using that extension.

-- 
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-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: What *I* thinks Haskell Needs.

1999-09-28 Thread Alex Ferguson


Fergus Henderson:
> One example is the case where you already have existing code that
> creates a heterogenous collection, and you want to extract an
> element from that heterogenous collection, and then if it is
> a member of a particular type class perform action A otherwise
> perform action B, *without* modifying the existing code.

OK, it sounds like this would indeed require 'tweaking' (at least)
the existing code, it the representation of the collection doesn't
admit the required operations.


> The dynamic typing extensions in GHC/Hugs will let you cast to a particular
> type, but they won't let you check whether that a dynamically typed value
> is a member of a particular type class, or cast such a value to a type class
> constrained type.

I had noticed that apparent limitation myself, while pondering a certain
problem (to which it turns out that (I think) existential types are
an adequate solution, in that case).

It would be interesting to investigate adding 'dynamic classes' to
Haskell, but it introduces the issue of what type to give the resulting
function:  I think I'd want to clearly distinguish between a genuine
(boundedly) polymorphic function, and one which covertly does a case
analysis of the (sub-)classes of its argument.

Cheers,
Alex.






RE: What *I* thinks Haskell Needs

1999-09-28 Thread Adrian Hey

On Mon 27 Sep, Frank A. Christoph wrote:
> I must admit that I don't like the idea of determining a value based on its
> type, at least in a language like Haskell. For me, functional programming is
> about how to write programs combinatorially, and justifying your hypotheses
> by encoding their proofs; so a type is something that ought to be uniquely
> derivable from a value, not the other way around. Haskell's class system
> already goes too far against this idea for my taste.
> 
> I know that some people do not feel this way, however.

I agree. This is one of the things I was griping about many moons ago
on the 'pattern match success changes types' thread, but your statement
above is far more eloquent.

This whole overloading business seems to complicate the Haskell type
system unnecessarily, and makes programs harder to understand, 
not easier, in my humble opinion. I think I would prefer something
closer to the ML approach.

Regards
-- 
Adrian Hey







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: What *I* thinks Haskell Needs.

1999-09-28 Thread Fergus Henderson

On 27-Sep-1999, Alex Ferguson <[EMAIL PROTECTED]> wrote:
> 
> Fergus Henderson, replying to me:
> > ghc does not offer any facility for type class casts.
> 
> I'm not clear what's meant by this;  are we speaking of some sort of
> conversion to a common _type_, in some manner?

Well, roughly speaking, I'm talking about a family of built-in functions
`cast', where `C' is some type class, having type

data CastResult = Failed | C t => Succeeded t
cast :: t -> CastResult

and with the semantics

cast (x::t) | C t   = Succeeded x
   | otherwise = Failed

where `C t' in the guard is to be interpreted as a boolean expression
that returns True if the type `t' is an instance of the class `C',
and False otherwise.  Here `t' is the type of the argument `x'.

-- 
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: What *I* thinks Haskell Needs.

1999-09-28 Thread Fergus Henderson

On 27-Sep-1999, Alex Ferguson <[EMAIL PROTECTED]> wrote:
> 
> Fergus Henderson, replying to me:
> > > That's far from clear.  Certainly, I don't think it's likely to be
> > > reasonably possible a conversative extension.
> 
> [...]
> > Ad-hoc overloading and type inference don't mix so well, because
> > you can easily get ambiguities which the compiler cannot resolve.
> > However, the user can add explicit type annotations where necessary
> > to resolve the ambiguities.
> 
> If you can can ambiguities arising in what would otherwise be a well-typed
> Haskell program, then that'd make it a non-conservative (which I shall
> spell right, this time) extension, in my book.

No, you only get ambiguities if there are two symbols that have the same
name both in scope at the same time, and currently that can't happen in
a well-typed Haskell program.  So I believe it would be conservative,
at least up until the point where you start modifying the Haskell
standard library to take advantage of it...

-- 
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: What *I* thinks Haskell Needs.

1999-09-28 Thread Fergus Henderson

On 27-Sep-1999, Alex Ferguson <[EMAIL PROTECTED]> wrote:
> 
> Kevin Atkinson, replying to me:
> 
> > > If I understand you correctly, then the best way of doing this would be
> > > with existentially (boundedly) quantified data types, currently a
> > > non-standard extention present in hbc (and I think, ghc, these days, not
> > > sure if it's with the same generality.)
> > 
> > existentially (boundedly) quantified data types can not cast up.
> 
> 'Cast up' to what?  If you can't write a class context that descibes
> the relatedness of everything you want to put in a heterogenous collection,
> then I'm inclined to doubt if it isn't more heterogenous than is
> sensible.
...
> I don't see how this relates to anything other than heterogenous collections;
> perhaps an example?

One example is the case where you already have existing code that
creates a heterogenous collection, and you want to extract an
element from that heterogenous collection, and then if it is
a member of a particular type class perform action A otherwise
perform action B, *without* modifying the existing code.

The same issue comes up if you have an existing interface
that invokes a callback function with a polymorphic type,
and you want some particular instance of this callback function
to examine the polymorphically typed value that it was given
and to perform action A if it is a member of a particular
type class and action B otherwise.

Typically action A will be some action that makes use of the methods
in the type class, and action B will be a fall-back algorithm.

> > In order to do that you would ALSO need to use the dramatic typing
> > extensions found in the GHC/Hugs library.

I think you mean the _dynamic_ typing extensions ;-)

The dynamic typing extensions in GHC/Hugs will let you cast to a particular
type, but they won't let you check whether that a dynamically typed value
is a member of a particular type class, or cast such a value to a type class
constrained type.

-- 
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: What *I* thinks Haskell Needs.

1999-09-28 Thread Fergus Henderson

On 27-Sep-1999, Alex Ferguson <[EMAIL PROTECTED]> wrote:
> 
> Kevin Atkinson:
> > Yes but often putting things in type classes is tedious to do.  I also
> > want to be able to overload not only on the TYPE of parameters but also
> > on the NUMBER of parameters.  It IS possible to do these things and it
> > DOES make sense in a curing system.
> 
> That's far from clear.  Certainly, I don't think it's likely to be
> reasonably possible a conversative extension.

I think it could be.
However, whether it is in "the spirit of Haskell" is another question.

Mercury supports both type classes and ad-hoc overloading.
You can define two different symbols with the same name in
different modules and import them into another module
and the compiler will use your type declarations to disambiguate.
You can define the same symbol with different arities (number of parameters)
within a single module, and the compiler will use the types and the
context to disambiguate.

Ad-hoc overloading and type inference don't mix so well, because
you can easily get ambiguities which the compiler cannot resolve.
However, the user can add explicit type annotations where necessary
to resolve the ambiguities.  And I find this preferable to making
the explicit type annotations part of the symbol names, which is
what I currently tend to do when writing Haskell.

(Note that the Mercury compiler currently does not do nearly as good
a job of dealing with type inference in the presense of ambiguities
as it could do.)

> > > > 2) Support for TRUE OO style programming.
> 
> > No. I mean being able to do things such as.
> > 
> > Have a collection of object of a common base class AND be able to up
> > cast them when necessary.
> 
> If I understand you correctly, then the best way of doing this would be
> with existentially (boundedly) quantified data types, currently a
> non-standard extention present in hbc (and I think, ghc, these days, not
> sure if it's with the same generality.)

ghc does not offer any facility for type class casts.
As far as I'm aware, hbc doesn't either, but I don't know for sure.

-- 
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 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/






Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Alex Ferguson


Fergus Henderson, replying to me:
> > That's far from clear.  Certainly, I don't think it's likely to be
> > reasonably possible a conversative extension.

[...]
> Ad-hoc overloading and type inference don't mix so well, because
> you can easily get ambiguities which the compiler cannot resolve.
> However, the user can add explicit type annotations where necessary
> to resolve the ambiguities.

If you can can ambiguities arising in what would otherwise be a well-typed
Haskell program, then that'd make it a non-conservative (which I shall
spell right, this time) extension, in my book.   I guess you could
always choose the 'Old Haskell Compliant' option, though, in such
cases, though that could be a mite confusing.  (As if the MR isn't,
mind you...)


> ghc does not offer any facility for type class casts.

I'm not clear what's meant by this;  are we speaking of some sort of
conversion to a common _type_, in some manner?

Cheers,
Alex.






Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Alex Ferguson


Kevin Atkinson, replying to me:

> > If I understand you correctly, then the best way of doing this would be
> > with existentially (boundedly) quantified data types, currently a
> > non-standard extention present in hbc (and I think, ghc, these days, not
> > sure if it's with the same generality.)
> 
> existentially (boundedly) quantified data types can not cast up.

'Cast up' to what?  If you can't write a class context that descibes
the relatedness of everything you want to put in a heterogenous collection,
then I'm inclined to doubt if it isn't more heterogenous than is
sensible.


> In order to do that you would ALSO need to use the dramatic typing
> extensions found in the GHC/Hugs library.

I don't see how this relates to anything other than heterogenous collections;
perhaps an example?


> The point that class hierarchy isn't precisely _type_ hierarchy is
> exactly the point I am trying to get gate Haskell needs to also be able to
> support a class hierarchy if it is to really support OO style 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...

Cheers,
Alex.






Qualified identifiers (was: RE: What *I* thinks Haskell Needs.)

1999-09-27 Thread Frank A. Christoph

> For bigger things which
> you want to identify, you can either use qualified module identifiers, or
> Haskell's type classes which at least let you establish and codify a
> motivation for using the same name for distinct things (namely, that their
> types are equivalent under a particular relation).

BTW, since I mentioned it, let me get on my hobby horse and implore other
Haskell programmers to _please_ make more use of the qualified ID syntax!
Haskell has had this feature for quite some time now, but I hardly ever see
it used...

Especially in modules that import a lot of other modules, it's

* easier to _recognize_ an identifier if it's prefixed by a module ID rather
than look through all the imported modules, and

* easier to _modify_ a module if all you need to do to pull in a new value
is to use it, rather than scrolling up, and adding it to the list of
identifiers in something like "import M (...)".

This is standard practice in both SML and Ocaml. (In fact, I would rather
not have to declare things like "import qualified M" at all...)

If you have a long module name, declare an alias:

  import qualified LongModuleName as LMN

BTW, another advantage of this syntax is that identifiers within their own
defining module get shorter, and consequently it gets easier to read. For
example, don't define "addToFM"; define "addTo" and then do "import
FiniteMap as FM". Sometimes this means having to hide Prelude identifiers
and qualify them at use (as it would be with "lookupFM" in GHC's FiniteMap
module) but is that such a great price to pay...?

Please. Pretty please? Pretty please with sugar on top?

--FC

P.S. Except infix combinators. These are ugly when you qualify them.







Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Alex Ferguson


Kevin Atkinson:
> Yes but often putting things in type classes is tedious to do.  I also
> want to be able to overload not only on the TYPE of parameters but also
> on the NUMBER of parameters.  It IS possible to do these things and it
> DOES make sense in a curing system.

That's far from clear.  Certainly, I don't think it's likely to be
reasonably possible a conversative extension.


> > > 2) Support for TRUE OO style programming.

> No. I mean being able to do things such as.
> 
> Have a collection of object of a common base class AND be able to up
> cast them when necessary.

If I understand you correctly, then the best way of doing this would be
with existentially (boundedly) quantified data types, currently a
non-standard extention present in hbc (and I think, ghc, these days, not
sure if it's with the same generality.)


> Be able to override methods and ALSO be able for the overriding methods
> to call there parent methods.  

If by that you mean a more flexible and general means of specifying
defaults, I'd agree.  Method definitions don't have a strict 'parent'
in the usual OO sense, since the class hierarchy isn't precisely a
_type_ hierarchy (and a good thing too, IMO), so I'm not entirely
confident about what you mean by parent method, though.


> > > 4) Being able to write
> > >   do a <- getLine
> > >  b <- getLine
> > >  proc a b
> > > as
> > >   proc getLine getLine
> > > and the like.

> proc getLine getLine will be interpreted as the do notion above.  With a
> powerful enough type system it WILL be possible.  I will go into details
> later if anyone is interested.

Please do.  This is something that it would be nice to do, on one level:
occassionally one has to 'monadise' part of one's program, and due to
the above effect, end up driving a coach and four through the rest of
one's code.

But it's a somewhat subtle subtle to address without either a) severely
breaking the type system;  and b) totally confusing the user, if the
result involves quite different entities being denoted by the same
symbol.  The question is, if one is using the same symbol for a
collection of semantics objects, then sensibly, they must be _related_
things, so, how best to capture that relatedness?  The OOP answer
of 'not at all' is a very poor one, IMO.

Cheers,
Alex.






RE: What *I* thinks Haskell Needs.

1999-09-27 Thread Frank A. Christoph

> > I find that if you make liberal use of higher-order constructs and
> > modularize your code, then the need to do explicit binding is
> not so much of
> > a problem. Then again, I am the sort of person who uses "let"
> and "where"
> > whenever he can to name subexpressions as well...
>
> But the point is I would like the type system to AUTOMATICALLY do this
> for me so that I don't have to memorize/lookup a bunch of higher order
> functions.  True ONCE you know them all they are not difficult to use
> but to a new programmer all these (seemly unnecessary) high functions
> can make doing the simplest task quite difficult.  So the new programmer
> will just use the do

Doesn't it also make it easier on new users that things with different
semantics have different names? It seems like true ad hoc overloading would
only make things more confusing; certainly the error messages would become
more difficult to understand.

It would eliminate the need to think up new names in some circumstances, but
if you compare the amount of time spent in doing that when you write a
program, to the amount of time you might spend trying to figure out why your
program won't compile, or worse, compiles but runs incorrectly (I have a
hard enough time, sometimes, figuring out what the type of something is in
the presence of functors and MPTC!) Experiential reports and empirical data
would be valuable here.

> This is why I belive in true adhoc overloading.
>
> 1) so that you don't have to make up names just reuse the old ones
> 2) make using standard library functions easier to use because there
> will be a lot fewer names to lookup/memorize.

1) For intermediate values which are not so important, you can get around
inventing new names by using scoping and shadowing. For bigger things which
you want to identify, you can either use qualified module identifiers, or
Haskell's type classes which at least let you establish and codify a
motivation for using the same name for distinct things (namely, that their
types are equivalent under a particular relation). That's already four
mechanisms for dealing with overloading.

2) It would also be useful if documentation were easier to access and use
(which has been a recent topic).

I must admit that I don't like the idea of determining a value based on its
type, at least in a language like Haskell. For me, functional programming is
about how to write programs combinatorially, and justifying your hypotheses
by encoding their proofs; so a type is something that ought to be uniquely
derivable from a value, not the other way around. Haskell's class system
already goes too far against this idea for my taste.

I know that some people do not feel this way, however.

--FC







RE: What *I* thinks Haskell Needs.

1999-09-27 Thread Carlos Camarao de Figueiredo


> Doesn't it also make it easier on new users that things with
> different semantics have different names?

The main benefit of overloading is (in my view) to support constrained
polymorphism: an operation (or value) can be used for all types for
which there are certain (other) operations (or values) defined.

Usual example: it is easy (even for new users) to define

  square x = x * x

and think of square as a function that performs x * x for all types
for which * is defined. Having to define things like

  square_int:: Int -> Int
  square_int x = x * x

  square_float:: Float -> Float
  square_float x = x * x

(or perhaps not making "*" overloaded?) is perhaps not so easy to
justify (for new users). Or perhaps it is, in a polymorphic language
without constrained polymorphism...

Type classes allow definitions such as square x = x * x, but
unfortunately it requires programmers to specify (anticipate) what is
the "reasonable" most general type of "*". Type a->a->a may adequately
cover all possible adequate uses of "*", but in other cases some
possible uses of an overloaded symbol might be excluded only because
the programmer did not anticipate well. In fact, this a priori
anticipation is not necessary at all. The type of square may be
inferred, from the definitions of "*" that occur in the relevant
context. (With separate compilation, this relevant context is given
according to the import interface of a compilation unit.) (See also
"Type Inference for Overloading without Restrictions, Declarations or
Annotations", http://www.dcc.ufmg.br/~camarao.)

In my view this is no minor issue... Similar remarks would apply for
overloading monadic operations, allowing, for example, the definition
of modular monadic interpreters (by the way, without wrapping and
unwrapping with newtypes as well...).

Carlos









RE: What *I* thinks Haskell Needs.

1999-09-27 Thread Frank A. Christoph

Oops, I left out the type context:

> liftM2' :: (Monad m) => (a -> b -> m c) -> (m a -> m b -> m c)
> liftM2' proc m1 m2 = do
>   v1 <- m1
>   v2 <- m2
>   proc v1 v2

Oh, and here is a nicer definition:

  import Monad

  liftM2' :: (Monad m) => (a -> b -> m c) -> (m a -> m b -> m c)
  liftM2' proc m1 m2 = join $ liftM2 proc m1 m2

Maybe jLiftM2 is a better name?

--FC







RE: What *I* thinks Haskell Needs.

1999-09-27 Thread Frank A. Christoph

> Here is a laundry list of things I think Haskell still needs.  By
> Haskell here I mean Haskell plus extension that are found in both hugs
> and ghc.
...
> 4) Being able to write
>   do a <- getLine
>  b <- getLine
>  proc a b
> as
>   proc getLine getLine
> and the like.  I don't know the number of times that I get REALLY sick
> of having to explicitly bind everything to a variable.  Monads do a very
> good job of supporting imperative style.  Now lets make them less
> tedious to use.

You could define proc':

proc' act1 act2 = do
  v1 <- act1
  v2 <- act2
  proc v1 v2

so you can write:

 proc' getLine getLine

When proc returns a value rather than a computation, i.e., proc :: a -> b ->
c, and c is not monadic, then you can just write Monad.liftM2 proc getLine
getLine.

You could define a higher-order version of proc' above in the same vein:

liftM2' :: (a -> b -> m c) -> (m a -> m b -> m c)
liftM2' proc m1 m2 = do
  v1 <- m1
  v2 <- m2
  proc v1 v2

In simpler cases where proc takes only one argument, you can avoid thinking
up new names by currying:

  getLine >>= proc

I find that if you make liberal use of higher-order constructs and
modularize your code, then the need to do explicit binding is not so much of
a problem. Then again, I am the sort of person who uses "let" and "where"
whenever he can to name subexpressions as well...

--FC







Ad-hoc overloading in Haskell (was Re: What *I* thinks Haskell Needs.)

1999-09-27 Thread Kevin Atkinson

On Tue, 28 Sep 1999, Fergus Henderson wrote:

> > That's far from clear.  Certainly, I don't think it's likely to be
> > reasonably possible a conversative extension.
> 
> I think it could be.
> However, whether it is in "the spirit of Haskell" is another question.
> 
> Mercury supports both type classes and ad-hoc overloading.
> You can define two different symbols with the same name in
> different modules and import them into another module
> and the compiler will use your type declarations to disambiguate.
> You can define the same symbol with different arities (number of parameters)
> within a single module, and the compiler will use the types and the
> context to disambiguate.
> 
> Ad-hoc overloading and type inference don't mix so well, because
> you can easily get ambiguities which the compiler cannot resolve.
> However, the user can add explicit type annotations where necessary
> to resolve the ambiguities.  And I find this preferable to making
> the explicit type annotations part of the symbol names, which is
> what I currently tend to do when writing Haskell.
> 

I am glad that SOMEONE agrees with me.  Anyone else

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







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

1999-09-27 Thread Kevin Atkinson

On Mon, 27 Sep 1999, Alex Ferguson wrote:

> Kevin Atkinson, replying to me:
> 
> > > If I understand you correctly, then the best way of doing this would be
> > > with existentially (boundedly) quantified data types, currently a
> > > non-standard extention present in hbc (and I think, ghc, these days, not
> > > sure if it's with the same generality.)
> > 
> > existentially (boundedly) quantified data types can not cast up.
> 
> 'Cast up' to what?  If you can't write a class context that descibes
> the relatedness of everything you want to put in a heterogenous collection,
> then I'm inclined to doubt if it isn't more heterogenous than is
> sensible.

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

> > In order to do that you would ALSO need to use the dramatic typing
> > extensions found in the GHC/Hugs library.
> 
> I don't see how this relates to anything other than heterogenous collections;
> perhaps an example?

A collection of objects with existential types very often is a
heterogeneous collections.

> > The point that class hierarchy isn't precisely _type_ hierarchy is
> > exactly the point I am trying to get gate Haskell needs to also be able to
> > support a class hierarchy if it is to really support OO style 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...

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







Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Kevin Atkinson

On Mon, 27 Sep 1999, Alex Ferguson wrote:

> > > > 2) Support for TRUE OO style programming.
> 
> > No. I mean being able to do things such as.
> > 
> > Have a collection of object of a common base class AND be able to up
> > cast them when necessary.
> 
> If I understand you correctly, then the best way of doing this would be
> with existentially (boundedly) quantified data types, currently a
> non-standard extention present in hbc (and I think, ghc, these days, not
> sure if it's with the same generality.)

existentially (boundedly) quantified data types can not cast up.  In order
to do that you would ALSO need to use the dramatic typing extensions found  
in the GHC/Hugs library.  Unfortunately the dramatic typing library leaves
a lot to be desired.

> > Be able to override methods and ALSO be able for the overriding methods
> > to call there parent methods.  
> 
> If by that you mean a more flexible and general means of specifying
> defaults, I'd agree.  Method definitions don't have a strict 'parent'
> in the usual OO sense, since the class hierarchy isn't precisely a
> _type_ hierarchy (and a good thing too, IMO), so I'm not entirely
> confident about what you mean by parent method, though.

The point that class hierarchy isn't precisely _type_ hierarchy is
exactly the point I am trying to get gate Haskell needs to also be able to
support a class hierarchy if it is to really support OO style programming.

> > proc getLine getLine will be interpreted as the do notion above.  With a
> > powerful enough type system it WILL be possible.  I will go into details
> > later if anyone is interested.
> 
> Please do.  This is something that it would be nice to do, on one level:
> occassionally one has to 'monadise' part of one's program, and due to
> the above effect, end up driving a coach and four through the rest of
> one's code.

It has already been done to some extent in other threads.

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







Re: Existential types, was Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Arthur Gold


>Can some one please fill me in on why existential types are not
> part of Haskell 98? Probably this is answered in some paper/statement
> that I can read some where? I sort of understand them (* I am still
> learning haskell. WOrking through S.T's book right now *)  but
> not enough perhaps to know why they are not used.
>I do prefer that the language not get to much semantics from
> its type system, perhaps that  the answer is related?
> 
> Cheers

As I recall (and one of the Simons is sure to clarify the situation) it
was merely a matter (like MPTC) of "having to draw the line somewhere"
in terms of features to include in the standard. I'm pretty sure it's
due to be in the Haskell 2 (or _whatever_ they end up calling it)
standard.

--ag

-- 
Artie Gold, Austin, TX
mailto:[EMAIL PROTECTED] or mailto:[EMAIL PROTECTED]
--
"If you come to a fork in the road, take it." -- L.P.Berra






Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Kevin Atkinson

On Mon, 27 Sep 1999, George Russell wrote:

> Kevin Atkinson wrote:
> [snip]
> > 1) Support for true ad-hoc overloading.
> [snip] 
> > 2) Support for TRUE OO style programming.
> [snip]
> > 4) Being able to write
> >   do a <- getLine
> >  b <- getLine
> >  proc a b
> > as
> >   proc getLine getLine
> [snip]
> AAARRRGGH no.  I don't like overloading.  For one thing it makes it a bore
> working out what any given function call means.  Haskell takes it about as
> far as it goes, but I don't want to go any further.  For example, I would much
> prefer to maintain
>   do a <- getLine
>  b <- getLine
>  proc a b
> since all the action is clearly written out.  I don't have to know that
> getLine is an IO something and deduce automatic coercion.
> 
> If anything we should be trying to simplify Haskell's type system, not
> complicate it.  I would welcome a better way of doing multi-parameter
> type classes, but that seems to be something of a research problem
> right now.

Perhapes an implicit coercion is going two far. But i would DEFENTLY
like to say something like.

lift proc getLine getLine
lift proc "A line." getLine
lift proc "A line." "Another line."

The lift in this case makes it clear what is going on.   With current
haskell I would have had to use a seperate lift function for each case.

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







Re: Qualified identifiers (was: RE: What *I* thinks Haskell Needs.)

1999-09-27 Thread Marcin 'Qrczak' Kowalczyk

Mon, 27 Sep 1999 18:12:40 +0900, Frank A. Christoph <[EMAIL PROTECTED]> pisze:

> BTW, another advantage of this syntax is that identifiers within
> their own defining module get shorter, and consequently it gets
> easier to read. For example, don't define "addToFM"; define "addTo"
> and then do "import FiniteMap as FM".

I would prefer unifying names of FiniteMap and Array's operations into
type classes where possible, also for other types where it makes sense
(lists, sets). However don't have the whole picture in mind yet.

-- 
 __("+++$ 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-







Existential types, was Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Ronald J. Legere



On Mon, 27 Sep 1999, Alex Ferguson wrote:
> 

<* edited*>
 
> > > > 2) Support for TRUE OO style programming.
> 
> > No. I mean being able to do things such as.
> > 
> > Have a collection of object of a common base class AND be able to up
> > cast them when necessary.
> 
> If I understand you correctly, then the best way of doing this would be
> with existentially (boundedly) quantified data types, currently a
> non-standard extention present in hbc (and I think, ghc, these days, not
> sure if it's with the same generality.)


   Can some one please fill me in on why existential types are not
part of Haskell 98? Probably this is answered in some paper/statement
that I can read some where? I sort of understand them (* I am still
learning haskell. WOrking through S.T's book right now *)  but 
not enough perhaps to know why they are not used. 
   I do prefer that the language not get to much semantics from 
its type system, perhaps that  the answer is related? 

Cheers








Re: What *I* thinks Haskell Needs.

1999-09-27 Thread George Russell

Kevin Atkinson wrote:
[snip]
> 1) Support for true ad-hoc overloading.
[snip] 
> 2) Support for TRUE OO style programming.
[snip]
> 4) Being able to write
>   do a <- getLine
>  b <- getLine
>  proc a b
> as
>   proc getLine getLine
[snip]
AAARRRGGH no.  I don't like overloading.  For one thing it makes it a bore
working out what any given function call means.  Haskell takes it about as
far as it goes, but I don't want to go any further.  For example, I would much
prefer to maintain
  do a <- getLine
 b <- getLine
 proc a b
since all the action is clearly written out.  I don't have to know that
getLine is an IO something and deduce automatic coercion.

If anything we should be trying to simplify Haskell's type system, not
complicate it.  I would welcome a better way of doing multi-parameter
type classes, but that seems to be something of a research problem
right now.






Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Kevin Atkinson

"Frank A. Christoph" wrote:
> 
> > Here is a laundry list of things I think Haskell still needs.  By
> > Haskell here I mean Haskell plus extension that are found in both hugs
> > and ghc.
> ...
> > 4) Being able to write
> >   do a <- getLine
> >  b <- getLine
> >  proc a b
> > as
> >   proc getLine getLine
> > and the like.  I don't know the number of times that I get REALLY sick
> > of having to explicitly bind everything to a variable.  Monads do a very
> > good job of supporting imperative style.  Now lets make them less
> > tedious to use.
> 
> You could define proc':
> 
> proc' act1 act2 = do
>   v1 <- act1
>   v2 <- act2
>   proc v1 v2
> 
> so you can write:
> 
>  proc' getLine getLine

I know.

> When proc returns a value rather than a computation, i.e., proc :: a -> b ->
> c, and c is not monadic, then you can just write Monad.liftM2 proc getLine
> getLine.
> 
> You could define a higher-order version of proc' above in the same vein:
> 
> liftM2' :: (a -> b -> m c) -> (m a -> m b -> m c)
> liftM2' proc m1 m2 = do
>   v1 <- m1
>   v2 <- m2
>   proc v1 v2

Yes I also know.

> 
> In simpler cases where proc takes only one argument, you can avoid thinking
> up new names by currying:
> 
>   getLine >>= proc

Yes I also know.
> 
> I find that if you make liberal use of higher-order constructs and
> modularize your code, then the need to do explicit binding is not so much of
> a problem. Then again, I am the sort of person who uses "let" and "where"
> whenever he can to name subexpressions as well...

But the point is I would like the type system to AUTOMATICALLY do this
for me so that I don't have to memorize/lookup a bunch of higher order
functions.  True ONCE you know them all they are not difficult to use
but to a new programmer all these (seemly unnecessary) high functions
can make doing the simplest task quite difficult.  So the new programmer
will just use the do

This is why I belive in true adhoc overloading.

1) so that you don't have to make up names just reuse the old ones
2) make using standard library functions easier to use because there
will be a lot fewer names to lookup/memorize.
-- 
Kevin Atkinson
[EMAIL PROTECTED]
http://metalab.unc.edu/kevina/






Re: What *I* thinks Haskell Needs.

1999-09-27 Thread Kevin Atkinson

Arthur Gold wrote:
> 
> Though I am _not_ exactly a Haskell expert, I could not avoid
> commenting...
> 
> Kevin Atkinson wrote:
> >
> > Here is a laundry list of things I think Haskell still needs.  By
> > Haskell here I mean Haskell plus extension that are found in both hugs
> > and ghc.
> >
> > 1) Support for true ad-hoc overloading.  I am a *strong* believer that
> > if the context is clear for a human than it should be clear to the
> > computer.  This also includes support for default parameters as found in
> > C++.

> "True ad-hoc overloading?" Unless you restrict it to dispatch on the
> first argument, this would imply muliple-dispatch generic functions. In
> fact, this is really what multiple parameter type-classes are all about.
> So it's in there (well in the extensions, anyway).

Yes but often putting things in type classes is tedious to do.  I also
want to be able to overload not only on the TYPE of parameters but also
on the NUMBER of parameters.  It IS possible to do these things and it
DOES make sense in a curing system.

> Default parameters just don't make sense in a language that supports
> currying.

If overloading based on the NUMBER of parameters makes sense so does
default parameters as default parameters will just be syntactic sugar.

See http://www.dcc.ufmg.br/~camarao.

> > 2) Support for TRUE OO style programming.
> What is "TRUE" OO style programming? If you mean objects with mutable
> state, you're violating one of the most basic tenets of FP.

No. I mean being able to do things such as.

Have a collection of object of a common base class AND be able to up
cast them when necessary.

Be able to override methods and ALSO be able for the overriding methods
to call there parent methods.  

I believe Haskell CAN do these things however the solutions are anything
but elegant.

> > 4) Being able to write
> >   do a <- getLine
> >  b <- getLine
> >  proc a b
> > as
> >   proc getLine getLine
> > and the like.  I don't know the number of times that I get REALLY sick
> > of having to explicitly bind everything to a variable.  Monads do a very
> > good job of supporting imperative style.  Now lets make them less
> > tedious to use.

> ACK! For one thing this would mean that arguments would _always_ have to
> be evaluated left-to-right...which is completely incompatible with a
> non-strict language.

NO. NO. NO.  

proc getLine getLine will be interpreted as the do notion above.  With a
powerful enough type system it WILL be possible.  I will go into details
later if anyone is interested.

> (actually, I've never been too happy with the 'do' notation myself, as
> it to often obscures what's really going on...and I think what's really
> going on is _important_)

Maybe however it CAN be tedious.

> Further, if you're going to mess with referential transparency, what's
> the point? You might as well just use C++ (or, if things like pattern
> matching are what draws you to Haskell, take a look at Pizza or GJava.

Your missing the point.

> A note on referential transparency:

> One of the great potential benfits of an rt language--and one that at
> least I believe will be more significant as time goes on--is the
> potential for exposing parallelism. There have been some pretty cool
> papers on the subject, and as multiple processor machines become more
> and more common (as they no doubt will) the ability to parallelize at
> run-time (because you needn't do extensive code analysis) will become
> _terribly_ valuable.

I agree with you here.  You just need to get the word out as WAY to many
people don't release it (with half of those people not even knowing what
a functional programming language is)

> > So what do you Haskell experts think.

> Perhaps (and please take this as neither flame nor flame-bait) pure-lazy
> FP just ain't for you! (just as it certainly isn't the right tool for
> certain cllases of tasks).

But with some work it CAN be.

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






Re: What *I* thinks Haskell Needs.

1999-09-26 Thread Arthur Gold

Though I am _not_ exactly a Haskell expert, I could not avoid
commenting...

Kevin Atkinson wrote:
> 
> Here is a laundry list of things I think Haskell still needs.  By
> Haskell here I mean Haskell plus extension that are found in both hugs
> and ghc.
> 
> 1) Support for true ad-hoc overloading.  I am a *strong* believer that
> if the context is clear for a human than it should be clear to the
> computer.  This also includes support for default parameters as found in
> C++.
"True ad-hoc overloading?" Unless you restrict it to dispatch on the
first argument, this would imply muliple-dispatch generic functions. In
fact, this is really what multiple parameter type-classes are all about.
So it's in there (well in the extensions, anyway).
Default parameters just don't make sense in a language that supports
currying.
> 
> 2) Support for TRUE OO style programming.
What is "TRUE" OO style programming? If you mean objects with mutable
state, you're violating one of the most basic tenets of FP. 
> 
> 3) A better solution to all the unresolved overloading that comes up due
> to multi parameter type classes.
Many, if not most such difficulties associated with MPTC have to do with
the various numeric classes (Num, Fractional, etc.)...and this is
something that most definitely _is_ on the 'to-do' list, as I understand
it. 
> 
> 4) Being able to write
>   do a <- getLine
>  b <- getLine
>  proc a b
> as
>   proc getLine getLine
> and the like.  I don't know the number of times that I get REALLY sick
> of having to explicitly bind everything to a variable.  Monads do a very
> good job of supporting imperative style.  Now lets make them less
> tedious to use.
ACK! For one thing this would mean that arguments would _always_ have to
be evaluated left-to-right...which is completely incompatible with a
non-strict language. 
(actually, I've never been too happy with the 'do' notation myself, as
it to often obscures what's really going on...and I think what's really
going on is _important_)
Further, if you're going to mess with referential transparency, what's
the point? You might as well just use C++ (or, if things like pattern
matching are what draws you to Haskell, take a look at Pizza or GJava.
> 5) A rich set of standard libraries such as provided by the STL is C++.
...and they're on the way...not as quickly as anyone would like
(particularly the implementors themselves, no doubt ;-) )...
> And the points that are brought up so much that I don't even what to get
> into.
> 
> 6) speed.
> 
> 7) less memory.

A note on referential transparency:
One of the great potential benfits of an rt language--and one that at
least I believe will be more significant as time goes on--is the
potential for exposing parallelism. There have been some pretty cool
papers on the subject, and as multiple processor machines become more
and more common (as they no doubt will) the ability to parallelize at
run-time (because you needn't do extensive code analysis) will become
_terribly_ valuable.
> So what do you Haskell experts think.
Perhaps (and please take this as neither flame nor flame-bait) pure-lazy
FP just ain't for you! (just as it certainly isn't the right tool for
certain cllases of tasks).

Just my .02...
--ag
> --
> Kevin Atkinson
> [EMAIL PROTECTED]
> http://metalab.unc.edu/kevina/

-- 
Artie Gold, Austin, TX
mailto:[EMAIL PROTECTED] or mailto:[EMAIL PROTECTED]
--
"If you come to a fork in the road, take it." -- L.P.Berra