Re: Functional programming in Python

2001-05-29 Thread Marcin 'Qrczak' Kowalczyk

29 May 2001 22:44:38 +0200, Ketil Malde <[EMAIL PROTECTED]> pisze:

> Wouldn't 
> x f g
> in a Forth'ish machine mean
> g(f,x)   -- using "standard" math notation, for a change
> rather than
> g(f(x))
> ?

It depends whether f changes the value at top of the stack or only
puts something there.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


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



Re: Functional programming in Python

2001-05-29 Thread Brook Conner

On Tuesday, May 29, 2001, at 04:44  PM, Ketil Malde wrote:

> Jerzy Karczmarczuk <[EMAIL PROTECTED]> writes:
>
> Wouldn't
> x f g
> in a Forth'ish machine mean
> g(f,x)   -- using "standard" math notation, for a change
> rather than
> g(f(x))
> ?

In PostScript, a Forth derivative, it would mean g(f(x)). The 
difference comes down when tokens in the input stream are 
evaluated: as they are encountered or at the very end. The input 
stream is a queue - first in, first out (FIFO). A language *could* 
treat the input stream as a stack (LIFO), but that would require 
storing the entire stream in memory before computation could begin. 
As Forth-like languages are usually designed for embedded systems 
with low memory and processing power, a large LIFO stack including 
the entire program is contra-indicated :-) Instead PostScript (and 
other Forth-likes I've seen), treat the input stream as a FIFO 
queue. This way, the interpreter can handle tokens immediately and 
the stack doesn't get any larger than intermediate values in 
computations. And it also matches well with the serial 
communication these machines usually have with the producer of the 
program (there's a reason PostScript laser printers used serial 
ports easily enough, not parallel ones).

So, evaluation proceeds as follows:

for each item in the stream (FIFO)
evaluate it
pop items off the stack if evaluation requires it
push result(s) on to stack

So, presuming x is a variable with value "3", and f and g are 
functions of one parameter:

x is identified and its value is pushed on to the stack.

so the stream is now "f g" and the stack is now "3"

f is identified as a function. The value of x is popped off the 
stack (if f needed more than one parameter, more values would be 
popped off - in this case, resulting in an error from an empty 
stack).

The stream is now "g" and the stack is empty. The interpreter is 
loaded with the function f and the value 3.

f is evaluated with the value of x. The result is pushed onto the stack.

The stream is "g" and the stack contains the result of f(3).

g is identified as a function and the stack is popped.

The stream is empty and the stack is too. The interpreter is loaded 
with the function g and the value f(3).

g is evaluated with the value f(3). The result is pushed onto the stack.

As the stream is now empty, but the stack has items in it, a 
PostScript interpreter would typically print the contents of the 
stack.


This is of course g(f(x), not g(f,x). If the input stream was a 
stack, too, then "g" would be evaluated first. If g took two 
arguments, it would produce g(f,x). If g took one argument, it 
would produce g(f). If that was a function, then it would continue 
with (g(f))(x), otherwise it would end with a stack containing two 
items: g(f) on top of x.

The way you get g(f,x) in PostScript or other forths is quoting (as 
in Lisp). PostScript handles this with a /slash for a single token 
or {braces} for lists. Either can be evaluated later: if it's a 
stream of tokens, then those are evaluated (FIFO). So, procedure 
definition in PostScript looks like this:

/inches { 72 * } def

which pushes the symbol "inches" onto the stack and then the list 
of tokens "72 *"  onto the stack (PostScript's native unit is the 
point, defined as 1/72 of an inch). "def" pops the top of the stack 
and attaches it as a value to the variable named in the symbol next 
in the stack (no symbol equals an error). Later, a statement like 
"3 inches" (an unusually readable statement in a Forth-like 
language :-) is equivalent to "3 {72 *}" which is equivalent to "3 
72 *", or 216.


Brook

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



Re: Functional programming in Python

2001-05-29 Thread Ketil Malde

Jerzy Karczmarczuk <[EMAIL PROTECTED]> writes:

>> BTW, before I knew Haskell I exprimented with a syntax in which 'x f'
>> is the application of 'f' to 'x', and 'x f g' means '(x f) g'. 

> Hmmm. An experimental syntax, you say...
> Oh, say, you reinvented FORTH?

Wouldn't 
x f g
in a Forth'ish machine mean
g(f,x)   -- using "standard" math notation, for a change
rather than
g(f(x))
?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

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



Re: Functional programming in Python

2001-05-29 Thread Jerzy Karczmarczuk

Marcin  Kowalczyk:

> BTW, before I knew Haskell I exprimented with a syntax in which 'x f'
> is the application of 'f' to 'x', and 'x f g' means '(x f) g'. Other
> arguments can also be on the right, but in this case with parentheses,
> e.g. 'x f (y)' is a function f applied to two arguments.

Hmmm. An experimental syntax, you say...
Oh, say, you reinvented FORTH?

(No args in parentheses there, a function taking something at its right
simply *knows* that there is something there).


Jerzy Karczmarczuk
Caen, France

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



Re: Functional programming in Python

2001-05-28 Thread Marcin 'Qrczak' Kowalczyk

Mon, 28 May 2001 10:23:58 +0100, Malcolm Wallace <[EMAIL PROTECTED]> pisze:

> It seems that right-associativity is so intuitive that even the
> person proposing it doesn't get it right.  :-)

And even those who correct them :-)

>> f x (foldr1 f xs)f x foldr1 f xs
> 
> Wouldn't the rhs actually mean f x (foldr1 (f xs)) in current notation?

No: f (x (foldr1 (f xs)))

Basically Haskell's style uses curried functions, so it's essential
to be able to apply a function to multiple parameters without a number
of nested parentheses.

BTW, before I knew Haskell I exprimented with a syntax in which 'x f'
is the application of 'f' to 'x', and 'x f g' means '(x f) g'. Other
arguments can also be on the right, but in this case with parentheses,
e.g. 'x f (y)' is a function f applied to two arguments.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


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



RE: Functional programming in Python

2001-05-28 Thread Malcolm Wallace

It seems that right-associativity is so intuitive that even the person
proposing it doesn't get it right.  :-)  Partial applications are a
particular problem:

> Haskell   Non-Haskell
> Left Associative  Right Associative
> From Prelude--
> f x (foldr1 f xs) f x foldr1 f xs

Wouldn't the rhs actually mean f x (foldr1 (f xs)) in current notation?

> showChar '[' . shows x . showl xs showChar '[] shows x showl xs

Wouldn't the rhs actually mean  showChar '[' (shows x (showl xs))
in current notation?   This is quite different to the lhs composition.

For these two examples, the correct right-associative expressions,
as far as I can tell, should be:
  f x (foldr1 f xs) f x (foldr1 f) xs
  showChar '[' . shows x . showl xs showChar '[' . shows x . showl xs

Regards,
Malcolm

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



Re: Functional programming in Python

2001-05-27 Thread Tom Pledger

S. Alexander Jacobson writes:
 | On Fri, 25 May 2001, Zhanyong Wan wrote:
 | > As you explained, the parse of an expression depends the types of the
 | > sub-expressions, which imo is BAD.  Just consider type inference...

Also, we can no longer take a divide-and-conquer approach to reading
code, since the syntax may depend on the types of imports.

 | Ok, your complaint is that f a b c=a b c could have type
 | (a->b->c)->a->b->c or type (b->c)->(a->b)->a->c depending on the arguments
 | passed e.g. (f head (map +2) [3]) has different type from (f add 2 3).
 | 
 | Admittedly, this is different from how haskell type checks now.  I guess
 | the question is whether it is impossible to type check or whether it just
 | requires modification to the type checking algorithm.  Does anyone know?

Here's a troublesome example.

module M(trouble) where

f, g :: (a -> b) -> a -> b
f = undefined
g = undefined

trouble = (.) f g

-- ((.) f) g :: (a -> b) -> a -> b
-- (.) (f g) :: (a -> b -> c) -> a -> b -> c



Regards,
Tom

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



Re: Functional programming in Python

2001-05-25 Thread Juan Carlos Arevalo Baeza

At 05:25 PM 5/25/2001 -0400, S. Alexander Jacobson wrote:

>Admittedly, this is different from how haskell type checks now.  I guess
>the question is whether it is impossible to type check or whether it just
>requires modification to the type checking algorithm.  Does anyone know?

I don't think so... The only ambiguity that I can think of is with 
passing functions as arguments to other functions, and you showed that it 
can be resolved by currying:

map f x

would have to be force-curried using parenthesis:

(map f) x

because otherwise, it would mean:

map (f x)

which is both: very wrongly typed and NOT the intention.

I like your parsing scheme. I still DO like more explicit languages 
better, though (i.e. map(f, x) style, like C & Co.). Currying is cool, but 
it can be kept at a conceptual level, not affecting syntax.


Salutaciones,
   JCAB

-
Juan Carlos "JCAB" Arevalo Baeza| http://www.roningames.com
Senior Technology programmer| mailto:[EMAIL PROTECTED]
Ronin Entertainment | ICQ: 10913692
(my opinions are only mine)
JCAB's Rumblings: http://www.metro.net/jcab/Rumblings/html/index.html



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



Re: Functional programming in Python

2001-05-25 Thread S. Alexander Jacobson

On Fri, 25 May 2001, Zhanyong Wan wrote:
> As you explained, the parse of an expression depends the types of the
> sub-expressions, which imo is BAD.  Just consider type inference...

Ok, your complaint is that f a b c=a b c could have type
(a->b->c)->a->b->c or type (b->c)->(a->b)->a->c depending on the arguments
passed e.g. (f head (map +2) [3]) has different type from (f add 2 3).

Admittedly, this is different from how haskell type checks now.  I guess
the question is whether it is impossible to type check or whether it just
requires modification to the type checking algorithm.  Does anyone know?

-Alex-

___
S. Alexander Jacobson   Shop.Com
1-646-638-2300 voiceThe Easiest Way To Shop (sm)



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



Re: Functional programming in Python

2001-05-25 Thread Zhanyong Wan


"S. Alexander Jacobson" wrote:
> 
> Does anyone know why the haskell designers did not make the syntax
> right associative?  It would clean up a lot of stuff.
> 
> Haskell Non-Haskell
> Left AssociativeRight Associative
> foo (bar (baz (x))) foo bar baz x
> foo $ bar $ baz x   foo bar baz x
> add (square x) (square y)   add square x square y
> add (square x) yadd square x y
> From Prelude--
> map f x (map f) x
> f x (n - 1) x   f x n - 1 x
> f x (foldr1 f xs)   f x foldr1 f xs
> showChar '[' . shows x . showl xs   showChar '[] shows x showl xs
> 
> You just need to read from right to left accumulating a stack of
> arguments.  When you hit a function that can consume some arguments, it
> does so.  There is an error if you end up with more than one value on
> the argument stack.

Note that in your proposal,

  add square x y

is parsed as

  add (square x) y

instead of

  add (square (x y)),

so it's not right associative either.

As you explained, the parse of an expression depends the types of the
sub-expressions, which imo is BAD.  Just consider type inference...

-- Zhanyong

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



RE: Functional programming in Python

2001-05-25 Thread S. Alexander Jacobson

Does anyone know why the haskell designers did not make the syntax
right associative?  It would clean up a lot of stuff.

Haskell Non-Haskell
Left AssociativeRight Associative
foo (bar (baz (x))) foo bar baz x
foo $ bar $ baz x   foo bar baz x
add (square x) (square y)   add square x square y
add (square x) yadd square x y
From Prelude--
map f x (map f) x
f x (n - 1) x   f x n - 1 x
f x (foldr1 f xs)   f x foldr1 f xs
showChar '[' . shows x . showl xs   showChar '[] shows x showl xs

You just need to read from right to left accumulating a stack of
arguments.  When you hit a function that can consume some arguments, it
does so.  There is an error if you end up with more than one value on
the argument stack.

-Alex-



On Fri, 25 May 2001, Tom Pledger wrote:

> Peter Douglass writes:
>  :
>  | but in ( foo ( bar (baz x) ) )
>  |
>  | You would want the following I think.
>  |
>  |  foo . bar . baz x
>  |
>  | which does have the parens omitted, but requires the composition
>  | operator.
>
> Almost.  To preserve the meaning, the composition syntax would need to
> be
>
> (foo . bar . baz) x
>
> or
>
> foo . bar . baz $ x
>
> or something along those lines.  I favour the one with parens around
> the dotty part, and tend to use $ only when a closing paren is
> threatening to disappear over the horizon.
>
> do ...
>return $ case ... of
>... -- many lines
>
> Regards,
> Tom
>
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

___
S. Alexander Jacobson   Shop.Com
1-646-638-2300 voiceThe Easiest Way To Shop (sm)


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



RE: Functional programming in Python

2001-05-24 Thread Tom Pledger

Peter Douglass writes:
 :
 | but in ( foo ( bar (baz x) ) )
 | 
 | You would want the following I think.
 | 
 |  foo . bar . baz x
 | 
 | which does have the parens omitted, but requires the composition
 | operator.

Almost.  To preserve the meaning, the composition syntax would need to
be

(foo . bar . baz) x

or

foo . bar . baz $ x

or something along those lines.  I favour the one with parens around
the dotty part, and tend to use $ only when a closing paren is
threatening to disappear over the horizon.

do ...
   return $ case ... of
   ... -- many lines

Regards,
Tom

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



RE: Functional programming in Python

2001-05-24 Thread Peter Douglass

Peter Hancock wrote:

> > foo( bar( baz( x ) ) )
> > it's:
> > (foo ( bar (baz x) ) )
> 
> Clearly the outer parentheses are unnecessary in the last expression.
> One undeniable advantage of (f a) is it saves parentheses.

Yes and no.   In

( ( ( foo bar) baz) x )

the parens can be omitted to leave

  foo bar baz x

but in ( foo ( bar (baz x) ) )

You would want the following I think.

 foo . bar . baz x

which does have the parens omitted, but requires the composition operator.

--PeterD 

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



Re: Functional programming in Python

2001-05-24 Thread Peter Hancock

Hi, you said

> Unfortunately in many cases you need to apply nearly as many
> parens for a Haskell expression as you would for a Python one, but 
> they're in different places. It's not:
>
> foo( bar( baz( x ) ) )
> it's:
> (foo ( bar (baz x) ) )

Clearly the outer parentheses are unnecessary in the last expression.
One undeniable advantage of (f a) is it saves parentheses.

My feeling is that the f(a) (mathematical) notation works well when
type set or handwritten, but the (f a) (combinatory logic) notation
looks better with non-proportional fonts.

In a way the f(a) notation "represents things better": the f is at a
higher parenthesis level than the a.

Peter Hancock

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



Re: Functional programming in Python

2001-05-24 Thread Peter Hancock

Hi, you said

> Unfortunately in many cases you need to apply nearly as many
> parens for a Haskell expression as you would for a Python one, but 
> they're in different places. It's not:
>
> foo( bar( baz( x ) ) )
> it's:
> (foo ( bar (baz x) ) )

Clearly the outer parentheses are unnecessary in the last expression.
One undeniable advantage of (f a) is it saves parentheses.

My feeling is that the f(a) (mathematical) notation works well when
type set or handwritten, but the (f a) (combinatory logic) notation
looks better with non-proportional fonts.

In a way the f(a) notation "represents things better": the f is at a
higher parenthesis level than the a.

Peter Hancock

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



Re: Functional programming in Python

2001-05-22 Thread Dean Herington

[EMAIL PROTECTED] wrote:

> There's another piece to this question that we're overlooking, I
> think. It's not just a difference (or lack thereof) in precedence, it's the
> fact that parentheses indicate application in Python and many other
> languages, and a function name without parentheses after it is a reference
> to the function, not an application of it. This has nothing to do with
> currying that I can see - you can have curried functions in Python, and they
> still look the same. The main advantage I see for the Haskell style is
> (sometimes) fewer keypresses for parentheses, but I still find it surprising
> at times. Unfortunately in many cases you need to apply nearly as many
> parens for a Haskell expression as you would for a Python one, but they're
> in different places. It's not:
>
> foo( bar( baz( x ) ) )
> it's:
> (foo ( bar (baz x) ) )
>
> I'm not sure why folks thought this was an improvement. I suppose it
> bears more resemblance to lambda calculus?

In Haskell, one doesn't need to distinguish "a reference to the function" from
"an application of it".  As a result, parentheses need to serve only a single
function, that of grouping.  Parentheses surround an entire function
application, just as they surround an entire operation application:

foo (fum 1 2) (3 + 4)

I find this very consistent, simple, and elegant.

Dean


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



RE: Functional programming in Python

2001-05-22 Thread brk



> -Original Message-
> From: Manuel M. T. Chakravarty [SMTP:[EMAIL PROTECTED]]
> Sent: Tuesday, May 22, 2001 6:55 AM
> To:   [EMAIL PROTECTED]
> Cc:   [EMAIL PROTECTED]
> Subject:      Re: Functional programming in Python
> 
> Pertti Kellomäki <[EMAIL PROTECTED]> wrote,
> 
> > > From: Ketil Malde <[EMAIL PROTECTED]>
> > > "Manuel M. T. Chakravarty" <[EMAIL PROTECTED]> writes:
> > > > You want to be able to write
> > > 
> > > >   f 1 2 + g 3 4
> > > 
> > > > instead of
> > > 
> > > >   (f 1 2) + (g 3 4)
> > > 
> > > I do?  Personally, I find it a bit confusing, and I still often get it
> > > wrong on the first attempt. 
> > 
> > Same here. A while back someone said something along the lines that
> people
> > come to Haskell because of the syntax. For me it is the other way
> around.
> > My background is in Scheme/Lisp, and I still find it irritating that I
> cannot
> > just say indent-sexp and the like in Emacs. It is the other properties
> of the
> > language that keep me using it. I also get irritated when I get
> > precedence wrong, so in fact I tend to write (f 1 2) + (g 2 3), which to
> > my eye conveys the intended structure much better and compiles at first
> try.
> 
> In languages that don't use curring, you would write 
> 
>   f (1, 2) + g (2, 3) 
> 
> which also gives application precedence over infix
> operators.  So, I think, we can safely say that application
> being stronger than infix operators is the standard
> situation.
[Bryn Keller]  
There's another piece to this question that we're overlooking, I
think. It's not just a difference (or lack thereof) in precedence, it's the
fact that parentheses indicate application in Python and many other
languages, and a function name without parentheses after it is a reference
to the function, not an application of it. This has nothing to do with
currying that I can see - you can have curried functions in Python, and they
still look the same. The main advantage I see for the Haskell style is
(sometimes) fewer keypresses for parentheses, but I still find it surprising
at times. Unfortunately in many cases you need to apply nearly as many
parens for a Haskell expression as you would for a Python one, but they're
in different places. It's not:

foo( bar( baz( x ) ) )
it's:
(foo ( bar (baz x) ) )

I'm not sure why folks thought this was an improvement. I suppose it
bears more resemblance to lambda calculus?


> Nevertheless, the currying notation is a matter of habit.
> It took me a while to get used to it, too (as did layout).
> But now, I wouldn't want to miss them anymore.  And as far
> as layout is concerned, I think, the Python people have made
> the same experience.  For humans, it is quite natural to use
> visual cues (like layout) to indicate semantics.
[Bryn Keller]  
Absolutely. Once you get used to layout (Haskell style or Python
style), everything else looks like it was designed specifically to irritate
you. On the other hand, it's nice to have a brace-delimited style since that
makes autogenerating code a lot easier.

Bryn



> Cheers,
> Manuel
> 
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe

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



Re: Functional programming in Python

2001-05-22 Thread Paul Hudak

> I realize this is a topic where it would be very easy to start a flame
> war, but hopefully we can avoid that.

No problem :-)

> Maybe I did not express my point clearly. What I was trying to say was
> that
> because of the syntax, it is very easy for M-C-q in Emacs to convert
> that to ...

Ok, I understand now.  So clearly we just need better editing tools for
Haskell, which I guess is part of your point.

By the way, there are many Haskell programmers who prefer to write their
programs like this:

  let { a = x
  ; b = y
  ; c = z
  }
in ...

which arguably has its merits.

  -Paul

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



Re: Functional programming in Python

2001-05-22 Thread Kellomaki Pertti

I realize this is a topic where it would be very easy to start a flame
war, but hopefully we can avoid that.

Paul Hudak wrote:
> Why not have your tool generate layout-less code?  Surely that would be
> easier to program, and be less error prone.

The tool in question is Happy, and the error materialized as an
interaction
between the tool-generated parser code and the hand-written code in
actions.
So no, this was not an option since the tool is not written by me, and
given
my current capabilities in Haskell I could not even fix it. On the other
hand 
the bug is easy to work around, and it might even be fixed in newer
versions 
of Happy.
 
> Yes, but the layout is not ENFORCED.  I programmed in Lisp for many
> years before switching to Haskell, and a common error is something like
> this:
> 
> > (let ((a 0)
> >   (b 1)
> >(+ a b)))
> 
> In this case the error is relatively easy to spot, but in denser code it
> can be very subtle.  So in fact using layout in Lisp can imply a
> semantics that is simply wrong.

Maybe I did not express my point clearly. What I was trying to say was
that
because of the syntax, it is very easy for M-C-q in Emacs to convert
that to

(let ((a 0)
  (b 1)
  (+ a b)))

which brings the layout of the source code to agreement with how it is
perceived
by the compiler/interpreter. So it is easy for me to enforce the layout.

This is not so much of an issue when you are writing the code in the
first place,
but I find it a pain to have to adjust indentation when I move bits of
code around
in an evolving program. If there is good support for that, then I'll
just shut up
an start using it. After all, I have only been using Haskell for a very
short
period of time.
-- 
pertti

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



Re: Functional programming in Python

2001-05-22 Thread Paul Hudak

> Two points: I have been with Haskell less than half a year, and already
> I have run into a layout-related bug in a tool that produces Haskell
> source.

Why not have your tool generate layout-less code?  Surely that would be
easier to program, and be less error prone.

> Second, to a Lisp-head like myself something like
> (let ((a 0)
>   (b 1))
>(+ a b))
> does exactly what you say: it uses layout to indicate semantic.

Yes, but the layout is not ENFORCED.  I programmed in Lisp for many
years before switching to Haskell, and a common error is something like
this:

> (let ((a 0)
>   (b 1)
>(+ a b)))

In this case the error is relatively easy to spot, but in denser code it
can be very subtle.  So in fact using layout in Lisp can imply a
semantics that is simply wrong.

-Paul

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



Re: Functional programming in Python

2001-05-22 Thread Arjan van IJzendoorn

> > For humans, it is quite natural to use
> > visual cues (like layout) to indicate semantics.

I agree, but let us not try to do that with just two (already overloaded)
symbols.

> (let ((a 0)
>   (b 1))
>(+ a b))

let { a = 0; b = 1; } in a + b

is valid Haskell and the way I use the language. Enough and more descriptive
visual cues, I say.
Using layout is an option, not a rule (although the thing is called layout
rule...)

> But all this is not very constructive, because Haskell is not going to
> change into a fully parenthesized prefix syntax at my wish.

Thank god :-)

