Re: [Haskell-cafe] let and fixed point operator

2007-09-01 Thread Mitar
Hi!

 I did once try to learn Prolog. And failed. Miserably.

You should backtrack at this point and try again differently. :-)


Mitar
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-09-01 Thread Albert Y. C. Lai

Mitar wrote:

I did once try to learn Prolog. And failed. Miserably.


You should backtrack at this point and try again differently. :-)


There is likely a problem if he has inadvently walked past a cut. XD
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-31 Thread Paul Hudak

ok wrote:

What is so bad about

f x = g x''
  where x'' = x' + transform
x'  = x  * scale

(if you really hate inventing temporary names, that is).
There's nothing at all wrong with this, assuming it's what you meant to 
type :-), and it might even correspond perfectly to the mathematical 
notation used in some textbook.  But I would argue that this example is 
pretty simple, and that if there were a lot of xs and x's and x''s then 
the chance of making a typing mistake is greater, I believe, than if you 
had used x, xscaled, and xtransformed.  (On the other hand this is all 
pretty subjective... :-)


   -Paul

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-31 Thread Andrew Coppin

[EMAIL PROTECTED] wrote:

Anyway, I believe strongly that ALL people who have problems with the
Haskell protocole, and they are numerous, I teach a good sample of them,
should be encouraged to learn Prolog. IN DEPTH, and I mean it, Andrew
Coppin and Peter Hercek !
In Prolog A=B is the unification, which is a bit more than equality, and
something much more aggressive than an assignment. When you REALLY
understand unification, it will be easier to see the lazy instantiation
of the Haskell assignment, and, additionally, it becomes much more easy
to understand the automatic inference of types, which sooner or later
must be harnessed by all Haskell programmers...


I did once try to learn Prolog. And failed. Miserably.

I just couldn't bend my head around how the Prolog interpreter manages 
to make seemingly impossible leaps of deduction. (It's a *machine*! 
How can it deduce arbitrarily complex conclusions from any arbitrary set 
of axioms? That requires *intelligence*!) And yet, in other, seemingly 
identical cases, it utterly fails to deduce patently *obvious* 
results... really weird!


And then I read a book. A golden book. (No, seriously. The cover is 
gold-coloured.) It was called The Fun of Programming. And it 
demonstrates how to write a Haskell program that performs exactly the 
same impossible feats. And now, finally, it makes sense.


(I still have no idea what the hell all that business with the cut 
operator is though...)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-31 Thread Andrew Coppin

Paul Hudak wrote:

ok wrote:

What is so bad about

f x = g x''
  where x'' = x' + transform
x'  = x  * scale

(if you really hate inventing temporary names, that is).
There's nothing at all wrong with this, assuming it's what you meant 
to type :-), and it might even correspond perfectly to the 
mathematical notation used in some textbook.  But I would argue that 
this example is pretty simple, and that if there were a lot of xs and 
x's and x''s then the chance of making a typing mistake is greater, I 
believe, than if you had used x, xscaled, and xtransformed.  (On the 
other hand this is all pretty subjective... :-)


OMG! Mathematical and subjective in the same sentence! ;-)

Personally, I find that if I've got more than 2 of the thing, I number 
them rather than attach multiple primes... but that's just me.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-31 Thread Brandon S. Allbery KF8NH


On Aug 31, 2007, at 16:01 , Sterling Clover wrote:

In particular for a function -- n, m, etc or x, y, etc? What about  
for f' defined in a let block of f? If I use x y at the top level I  
need to use another set below -- is that where x' y' are more  
appropriate, or x1, y1?


Usual style is x',y'.

For longer names, camelCase is the usual convention but some  
libraries which basically import everything from C via the FFI use  
C_style_names.  Imported constants/macros which are uppercase with _  
tend to be mapped to tHIS_KIND_OF_NAME (see for example the Win32  
package).


One thing to watch out for is that monads tend to carry their own  
metaconventions:  a generic monad is m, a reader monad is r, a  
state monad is s, functors are f.


For tuples I tend to pattern match with (a,b), and for lists I tend  
to use (h:r) for head and rest. Are there