Arjan



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



Re: Functional programming in Python

2001-05-22 Thread Kellomaki Pertti

"Manuel M. T. Chakravarty" wrote:
> In languages that don't use curring, you would write
>   f (1, 2) + g (2, 3)
> which also gives application precedence over infix
> operators.  So, I think, we can safely say that application
> being stronger than infix operators is the standard
> situation.

Agreed, though you must remember that where I come from there is no
precedence at all.

> And as far
> as layout is concerned, I think, the Python people have made
> the same experience.  For humans, it is quite natural to use
> visual cues (like layout) to indicate semantics.

Two points: I have been with Haskell less than half a year, and already
I have run into a layout-related bug in a tool that produces Haskell
source.
This does not raise my confidence on the approach very much.
Second, to a Lisp-head like myself something like

(let ((a 0)
  (b 1))
   (+ a b))

does exactly what you say: it uses layout to indicate semantic. The
parentheses
are there only to indicate semantics to the machine, and to make it easy
for
tools to pretty print the expression in such a way that the layout
reflects
the semantics as seen by the machine.

But all this is not very constructive, because Haskell is not going to
change
into a fully parenthesized prefix syntax at my wish.
-- 
Pertti Kellom\"aki, Tampere Univ. of Technology, Software Systems Lab

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



Re: Functional programming in Python

2001-05-22 Thread Manuel M. T. Chakravarty

Pertti Kellomäki <[EMAIL PROTECTED]> wrote,

> > From: Ketil Malde <[EMAIL PROTECTED]>
> > "Manuel M. T. Chakravarty" <[EMAIL PROTECTED]> writes:
> > > You want to be able to write
> > 
> > >   f 1 2 + g 3 4
> > 
> > > instead of
> > 
> > >   (f 1 2) + (g 3 4)
> > 
> > I do?  Personally, I find it a bit confusing, and I still often get it
> > wrong on the first attempt. 
> 
> Same here. A while back someone said something along the lines that people
> come to Haskell because of the syntax. For me it is the other way around.
> My background is in Scheme/Lisp, and I still find it irritating that I cannot
> just say indent-sexp and the like in Emacs. It is the other properties of the
> language that keep me using it. I also get irritated when I get
> precedence wrong, so in fact I tend to write (f 1 2) + (g 2 3), which to
> my eye conveys the intended structure much better and compiles at first try.

In languages that don't use curring, you would write 

  f (1, 2) + g (2, 3) 

which also gives application precedence over infix
operators.  So, I think, we can safely say that application
being stronger than infix operators is the standard
situation.

Nevertheless, the currying notation is a matter of habit.
It took me a while to get used to it, too (as did layout).
But now, I wouldn't want to miss them anymore.  And as far
as layout is concerned, I think, the Python people have made
the same experience.  For humans, it is quite natural to use
visual cues (like layout) to indicate semantics.