The common convention for lists is e.g. (x:xs) (the latter is x-es).

other, more universal standards for these sorts of things? Another  
related question is whether using these short sweet variable names  
makes sense, or whether I should try to use more descriptive ones.


I generally use something short but descriptive when writing  
something specific, and single-character generic names when writing  
something that's generic and/or polymorphic.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Dan Piponi
On 8/30/07, Peter Hercek [EMAIL PROTECTED] wrote:

 f x =
let x = x * scale in
let x = x + transform in
g x

Why are you trying to call three different things by the same name 'x'
in one tiny block of code? That's very confusing and makes it hard to
reason equationally about the code.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Brent Yorgey
On 8/30/07, Peter Hercek [EMAIL PROTECTED] wrote:

 Hi,

 I find the feature that the construct let x = f x in expr
   assigns fixed point of f to x annoying. The reason is that
   I can not simply chain mofifications a variable like e.g. this:

 f x =
let x = x * scale in
let x = x + transform in
g x

 When one is lucky then it results in a compile error; in worse
   cases it results in stack overflow in runtime. The annoying
   part is figuring out new and new variable names for essentially
   the same thing to avoid the search/evaluation of the fixed point.

 I suppose Haskell was designed so that it makes sense. The only
   usage I can see is like this:

 let fact = \x - if x == 0 then 1 else x * fact (x-1) in

... but that is not any shorter than:

 let fact x = if x == 0 then 1 else x * fact (x-1) in

 So the question is what am I missing? Any nice use cases where
   fixed point search is so good that it is worth the trouble with
   figuring out new and new variable names for essentially the same
   stuff?

 Peter.


This is not really about fix points, it is about the very essence of
functional programming.  You cannot modify variables in the way you are
suggesting; a variable such as x must *always refer to the same thing*
within a given scope.  This is not a liability, but rather a very nice
thing: it makes it much easier to reason about programs if a given name
always refers to the same thing.  In an imperative language, where you
really can modify the contents of variables, you do not have this
guarantee.  The same variable could refer to different values at different
points in the program, which can lead to much confusion.

Now, I do understand your annoyance; it certainly is annoying to type
something like

f x =
  let y = x * scale in
  let z = y + transform in
  g z

where you have to come up with a bunch of different names for the
intermediate values. But it's actually possible to do this in a much nicer
way which is idiomatic in a functional language such as Haskell.  Note that
what you are really doing here is sending x through a pipeline of
functions which transform it into another value.  The way to combine
functions into a pipeline is by using function concatenation:

f = g . (+ transform) . (* scale)

This is exactly the same thing, but no annoying intermediate names in
sight!  This simply says that f is the function you get when you first
multiply by scale, then add transform, then finally apply function g.  If
you don't like the point-free style, you could also write something like

f x = g $ (+ transform) $ (* scale) $ x

(The $ simply lets you avoid writing lots of parentheses.)


Hope this helps,
-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Ketil Malde
On Thu, 2007-08-30 at 18:17 +0200, Peter Hercek wrote:

 I find the feature that the construct let x = f x in expr
   assigns fixed point of f to x annoying. 

Any alternative?  Non-recursive assignments?

 f x =
let x = x * scale in
let x = x + transform in
g x

I think it is often it is better to avoid temporary names.  I guess this
is a simplified example, but I think it is better to write:

  f x = g (transform + scale * x)

Or even use point-free style to avoid fixpoint?

   f = g . (+transform) . (* scale)

-k


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Brent Yorgey
On 8/30/07, Brent Yorgey [EMAIL PROTECTED] wrote:



   The way to combine functions into a pipeline is by using function
 concatenation:


Oops, of course I meant function composition instead of function
concatenation.

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Derek Elkins
On Thu, 2007-08-30 at 18:17 +0200, Peter Hercek wrote:
 Hi,
 
 I find the feature that the construct let x = f x in expr
   assigns fixed point of f to x annoying. The reason is that
   I can not simply chain mofifications a variable like e.g. this:
 
 f x =