Cheers,
Manuel

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



Re: Functional programming in Python

2001-05-22 Thread Pertti Kellomäki

> From: Ketil Malde <[EMAIL PROTECTED]>
> "Manuel M. T. Chakravarty" <[EMAIL PROTECTED]> writes:
> > You want to be able to write
> 
> >   f 1 2 + g 3 4
> 
> > instead of
> 
> >   (f 1 2) + (g 3 4)
> 
> I do?  Personally, I find it a bit confusing, and I still often get it
> wrong on the first attempt. 

Same here. A while back someone said something along the lines that people
come to Haskell because of the syntax. For me it is the other way around.
My background is in Scheme/Lisp, and I still find it irritating that I cannot
just say indent-sexp and the like in Emacs. It is the other properties of the
language that keep me using it. I also get irritated when I get
precedence wrong, so in fact I tend to write (f 1 2) + (g 2 3), which to
my eye conveys the intended structure much better and compiles at first try.
-- 
pertti

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



Re: Functional programming in Python

2001-05-20 Thread Ketil Malde

"Manuel M. T. Chakravarty" <[EMAIL PROTECTED]> writes:

> You want to be able to write

>   f 1 2 + g 3 4

> instead of

>   (f 1 2) + (g 3 4)

I do?  Personally, I find it a bit confusing, and I still often get it
wrong on the first attempt.  The good thing is that the rule is simple
to remember. :-)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

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



RE: Functional programming in Python

2001-05-15 Thread brk

> -Original Message-
> From: Manuel M. T. Chakravarty [SMTP:[EMAIL PROTECTED]]
> Sent: Monday, May 14, 2001 10:46 PM
> To:   [EMAIL PROTECTED]
> Cc:   [EMAIL PROTECTED]
> Subject:      RE: Functional programming in Python
> 
> [EMAIL PROTECTED] wrote,
> 
> > > From: Manuel M. T. Chakravarty [SMTP:[EMAIL PROTECTED]]
> > Evidently this is wrong, but my intuition is that <- simply binds a
> > name to a value, and that:
> 
> No, that is not the case.  It does more, it executes an I/O action.
> 
[Bryn Keller]  [snip]

> The short answer is that Version 2 (the arrow) executes any
> side effects encoded in `somefunc', whereas Version 1 (the
> let binding) doesn't do that.  Expressions given as an
> argument to a function behave as if they were let bound, ie,
> they don't execute any side effects.  This explains why the
> identity that you stated above does not hold.
> 
> So, at the core is that Haskell insists on distinguishing
> expressions that can have side effects from those that
> cannot.  This distinction makes the language a little bit
> more complicated (eg, by enforcing us to distinguish between
> `=' and `<-'), but it also has the benefit that both a
> programmer and the compiler can immediately tell which
> expressions do have side effects and which don't.  For
> example, this often makes it a lot easier to alter code
> written by somebody else.  It also makes it easier to
> formally reason about code and it gives the compiler scope
> for rather radical optimisations.
> 
[Bryn Keller]  
Exactly the clarification I needed, thank you! 

[Bryn Keller]  [snip]