let x = x * scale in
let x = x + transform in
g x

The common answer is that such code is considered ugly in most
circumstances.  Nevertheless, one solution would be to use the Identity
monad and write that as,
f x = runIdentity $ do 
x - x*scale
x - x + transform
return (g x)

 
 When one is lucky then it results in a compile error; in worse
   cases it results in stack overflow in runtime. The annoying
   part is figuring out new and 
 new variable names for essentially
   the same thing to avoid the search/evaluation of the fixed point.
 
 I suppose Haskell was designed so that it makes sense. The only
   usage I can see is like this:
 
 let fact = \x - if x == 0 then 1 else x * fact (x-1) in
 
... but that is not any shorter than:
 
 let fact x = if x == 0 then 1 else x * fact (x-1) in
 
 So the question is what am I missing? Any nice use cases where
   fixed point search is so good that it is worth the trouble with
   figuring out new and new variable names for essentially the same
   stuff?
 
 Peter.

Haskell is lazy, we can have (mutually) recursive values.  The canonical
example,
fibs = 0:1:zipWith (+) fibs (tail fibs)
Slightly more interesting,
karplusStrong = y
where y = map (\x - 1-2*x) (take 50 (randoms (mkStdGen 1)))
   ++ zipWith (\x y - (x+y)/2) y (tail y)

However, the real point is that you shouldn't be naming and renaming the
same thing.  Going back to your original example, it would be nicer to
most to write it as,
f = g . transform displacement . scale factor
or pointfully
f x = g (transform displacement (scale factor x))
with the appropriate combinators.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Andrew Coppin
OK, so it's only tangentally related, but... do you have *any idea* how 
many times I've written something like


 let x = (some complex function of x)
 in (some other complex function of x)

when in fact what I *meant* to do was type x' instead of x?!

It's really maddening to write 50,000 lines of code, eventually get it 
to compile, run it, and have the program lock up and start consuming so 
much virtual memory that the entire PC becomes unstable within seconds. 
(This isn't helped by the fact that Ctrl+C doesn't seem to make either 
GHCi or GHC-compiled programs halt...) Now you have 50,000 lines of 
otherwise untested code, and there's a bug within it *somewhere*... good 
luck.


Obviously you might very well have *meant* to write x = f x. But would 
it be possible to add some kind of optional compiler warning to find 
such assignments? It can be a nightmare trying to track down where you 
made the mistake...


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Brent Yorgey

 It's really maddening to write 50,000 lines of code, eventually get it
 to compile, run it, and have the program lock up and start consuming so
 much virtual memory that the entire PC becomes unstable within seconds.

(This isn't helped by the fact that Ctrl+C doesn't seem to make either
 GHCi or GHC-compiled programs halt...) Now you have 50,000 lines of
 otherwise untested code, and there's a bug within it *somewhere*... good
 luck.


Well, this is why you should test your program in bits and pieces before you
get to that point.  Writing 50,000 LOC before you even run your first test
is a horrible idea in any programming language.

-Brent
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread David Roundy
On Thu, Aug 30, 2007 at 06:16:12PM +0100, Andrew Coppin wrote:
 Obviously you might very well have *meant* to write x = f x. But would 
 it be possible to add some kind of optional compiler warning to find 
 such assignments? It can be a nightmare trying to track down where you 
 made the mistake...

If you enable -Wall, ghc will warn you about this, provided that x was
already bound in this context.
-- 
David Roundy
http://www.darcs.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Dan Piponi
On 8/30/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 Obviously you might very well have *meant* to write x = f x. But would
 it be possible to add some kind of optional compiler warning to find
 such assignments?

The thing that convinced me to learn Haskell in the first place was
the fact that you could write x = f x. Equations where you refer to
the same variable on the left and right hand sides are the bread of
butter and mathematics, and I was really pleased to find a programming
language that let me do the same. So to me the idea of having a
warning for this is a bit like putting a sign on bottled water saying
Warning: Contents may be wet. But that's just me. :-)

Still, it might be useful to for the compiler to warn when a newly
introduced name shadows another one.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Paul Hudak