> > p.s. What data have your students' reactions given you about what is
> > and is not difficult for beginners to grasp?
> 
> They found it to be a difficult topic, but they found
> "Unix/Shell scripts" even harder (and we did only simple
> shell scripts).  I actually made another interesting
> observation (and keep in mind that for many that was their
> first contact with programming).  I had prepared for the
> distinction between side effecting and non-side-effecting
> expressions to be a hurdle in understanding I/O.  What I
> hand't taken into account was that the fact that they had
> only worked in an interactive interpreter environment (as
> opposed to, possibly compiled, standalone code) would pose
> them a problem.  The interactive interpreter had allowed
> them to type in input and get results printed all way long,
> so they didn't see why it should be necessary to complicate
> a program with print statements.
[Bryn Keller]  
Interesting!

Thanks for your help, and for sharing your students' observations. I
always knew shell scripting was harder than it ought to be. ;-)

Bryn

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



RE: Functional programming in Python

2001-05-14 Thread Manuel M. T. Chakravarty

[EMAIL PROTECTED] wrote,

> > From:   Manuel M. T. Chakravarty [SMTP:[EMAIL PROTECTED]]
> >  Absolutely.  In fact, you have just pointed out one of the
> > gripes that I have with most Haskell texts and courses.  The
> > shunning of I/O in textbooks is promoting the image of
> > Haskell as a purely academic exercise.  Something which is
> > not necessary at all, I am teaching an introductory course
> > with Haskell myself and did I/O in Week 5 out of 14 (these
> > are students without any previous programming experience).
> > Moreover, IIRC Paul Hudak's book 
> > also introduces I/O early.
> > 
> > In other words, I believe that this a problem with the
> > presentation of Haskell and not with Haskell itself.
>
>   Since my first mesage and your and Simon Peyton-Jones' response,
> I've taken a little more time to work with Haskell, re-read Tackling the
> Awkward squad, and browsed the source for Simon Marlow's web server, and
> it's starting to feel more comfortable now. In the paper and in the server
> souce, there is certainly a fair amount of IO work happening, and it all
> looks fairly natural and intuitive. 
> 
>   Mostly I find when I try to write code following those examples (or
> so I think!), it turns out to be not so easy, and the real difficulty is
> that I can't even put my finger on why it's troublesome. I try many
> variations on a theme - some work, some fail, and often I can't see why. I
> should have kept all the versions of my program that failed for reasons I
> didn't understand, but unfortunately I didn't... The only concrete example
> of something that confuses me I can recall is the fact that this compiles:
> 
>   main = do allLines <- readLines; putStr $ unlines allLines
>   where readLines = do
>   eof <- isEOF
>   if eof then return [] else
>   do
>   line <- getLine
>   allLines <- readLines
>   return (line : allLines)
> 
>   but this doesn't:
> 
>   main = do putStr $ unlines readLines
>   where readLines = do
>   eof <- isEOF
>   if eof then return [] else
>   do
>   line <- getLine
>   allLines <- readLines
>   return (line : allLines)
> 
>   Evidently this is wrong, but my intuition is that <- simply binds a
> name to a value, and that:

No, that is not the case.  It does more, it executes an I/O action.

>   foo <- somefunc
>   bar foo
> 
>   should be identical to:
>   
>   bar somefunc

But it isn't; however, we have 

  do
let foo = somefunc
bar foo

is identical to

  do
bar somefunc

So, this all boils down to the question, what is the
difference between

  do
let foo = somefunc  -- Version 1
bar foo

and

  do
foo <- somefunc -- Version 2
bar foo

The short answer is that Version 2 (the arrow) executes any
side effects encoded in `somefunc', whereas Version 1 (the
let binding) doesn't do that.  Expressions given as an
argument to a function behave as if they were let bound, ie,
they don't execute any side effects.  This explains why the
identity that you stated above does not hold.

So, at the core is that Haskell insists on distinguishing
expressions that can have side effects from those that
cannot.  This distinction makes the language a little bit
more complicated (eg, by enforcing us to distinguish between
`=' and `<-'), but it also has the benefit that both a
programmer and the compiler can immediately tell which
expressions do have side effects and which don't.  For
example, this often makes it a lot easier to alter code
written by somebody else.  It also makes it easier to
formally reason about code and it gives the compiler scope
for rather radical optimisations.

To reinforce the distinction, consider the following two
pieces of code (where `readLines' is the routine you defined
above):

  do
let x = readLines
y <- x
z <- x
return (y ++ z)

and

  do
x <- readLines
let y = x
let z = x
return (y ++ z)

How is the result (and I/O behaviour) different?

>   That was one difficulty. Another was trying to figure out what the $
> sign was for. Finally I realized it was an alternative to parentheses,
> necessary due to the extremely high precedence of function application in
> Haskell. That high precedence is also disorienting, by the way. What's the
> rationale behind it?

You want to be able to write

  f 1 2 + g 3 4

instead of

  (f 1 2) + (g 3 4)

>   p.s. What data have your students' reactions given you about what is
> and is not difficult for beginners to grasp?

They found it to be a difficult topic, but they found
"Unix/Shell scripts" even harder (and we did only simple
shell scripts).  I actually made another interesting
observation (and keep in mind tha

RE: Functional programming in Python

2001-05-14 Thread brk



> -Original Message-
> From: Manuel M. T. Chakravarty [SMTP:[EMAIL PROTECTED]]
> Sent: Wednesday, May 09, 2001 12:57 AM
> To:   [EMAIL PROTECTED]
> Cc:   [EMAIL PROTECTED]
> Subject:      RE: Functional programming in Python
> 
[Bryn Keller]  [snip]
>  
> > and I have to agree with Dr. Mertz - I find
> > Haskell much more palatable than Lisp or Scheme. Many (most?) Python
> > programmers also have experience in more typeful languages (typically at
> > least C, since that's how one writes Python extension modules) so
> perhaps
> > that's not as surprising as it might seem.
> 
> Ok, but there are worlds between C's type system and
> Haskell's.[1]
> 
[Bryn Keller]  
Absolutely! C's type system is not nearly so powerful or unobtrusive
as Haskell's. 

> > Type inference (to my mind at least) fits the Python mindset very
> > well. 
> 
> So, how about the following conjecture?  Types essentially
> only articulate properties about a program that a good
> programmer would be aware of anyway and would strive to
> reinforce in a well-structured program.  Such a programmer
> might not have many problems with a strongly typed language.
[Bryn Keller]  
I would agree with this.

> Now, to me, Python has this image of a well designed
> scripting language attracting the kind of programmer who
> strives for elegance and well-structured programs.  Maybe
> that is a reason.
[Bryn Keller]  
This, too. :-)

[Bryn Keller]  [snip]

>  Absolutely.  In fact, you have just pointed out one of the
> gripes that I have with most Haskell texts and courses.  The
> shunning of I/O in textbooks is promoting the image of
> Haskell as a purely academic exercise.  Something which is
> not necessary at all, I am teaching an introductory course
> with Haskell myself and did I/O in Week 5 out of 14 (these
> are students without any previous programming experience).
> Moreover, IIRC Paul Hudak's book <http://haskell.org/soe/>
> also introduces I/O early.
> 
> In other words, I believe that this a problem with the
> presentation of Haskell and not with Haskell itself.
> 
> Cheers,
> Manuel
> 
> [1] You might wonder why I am pushing this point.  It is
> just because the type system seems to be a hurdle for
> some people who try Haskell.  I am curious to understand
> why it is a problem for some and not for others.
[Bryn Keller]  
Since my first mesage and your and Simon Peyton-Jones' response,
I've taken a little more time to work with Haskell, re-read Tackling the
Awkward squad, and browsed the source for Simon Marlow's web server, and
it's starting to feel more comfortable now. In the paper and in the server
souce, there is certainly a fair amount of IO work happening, and it all
looks fairly natural and intuitive. 

Mostly I find when I try to write code following those examples (or
so I think!), it turns out to be not so easy, and the real difficulty is
that I can't even put my finger on why it's troublesome. I try many
variations on a theme - some work, some fail, and often I can't see why. I
should have kept all the versions of my program that failed for reasons I
didn't understand, but unfortunately I didn't... The only concrete example
of something that confuses me I can recall is the fact that this compiles:

main = do allLines <- readLines; putStr $ unlines allLines
where readLines = do
eof <- isEOF
if eof then return [] else
do
line <- getLine
allLines <- readLines
return (line : allLines)

but this doesn't:

main = do putStr $ unlines readLines
where readLines = do
eof <- isEOF
if eof then return [] else
do
line <- getLine
allLines <- readLines
return (line : allLines)

Evidently this is wrong, but my intuition is that <- simply binds a
name to a value, and that:

foo <- somefunc
bar foo

should be identical to:

bar somefunc

That was one difficulty. Another was trying to figure out what the $
sign was for. Finally I realized it was an alternative to parentheses,
necessary due to the extremely high precedence of function application in
Haskell. That high precedence is also disorienting, by the way. What's the
rationale behind it?

Struggling along, but starting to enjoy the aesthetics of Haskell,
Bryn

p.s. What data have your students' reactions given you about what is
and is not difficult for beginners to grasp?

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



Arrays in Haskell, was: Re: Functional programming in Python

2001-05-11 Thread Wojciech Moczydlowski, Jr

On Tue, 8 May 2001, Erik Meijer wrote:

> Interestingly enough, I have the same feeling with Python!

Speaking of problems with Haskell, almost every time I write a larger
program, I'm frustrated with lack of efficient arrays/hashtables in the
standard. I know about ghc (I|U|M)Arrays for arrays and probably there
are hashtables implemented in Edison library, but the program's
portability would be lost and nhc/hugs would protest. I would be very 
happy if Haskell developers could settle on a simple, not sophisticated 
standard arrays.
I personally would like an interface like:

data Array type_of_objects_stored = ... -- abstract
data MArray a b = ... -- abstract
instance Monad (MArray a)

put :: Int -> a -> Array a -> MArray ()  
get :: Array a -> MArray a

runMArray :: Int -> MArray a -> a   -- int parameter is a size of used
array.

Even if they were put in IO, I still would not protest. Anything is better
than nothing.

Wojciech Moczydlowski, Jr



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



RE: Functional programming in Python

2001-05-09 Thread Manuel M. T. Chakravarty

[EMAIL PROTECTED] wrote,

>   It's interesting to me to note the things that were interesting to
> you. :-)  I'm the author of the Xoltar Toolkit (including functional.py)
> mentioned in those articles

Cool :-)

> and I have to agree with Dr. Mertz - I find
> Haskell much more palatable than Lisp or Scheme. Many (most?) Python
> programmers also have experience in more typeful languages (typically at
> least C, since that's how one writes Python extension modules) so perhaps
> that's not as surprising as it might seem.

Ok, but there are worlds between C's type system and
Haskell's.[1]

>   Type inference (to my mind at least) fits the Python mindset very
> well. 

So, how about the following conjecture?  Types essentially
only articulate properties about a program that a good
programmer would be aware of anyway and would strive to
reinforce in a well-structured program.  Such a programmer
might not have many problems with a strongly typed language.

Now, to me, Python has this image of a well designed
scripting language attracting the kind of programmer who
strives for elegance and well-structured programs.  Maybe
that is a reason.

> I think most Python programmers would be glad to have strong typing,
> so long as they don't have to press more keys to get it. If you have to
> declare all your types up front, it just means more time spent changing type
> declarations as the design evolves, but if the compiler can just ensure your
> usage is consistent, that's hard to argue with.

Type inference (as opposed to mere type checking) is
certainly a design goal in Haskell.

>   As for the difficulty with imperative constructs, I agree it's not
> even an issue for many (Dylan, ML, et. al.) languages, but for Haskell it
> still is, in my humble opinion. I found the task of writing a simple program
> that did a few simple imperative things inordinately difficult. I know about
> the 'do' construct, and I understand the difference between >> and >>=. I've
> read a book on Haskell, and implemented functional programming support for
> Python, but trying to use Haskell to write complete programs still ties my
> brain in knots. I see there are people writing complete, non-trivial
> programs in Haskell, but I don't see how.
> 
>   To be sure, I owe Haskell more of my time and I owe it to myself to
> overcome this difficulty, but I don't think it's only my difficulty. In the
> Haskell book I have, discussion of I/O is delayed until chapter 18, if
> memory serves. One thing that might really help Haskell become more popular
> is more documentation which presents I/O in chapter 2 or 3. Clearly the
> interesting part of a functional language is the beauty of stringing
> together all these functions into a single, elegant expression, but an
> introductory text would do well to focus on more immediate problems first.

Absolutely.  In fact, you have just pointed out one of the
gripes that I have with most Haskell texts and courses.  The
shunning of I/O in textbooks is promoting the image of
Haskell as a purely academic exercise.  Something which is
not necessary at all, I am teaching an introductory course
with Haskell myself and did I/O in Week 5 out of 14 (these
are students without any previous programming experience).
Moreover, IIRC Paul Hudak's book 
also introduces I/O early.

In other words, I believe that this a problem with the
presentation of Haskell and not with Haskell itself.

Cheers,
Manuel

[1] You might wonder why I am pushing this point.  It is
just because the type system seems to be a hurdle for
some people who try Haskell.  I am curious to understand
why it is a problem for some and not for others.

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



Re: Functional programming in Python

2001-05-08 Thread Erik Meijer

Interestingly enough, I have the same feeling with Python!

> As for the difficulty with imperative constructs, I agree it's not
> even an issue for many (Dylan, ML, et. al.) languages, but for Haskell it
> still is, in my humble opinion. I found the task of writing a simple
program
> that did a few simple imperative things inordinately difficult. I know
about
> the 'do' construct, and I understand the difference between >> and >>=.
I've
> read a book on Haskell, and implemented functional programming support for
> Python, but trying to use Haskell to write complete programs still ties my
> brain in knots. I see there are people writing complete, non-trivial
> programs in Haskell, but I don't see how.


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



RE: Functional programming in Python

2001-05-08 Thread brk

Hi Manuel,
It's interesting to me to note the things that were interesting to
you. :-)  I'm the author of the Xoltar Toolkit (including functional.py)
mentioned in those articles, and I have to agree with Dr. Mertz - I find
Haskell much more palatable than Lisp or Scheme. Many (most?) Python
programmers also have experience in more typeful languages (typically at
least C, since that's how one writes Python extension modules) so perhaps
that's not as surprising as it might seem.

Type inference (to my mind at least) fits the Python mindset very
well. I think most Python programmers would be glad to have strong typing,
so long as they don't have to press more keys to get it. If you have to
declare all your types up front, it just means more time spent changing type
declarations as the design evolves, but if the compiler can just ensure your
usage is consistent, that's hard to argue with.

As for the difficulty with imperative constructs, I agree it's not
even an issue for many (Dylan, ML, et. al.) languages, but for Haskell it
still is, in my humble opinion. I found the task of writing a simple program
that did a few simple imperative things inordinately difficult. I know about
the 'do' construct, and I understand the difference between >> and >>=. I've
read a book on Haskell, and implemented functional programming support for
Python, but trying to use Haskell to write complete programs still ties my
brain in knots. I see there are people writing complete, non-trivial
programs in Haskell, but I don't see how.

To be sure, I owe Haskell more of my time and I owe it to myself to
overcome this difficulty, but I don't think it's only my difficulty. In the
Haskell book I have, discussion of I/O is delayed until chapter 18, if
memory serves. One thing that might really help Haskell become more popular
is more documentation which presents I/O in chapter 2 or 3. Clearly the
interesting part of a functional language is the beauty of stringing
together all these functions into a single, elegant expression, but an
introductory text would do well to focus on more immediate problems first.
People on this list and others often say that the main body of the program
is almost always imperative in style, but there's little demonstration of
that fact - most examples are of a purely functional nature.

Please understand I mean these comments in the most constructive
sense. I have the highest respect for Haskell and the folks who work with
it.

Bryn




> -Original Message-
> From: Manuel M. T. Chakravarty [SMTP:[EMAIL PROTECTED]]
> Sent: Sunday, May 06, 2001 10:02 PM
> To:   [EMAIL PROTECTED]
> Subject:  Functional programming in Python
> 
> Two quite interesting articles about FP in Python are over
> at IBM developerWorks:
> 
>   http://www-106.ibm.com/developerworks/library/l-prog.html
>   http://www-106.ibm.com/developerworks/library/l-prog2.html
> 
> Two IMHO interesting things to note are the following:
> 
> * In Part 1, at the start, there is a bullet list of what
>   the author regards as FP "features".  I found the
>   following interesting about this list:
> 
>   - There is no mention of the emphasis placed on strong
> typing in many modern functional languages.
> 
>   - The author makes it sound as if FP can't handle
> imperative features, whereas I would say that this is a
> problem of the past and wasn't an issue in many FP
> languages (Lisp, ML, ...) in the first place.
> 
> The opinion of the author is not really suprising, but I
> think, it indicates a problem in how FP presents itself
> to the rest of the world.
> 
> * In Part 2, the author writes at the end:
> 
> I have found it much easier to get a grasp of functional
> programming in the language Haskell than in Lisp/Scheme
> (even though the latter is probably more widely used, if
> only in Emacs).  Other Python programmers might
> similarly have an easier time without quite so many
> parentheses and prefix (Polish) operators.
> 
>   I think, this is interesting, because both Lisp and Python
>   are dynammically typed.  So, I would have expected the
>   strong type system to be more of a hurdle than Lisp's
>   syntax (or lack thereof).
> 
> Cheers,
> Manuel
> 
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe

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