Andrew Coppin wrote:
OK, so it's only tangentally related, but... do you have *any idea* 
how many times I've written something like


 let x = (some complex function of x)
 in (some other complex function of x)

when in fact what I *meant* to do was type x' instead of x?! 


I try not to use primes (x', x'', etc.) on variables for exactly this 
reason, and instead try to use more descriptive names, such as newx, 
or y, or whatever.  Of course you can still make typing mistakes, but 
that's always the case...


   -Paul

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Chaddaï Fouché
Another interesting example of the x = f x use :

coins = [1,2,5,10,20,50,100,200]

beautiful = foldl (\without p -
  let (poor,rich) = splitAt p without
  with = poor ++
 zipWith (++) (map (map (p:)) with)
  rich
  in with
 ) ([[]] : repeat [])

I don't remember who wrote this code (I rewrote it from memory since
it impressed me quite a bit), but it's a very fast and beautiful (in
my eyes at least) solution to the menu problem :
(beautiful coins !! 200) would give you all the set of coins you could
use to pay for 200, in less than 40ms on my computer...

But, even more trivial... You use this all the time when you define
recursive function, you know ? You would need to add a rec keyword
to the language if you disallowed this.

Myself I'm a big fan of the point-free style (to a limit) and find
that it scale very well indeed when you begin to name the combination
of functions you want to use.

-- 
Jedaï
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Albert Y. C. Lai

Peter Hercek wrote:

So the question is what am I missing? Any nice use cases where
 fixed point search is so good that it is worth the trouble with
 figuring out new and new variable names for essentially the same
 stuff?


When I write functional code, I do find myself writing recursions much 
more often than writing imperative-wannabe assignments. I appreciate 
that Haskell's let defaults to recursion. I don't appreciate that 
OCaml makes a distinction between let and letrec, since every time I 
change a non-recursive definition to a recursive one, I am prone to 
forget to change let to letrec, IOW it is a hidden hazard to 
maintenance and evolution.


When I write imperative code in Haskell, the notation is so different 
from functional code that let doesn't even come into the equation.


When I write imperative code in imperative languages, my mental model 
treats x:=x+1 as x'=x+1 and y'=y and z'=z and ..., following several 
treatises on imperative semantics(*). Going back to functional 
programming, when I do write imperative-wannabe assignments, I totally 
like having names x, x', x'', etc., since they're in my head anyway.


Underlying all this is probably the soberness of recognizing that = is 
not :=.



(*) Such as:

Eric C. R. Hehner, A Practical Theory of Programming. First edition 
Springer 1993. Current edition at

http://www.cs.toronto.edu/~hehner/aPToP/

C. A. R. Hoare and He Jifeng, Unifying Theories of Programming. 
Prentice Hall 1998.


The Z specification language.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Peter Verswyvelen
F# and Concurrent Clean introduced special syntax for doing this. Basically
they just invent new names for you.

In Haskell (warning: I'm a newbie, so take this with a grain of salt), I
guess you just use monads if you want to pass a value from one function to
another under some context, or you could just make your own little much
simpler combinator like:

infixl 0 \ -- I just took the first weird symbol combination that came to
mind, this does not mean anything (I hope ;-)

x \ fx = fx x

f x = x * scale \ \x -
  x + transform \ \x -
  g x

like this you don't have to invent new names, and you don't have to type
much more.

I'm sure this silly sequencing operator must already exist in the library
somewhere?

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Peter Hercek
Sent: Thursday, August 30, 2007 6:18 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] let and fixed point operator

Hi,

I find the feature that the construct let x = f x in expr
  assigns fixed point of f to x annoying. The reason is that
  I can not simply chain mofifications a variable like e.g. this:

f x =
   let x = x * scale in
   let x = x + transform in
   g x

When one is lucky then it results in a compile error; in worse
  cases it results in stack overflow in runtime. The annoying
  part is figuring out new and new variable names for essentially
  the same thing to avoid the search/evaluation of the fixed point.

I suppose Haskell was designed so that it makes sense. The only
  usage I can see is like this:

let fact = \x - if x == 0 then 1 else x * fact (x-1) in

   ... but that is not any shorter than:

let fact x = if x == 0 then 1 else x * fact (x-1) in

So the question is what am I missing? Any nice use cases where
  fixed point search is so good that it is worth the trouble with
  figuring out new and new variable names for essentially the same
  stuff?

Peter.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Henning Thielemann

On Thu, 30 Aug 2007, Peter Verswyvelen wrote:

 infixl 0 \ -- I just took the first weird symbol combination that came to
 mind, this does not mean anything (I hope ;-)

 x \ fx = fx x

 f x = x * scale \ \x -
   x + transform \ \x -
   g x

 like this you don't have to invent new names, and you don't have to type
 much more.

 I'm sure this silly sequencing operator must already exist in the library
 somewhere?

Sure, its name is (=). It must be used for the Identity monad, as
mentioned by Derek Elkins earlier in this thread.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Andrew Coppin

Brent Yorgey wrote:



It's really maddening to write 50,000 lines of code, eventually get it
to compile, run it, and have the program lock up and start
consuming so
much virtual memory that the entire PC becomes unstable within
seconds.

(This isn't helped by the fact that Ctrl+C doesn't seem to make
either
GHCi or GHC-compiled programs halt...) Now you have 50,000 lines of
otherwise untested code, and there's a bug within it
*somewhere*... good
luck.


Well, this is why you should test your program in bits and pieces 
before you get to that point.  Writing 50,000 LOC before you even run 
your first test is a horrible idea in any programming language.


Horrible? Yes.

Avoidable? Not always, sadly...

(NB. 50,000 is an exaggeration. I've never written a program that large 
in my entire life in any programming language I've ever used.)


The problem is that, depending on the program, sometimes you have to 
write quite a lot of infrastructure before you get to the point where 
there's anything finished enough to test. Obviously it's better to avoid 
that happening, but that's easier said then done!


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Andrew Coppin

David Roundy wrote:

On Thu, Aug 30, 2007 at 06:16:12PM +0100, Andrew Coppin wrote:
  
Obviously you might very well have *meant* to write x = f x. But would 
it be possible to add some kind of optional compiler warning to find 
such assignments? It can be a nightmare trying to track down where you 
made the mistake...



If you enable -Wall, ghc will warn you about this, provided that x was
already bound in this context.
  


Most excellent. GHC saves the day again...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Andrew Coppin

Dan Piponi wrote:

On 8/30/07, Andrew Coppin [EMAIL PROTECTED] wrote:
  

Obviously you might very well have *meant* to write x = f x. But would
it be possible to add some kind of optional compiler warning to find
such assignments?



The thing that convinced me to learn Haskell in the first place was
the fact that you could write x = f x. Equations where you refer to
the same variable on the left and right hand sides are the bread of
butter and mathematics, and I was really pleased to find a programming
language that let me do the same.


Yeah, but... programs aren't like mathematics. I know people claim that 
they are, but they aren't.


In mathematics, if you write x = f y you mean that these two 
expressions are equal. In Haskell, if you say x = f y you mean *make* 
then equal!


(Let us not even go into the times when expressions like z = f z 
actually means z[n+1] = f [z]...)



So to me the idea of having a
warning for this is a bit like putting a sign on bottled water saying
Warning: Contents may be wet. But that's just me. :-)
  


Well, it's definitely a valid thing to want to do, which is why I asked 
for a *warning* not an error. ;-) Still, this seems to be an extremely 
common way for me to hurt myself, so...



Still, it might be useful to for the compiler to warn when a newly
introduced name shadows another one.
  


...or that...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Dan Piponi
On 8/30/07, Andrew Coppin [EMAIL PROTECTED] wrote:

 Yeah, but... programs aren't like mathematics. I know people claim that
 they are, but they aren't.

But the raison d'etre of Haskell is to make programming more like
mathematics. That motivates everything from the fact that it's a
declarative language, and the support for equational reasoning, to the
fact that IO happens in a monad, and the option to use primes on
variables names.

 In mathematics, if you write x = f y you mean that these two
 expressions are equal. In Haskell, if you say x = f y you mean *make*
 then equal!

Haskell is a declarative language, not an imperative language. When
you write x = f x in Haskell, you're declaring to the compiler that
x equals f x. In an imperative language like Java, the line x = f(x)
gives the compiler the imperative to emit instructions to store the
value of f(x) in a 'box' called x. In Haskell, there is no box.

(When you get down to the nuts and bolts, a Haskell compiler and a
Java compiler may ultimately actually do the same thing here, but the
way you think about a language is as important as what instructions
the code generator emits.)
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread jerzy . karczmarczuk
Dan Piponi writes: 


In mathematics, if you write x = f y you mean that these two
expressions are equal. In Haskell, if you say x = f y you mean *make*
then equal!




Haskell is a declarative language, not an imperative language. When
you write x = f x in Haskell, you're declaring to the compiler that
x equals f x. In an imperative language like Java, the line x = f(x)
gives the compiler the imperative to emit instructions to store the
value of f(x) in a 'box' called x. In Haskell, there is no box.


Well, there are boxes...
But there also thunks and latent, yet-unevaluated graphs... 


Anyway, I believe strongly that ALL people who have problems with the
Haskell protocole, and they are numerous, I teach a good sample of them,
should be encouraged to learn Prolog. IN DEPTH, and I mean it, Andrew
Coppin and Peter Hercek ! 


In Prolog A=B is the unification, which is a bit more than equality, and
something much more aggressive than an assignment. When you REALLY
understand unification, it will be easier to see the lazy instantiation
of the Haskell assignment, and, additionally, it becomes much more easy
to understand the automatic inference of types, which sooner or later
must be harnessed by all Haskell programmers... 

The best. 

Jerzy Karczmarczuk 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Dan Piponi
On 8/30/07, [EMAIL PROTECTED]
[EMAIL PROTECTED] wrote:
 Dan Piponi writes:
  In Haskell, there is no box.

 Well, there are boxes...
 But there also thunks and latent, yet-unevaluated graphs...

But the point of Haskell is to provide an abstraction that hides these
details from you. (Though ultimately it's a leaky abstraction and
there comes a point where you do need to know about these things.)

 Anyway, I believe strongly that ALL people who have problems with the
 Haskell protocole, and they are numerous, I teach a good sample of them,
 should be encouraged to learn Prolog.

I'd second that. It's hard to see the difference between declarative
and imperative programming when you only have one instance of a
declarative language from which to generalise.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread Derek Elkins
On Thu, 2007-08-30 at 23:58 +0200, [EMAIL PROTECTED]
wrote:
 Dan Piponi writes: 
 
  In mathematics, if you write x = f y you mean that these two
  expressions are equal. In Haskell, if you say x = f y you mean *make*
  then equal!
  
 
  Haskell is a declarative language, not an imperative language. When
  you write x = f x in Haskell, you're declaring to the compiler that
  x equals f x. In an imperative language like Java, the line x = f(x)
  gives the compiler the imperative to emit instructions to store the
  value of f(x) in a 'box' called x. In Haskell, there is no box.
 
 Well, there are boxes...
 But there also thunks and latent, yet-unevaluated graphs... 
 
 Anyway, I believe strongly that ALL people who have problems with the
 Haskell protocole, and they are numerous, I teach a good sample of them,
 should be encouraged to learn Prolog. IN DEPTH, and I mean it, Andrew
 Coppin and Peter Hercek ! 
 
 In Prolog A=B is the unification, which is a bit more than equality, and
 something much more aggressive than an assignment. When you REALLY
 understand unification, it will be easier to see the lazy instantiation
 of the Haskell assignment, and, additionally, it becomes much more easy
 to understand the automatic inference of types, which sooner or later
 must be harnessed by all Haskell programmers... 

One should learn Prolog anyway.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] let and fixed point operator

2007-08-30 Thread ok

What is so bad about

f x = g x''
  where x'' = x' + transform
x'  = x  * scale

(if you really hate inventing temporary names, that is).


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe