Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-15 Thread J. Stutterheim
The IDE still works for Windows, but it isn't actively developed anymore (though bugs and minor annoyances are still being fixed). For Mac and Linux we now have a command line tool that uses the IDE's codebase. Personally, I just use vim (of course you can use any editor you prefer; vim comes with syntax colouring for Clean out of the box) for coding and then use a new CLI tool called CPM (Clean Project Manager) to build my project. This tool will be included by default with the next Clean release. I doubt the IDE will be resurrected on Mac and Linux, because it is just too much work to port Object IO (the GUI library) to those platforms and our own Mac/Linux users strongly prefer their own editors over the IDE anyway. For people that prefer a non-CLI workflow, we are actually looking into making a web-based IDE in iTasks (although it doesn't have a very high priority at the moment).The OS dependency for dynamics stems from the fact that the Clean dynamics are quite a bit more powerful than Haskell's. For example, using dynamics, it is possible to send arbitrary functions to another Clean application, which can then dynamically link these functions in at runtime and immediately execute them. It doesn't even need to be the same program, which Cloud Haskell does require(and theoretically, it can even be another OS). This advanced dynamic linking feature requires intimate knowledge of the target OS' binary representation. (I would actually really like to see Haskell's dynamics system to become as powerful as Clean's; it also supports polymorphism, for example)On Jul 15, 2013, at 04:31 AM, "Richard A. O'Keefe" o...@cs.otago.ac.nz wrote: On 13/07/2013, at 11:27 PM, J. Stutterheim wrote:- they then abandoned the Macintosh world forWindows. The Mac IDE was killed off; there isnow an IDE for Windows but not MacOS or Linux.The good news is that the latest version of Clean[2] and its code generator[3] now works fine again on 64 bit Mac OS X Is that still the command-line tools, or has the IDE been resurrected? - other major features remain Windows-onlyThe bad news is that this is true to some extend; the dynamics system is still largely Windows-only. However, this is the only language feature I can think of that really is Windows-only. I have never been able to understand why there should be ANY OS-dependency in the dynamics feature. - the available books about Clean are way out ofdate, several drafts of other books remainincomplete.- the documentation (like the Report) has always beenrather amateurish and incomplete. Certainlycompared with the Haskell documentation.An iTasks book is actually in the works, which will contain a fair bit of Clean (although it is not a dedicated Clean book). There are also concrete plans to update the language manual soon-ish. Not to be offensive, because after saying "Denk U" I have no more Dutch words I can use, but it would really pay to find a native speaker of English to give the manual a final polish.- there is nothing to compare with the Haskell Platform.Actually, yes there is[4]. A misundertanding. "Nothing to compare with" is idiomatic for "nothing of comparable size to". Yes, you _can_ compare the Clean Platform with the Haskell Platform; it's a lot smaller. It can be described as a mix between Haskell Platform and a mini Hackage-like repository. There is no such thing as a Clean alternative to cabal install, though.Keep in mind that there is only a handful of people working on Clean, while Haskell has a huge community in comparison. Haskell has always benefited from - openness - multiple implementations - documentation ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-15 Thread Richard A. O'Keefe

On 15/07/2013, at 8:23 PM, J. Stutterheim wrote:
 The OS dependency for dynamics stems from the fact that the Clean dynamics 
 are quite a bit more powerful than Haskell's. For example, using dynamics, it 
 is possible to send arbitrary functions to another Clean application, which 
 can then dynamically link these functions in at runtime and immediately 
 execute them. It doesn't even need to be the same program, which Cloud 
 Haskell does require (and theoretically, it can even be another OS). This 
 advanced dynamic linking feature requires intimate knowledge of the target 
 OS' binary representation.

There is no obvious reason why it should.
Imagine a programming language implementation where a function
is compiled to some abstract representation (like Kistler's Juice)
and a native representation is added on loading or on first use.
For Oberon, Kistler found that transmitting compressed abstract
syntax trees and generating native code on reception took less
time and yielded better code than sending native code.  Even when
reading from a local disc, loading compressed ASTs and generating
native code on the fly was faster than a conventional dynamic linker.

A major issue here, of course, is that Windows could be 32-bit or
64-bit, x86 or ARM, and even if you restrict attention to one of
these combinations, there are things like exactly what SIMD
instructions are available.

 (I would actually really like to see Haskell's dynamics system to become as 
 powerful as Clean's; it also supports polymorphism, for example)

Perhaps you could say something about the following problem:

I have a data structure that includes some functions.
These functions use version X of module M.
I send that data structure to another application,
which is using version Y of module M, where Y /= X.

What happens?  This is the primary reason why Erlang has not
imitated Kali Scheme, which could also send functions.
For that matter, what happens if the function is sent to another
application (on a remote machine) that doesn't have _any_
version of module M and doesn't know where to find one?

I am _not_ suggesting that these are problems that Clean could not solve
or has not solved.  On the contrary, I'm saying that it would be very
interesting to hear how Clean has solved them.

From a security point of view, of course, failing to practice Safe Hex
is a bit worrying, but proof-carrying code and signatures can go some
way towards addressing that concern.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-14 Thread Richard A. O'Keefe

On 12/07/2013, at 6:12 PM, Andreas Abel wrote:
[I can't try your F# example but ocaml does something different.]

Yes.  They are different languages.

By the way, I used the F# that comes with Mono.

 On 12.07.2013 02:22, Richard A. O'Keefe wrote:
 For what it's worth,
 
 let x = 1 in
 -   let x = x+1 in
 - let x = x+2 in
 -   x;;
 
 prints
 
 val it : int = 4
 
 in the F# interactive system, but
 
 let x = 1 in
 - let x = x+1 in
 - let x = x+2 in
 -   x;;
 
  let p = e in body
 
 is just
 
  (\ p - body) e
 
 it cannot be simpler than that.

True.  But it *can* be more complex than that,
and in F# it *is*.

  So I do not see your point.

The differently indented versions of the nested let do
different things.  Although F# is a descendant of Ocaml,
it is not the case that all lets in F# allow shadowing.

That's the point.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-14 Thread Richard A. O'Keefe

On 13/07/2013, at 11:27 PM, J. Stutterheim wrote:
 - they then abandoned the Macintosh world for
  Windows.  The Mac IDE was killed off; there is
  now an IDE for Windows but not MacOS or Linux.
 
 The good news is that the latest version of Clean[2] and its code 
 generator[3] now works fine again on 64 bit Mac OS X

Is that still the command-line tools, or has the IDE been resurrected?

 - other major features remain Windows-only
 
 The bad news is that this is true to some extend; the dynamics system is 
 still largely Windows-only. However, this is the only language feature I can 
 think of that really is Windows-only.

I have never been able to understand why there should be ANY
OS-dependency in the dynamics feature.

 - the available books about Clean are way out of
  date, several drafts of other books remain
  incomplete.
 - the documentation (like the Report) has always been
  rather amateurish and incomplete.  Certainly
  compared with the Haskell documentation.
 
 An iTasks book is actually in the works, which will contain a fair bit of 
 Clean (although it is not a dedicated Clean book). There are also concrete 
 plans to update the language manual soon-ish.

Not to be offensive, because after saying Denk U I have no more
Dutch words I can use, but it would really pay to find a native
speaker of English to give the manual a final polish.
 
 - there is nothing to compare with the Haskell Platform.
 
 Actually, yes there is[4].

A misundertanding.  Nothing to compare with is idiomatic for
nothing of comparable size to.  Yes, you _can_ compare the
Clean Platform with the Haskell Platform; it's a lot smaller.

 It can be described as a mix between Haskell Platform and a mini Hackage-like 
 repository. There is no such thing as a Clean alternative to cabal install, 
 though.
 
 Keep in mind that there is only a handful of people working on Clean, while 
 Haskell has a huge community in comparison. 

Haskell has always benefited from
- openness
- multiple implementations
- documentation


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-13 Thread J. Stutterheim
I currently work at the Radboud University where Clean is being developed. As 
such, I use it daily. Coming from Haskell, I have to admit that I never really 
got used to the let-before syntax, exactly for the reasons described in the 
previous emails. However, it does have some merit. In combination with 
uniqueness typing, the compiler can do destructive updates on the variables in 
the let-before blocks, making the generated code more efficient.

Possibly a bit off-topic, but please allow me to give an update about the 
latest status of Clean (mixed with some personal opinion ;)

 Clean is relatively unknown because
 - they started in the Macintosh world, and when
   they provided a compiler for the Unix world,
   they did not port their modern graphics and
   I/O library to it.  So you could never write
   a program that would run on Macs and other things.

Object IO (the graphics library) will probably never work for systems other 
than Windows because f low priority and a lack of manpower. This is admittedly 
unfortunate if you want to write native client-side GUIs. Currently, most of 
Clean's progress is driven by the iTask System[1], which provides a web GUI.

 - they then abandoned the Macintosh world for
   Windows.  The Mac IDE was killed off; there is
   now an IDE for Windows but not MacOS or Linux.

The good news is that the latest version of Clean[2] and its code generator[3] 
now works fine again on 64 bit Mac OS X (I would rate it as advanced beta, or 
perhaps even RC quality). Linux 64 support is currently being stabilised 
(currently alpha quality). Hopefully we will be able to create a new Clean 
release for Mac OS X, Linux and Windows this year. It will then also contain a 
command-line based build tool for Clean IDE project files.

 - other major features remain Windows-only

The bad news is that this is true to some extend; the dynamics system is still 
largely Windows-only. However, this is the only language feature I can think of 
that really is Windows-only.

 - the change from Clean 1.3 to Clean 2 was huge,
   like I mentioned above, none of my code survived
   the change, and there was at that time no
   conversion program

Warning, personal opinion ahead: that's the price of progress I suppose :) 
Because Clean has a very small user base, the language itself is still 
evolving, and there is no release schedule of any kind, it doesn't really pay 
to have a complicated deprecation process.

 - the available books about Clean are way out of
   date, several drafts of other books remain
   incomplete.
 - the documentation (like the Report) has always been
   rather amateurish and incomplete.  Certainly
   compared with the Haskell documentation.

An iTasks book is actually in the works, which will contain a fair bit of Clean 
(although it is not a dedicated Clean book). There are also concrete plans to 
update the language manual soon-ish.

 - there is nothing to compare with the Haskell Platform.

Actually, yes there is[4]. It can be described as a mix between Haskell 
Platform and a mini Hackage-like repository. There is no such thing as a Clean 
alternative to cabal install, though.

Keep in mind that there is only a handful of people working on Clean, while 
Haskell has a huge community in comparison. This makes it hard to keep up with 
advanced language features.


- Jurriën

[1] http://wiki.clean.cs.ru.nl/ITasks
[2] https://svn.cs.ru.nl/cgi-bin/admin/info/clean-compiler
[3] https://svn.cs.ru.nl/cgi-bin/admin/info/clean-code-generator
[4] https://svn.cs.ru.nl/cgi-bin/admin/info/clean-platform
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-12 Thread Andreas Abel

On 12.07.2013 02:22, Richard A. O'Keefe wrote:

For what it's worth,


let x = 1 in

-   let x = x+1 in
- let x = x+2 in
-   x;;

prints

val it : int = 4

in the F# interactive system, but


let x = 1 in

- let x = x+1 in
- let x = x+2 in
-   x;;

prints Duplicate definition of x at the second line.


Since silverlight does not work properly on my systems, I cannot 
tryfsharp.org.  I can try ocaml, which does not use indentation, and 
there the value is 4, and there is no ambiguity at all.


  let p = e in body

is just

  (\ p - body) e

it cannot be simpler than that.  So I do not see your point.

--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-11 Thread oleg

I'd like to emphasize that there is a precedent to non-recursive let
in the world of (relatively pure) lazy functional programming.
The programming language Clean has such non-recursive let and uses
it and the shadowing extensively. They consider shadowing a virtue,
for uniquely typed data.

Richard A. O'Keefe wrote
  let (x,s) = foo 1 [] in
  let (y,s) = bar x s in
  let (z,s) = baz x y s in ...
 I really wish you wouldn't do that.
 ...
 I find that that when the same name gets reused like
 that I get very confused indeed about which one I am
 looking at right now.
 ...
 If each instance of the variable is labelled with a
 sequence number, I don't get confused because each
 variable has a different name and I can *see* which
 one this is.

 Yes, sequence numbering variable states is a chore for
 the person writing the code, but it's a boon for the
 person reading the code.

Let me point out the latest Report on the programming language Clean
http://clean.cs.ru.nl/download/doc/CleanLangRep.2.2.pdf
specifically PDF pages 38-40 (Sec 3.5.4 Let-Before Expression). Let me
quote the relevant part:

Many of the functions for input and output in the CLEAN I/O library
are state transition functions. Such a state is often passed from one
function to another in a single threaded way (see Chapter 9) to force
a specific order of evaluation. This is certainly the case when the
state is of unique type. The threading parameter has to be renamed to
distinguish its different versions. The following example shows a
typical example: Use of state transition functions. The uniquely typed
state file is passed from one function to another involving a number
of renamings: file, file1, file2)

readchars:: *File - ([Char], *File)
readchars file
| not ok   = ([],file1)
| otherwise = ([char:chars], file2)
where
  (ok,char,file1) = freadc file
  (chars,file2)   = readchars file1

This explicit renaming of threaded parameters not only looks very
ugly, these kind of definitions are sometimes also hard to read as
well (in which order do things happen? which state is passed in which
situation?). We have to admit: an imperative style of programming is
much easier to read when things have to happen in a certain order such
as is the case when doing I/O. That is why we have introduced
let-before expressions.

It seems the designers of Clean have the opposite view on the explicit
renaming (that is, sequential numbering of unique variables).

Let-before expressions have a special scope rule to obtain an
imperative programming look. The variables in the left- hand side of
these definitions do not appear in the scope of the right-hand side of
that definition, but they do appear in the scope of the other
definitions that follow (including the root expression, excluding
local definitions in where blocks.

Notice that a variable defined in a let-before expression cannot be
used in a where expression. The reverse is true however: definitions
in the where expression can be used in the let before expression.  Use
of let before expressions, short notation, re-using names taking use
of the special scope of the let before)

readchars:: *File - ([Char], *File)
readchars file
#(ok,char,file)   = freadc file
|not ok   = ([],file)
#(chars,file) = readchars file
=([char:chars], file)

The code uses the same name 'file' all throughout, shadowing it
appropriately. Clean programmers truly do all IO in this style, see
the examples in
http://clean.cs.ru.nl/download/supported/ObjectIO.1.2/doc/tutorial.pdf

[To be sure I do not advocate using Clean notation '#' for
non-recursive let in Haskell. Clean is well-known for its somewhat
Spartan notation.]

State monad is frequently mentioned as an alternative. But monads are
a poor alternative to uniqueness typing. Granted, if a function has
one unique argument, e.g., World, then it is equivalent to the ST (or
IO) monad. However, a function may have several unique arguments. For
example, Arrays in Clean are uniquely typed so they can be updated
destructively. A function may have several argument arrays. Operations
on one array have to be serialized (which is what uniqueness typing
accomplishes) but the relative order among operations on distinct
arrays may be left unspecified, for the compiler to determine.

Monads, typical of imperative programs, overspecify the order. For
example,
do
  x - readSTRef ref1
  y - readSTRef ref2
  writeSTRef ref2 (x+y)

the write to ref2 must happen after reading ref2, but ref1 could be
read either before or after ref2. (Assuming ref2 and ref1 are distinct
-- the uniqueness typing will make sure of it.)  Alas, in a monad we
cannot leave the order of reading ref1 and ref2 

Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-11 Thread Richard A. O'Keefe

On 11/07/2013, at 6:16 PM, o...@okmij.org wrote:

 
 I'd like to emphasize that there is a precedent to non-recursive let
 in the world of (relatively pure) lazy functional programming.

So what?  You can find precedents for almost anything.
I could even point you to a lazy mostly-functional language
with assignment statements in which an identifier occurrence
may refer to two different variables in the course of execution.

Having a precedent doesn't mean that it's a good thing.

 The programming language Clean has such non-recursive let

I am familiar with Clean and used it quite a bit for several years.
My experience with that Clean idiom is *WHY* I hate this usage and
love monads.
 
 Let me point out the latest Report on the programming language Clean
http://clean.cs.ru.nl/download/doc/CleanLangRep.2.2.pdf

which I already have.  If the Clean developers hadn't decided to
concentrate on Windows, leaving the systems I used to wither,
and if they hadn't made fairly massive changes to the language
that broke all my code, it's _possible_ that I might eventually have
come to regard this style as acceptable.

 It seems the designers of Clean have the opposite view on the explicit
 renaming (that is, sequential numbering of unique variables).

That is so.  If that's what you want, you know where to find it.

Like I said, precedent is not proof of goodness.

 
readchars:: *File - ([Char], *File)
readchars file
#(ok,char,file)   = freadc file
|not ok   = ([],file)
#(chars,file) = readchars file
=([char:chars], file)

This is *PRECISELY* the kind of stuff that I find confusing.
If they would just *NUMBER* the states so that I can tell what
is happening when, I would be so much happier.

 The code uses the same name 'file' all throughout, shadowing it
 appropriately. Clean programmers truly do all IO in this style, see
 the examples in
http://clean.cs.ru.nl/download/supported/ObjectIO.1.2/doc/tutorial.pdf
 
 [To be sure I do not advocate using Clean notation '#' for
 non-recursive let in Haskell. Clean is well-known for its somewhat
 Spartan notation.]

I wouldn't call Clean Spartan.  Clean syntax is elaborate.
It achieves brevity not by avoiding keywords but by using
punctuation marks for them, as in [t] vs [!t] vs [|t]
-- does it leap to the eye that [t] is lazy, [!t] is head
strict, and [|t] is strictness-polymorphic? --
and the very important distinction between
a *function* f x = e and a *macro* f x :== e.
(There's a reason why the higher-order list processing
'functions' are actually 'macros'.  See page 109 of the report.
There's precedent for a LOT of things that I don't want in Haskell.)

 State monad is frequently mentioned as an alternative. But monads are
 a poor alternative to uniqueness typing.

In this particular case, uniqueness typing is an utter red herring.
People are advocating state monads JUST TO HIDE THE WIRING, not to
get the effect of destructive assignment.
I *agree* that uniqueness typing is a fine thing and recommended it
to the Mercury developers, who adopted it.

I don't care whether they are called monads, state combinators,
or weeblefretzers.  What I care about is that that
 - the states are HIDDEN from the human reader and
 - they are AUTOMATICALLY wired up correctly for the author.

Suppose we have

# (x,s) = foo s
# (y,z) = bar x s
# (z,s) = ugh x y s

where my finger slipped on the s key in the second line and
pressed the z key instead.  Precisely BECAUSE the variable name
is the same each time, nobody notices, not the compiler, not you,
not me.  The program just goes wrong.

With numbered variables,

let (x,s1) = foo s0
(y,z2) = bar x s1
(z,s3) = ugh x y s2
in ...

the compiler notices that s2 isn't defined.

With suitable combinators,

foo = \x - bar x = \y - ugh x y ...

nobody can make the mistake in the first place,
because the state variable isn't _there_ to get wrong.
 
 Why Clean is relatively unknown? Well, why is Amiga?

Clean is relatively unknown because
 - they started in the Macintosh world, and when
   they provided a compiler for the Unix world,
   they did not port their modern graphics and
   I/O library to it.  So you could never write
   a program that would run on Macs and other things.
 - they then abandoned the Macintosh world for
   Windows.  The Mac IDE was killed off; there is
   now an IDE for Windows but not MacOS or Linux.
 - other major features remain Windows-only
 - the change from Clean 1.3 to Clean 2 was huge,
   like I mentioned above, none of my code survived
   the change, and there was at that time no
   conversion program
 - the available books about Clean are way out of
   date, several drafts of other books remain
   incomplete.
 - the documentation (like the Report) has always been
   rather amateurish and incomplete.  Certainly
   compared with the Haskell documentation.
 - 

Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Andreas Abel

Hi Oleg,

just now I wrote a message to haskell-pr...@haskell.org to propose a 
non-recursive let.  Unfortunately, the default let is recursive, so we 
only have names like let' for it.  I also mentioned the ugly workaround 
(- return $) that I was shocked to see the first time, but use myself 
sometimes now.


Cheers,
Andreas

On 10.07.2013 09:34, o...@okmij.org wrote:

Andreas wrote:

The greater evil is that Haskell does not have a non-recursive let.
This is source of many non-termination bugs, including this one here.
let should be non-recursive by default, and for recursion we could have
the good old let rec.


Hear, hear! In OCaml, I can (and often do) write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

In Haskell I'll have to uniquely number the s's:

 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...

and re-number them if I insert a new statement. BASIC comes to mind. I
tried to lobby Simon Peyton-Jones for the non-recursive let a couple
of years ago. He said, write a proposal. It's still being
written... Perhaps you might want to write it now.

In the meanwhile, there is a very ugly workaround:

 test = runIdentity $ do
  (x,s) - return $ foo 1 []
  (y,s) - return $ bar x s
  (z,s) - return $ baz x y s
  return (z,s)

After all, bind is non-recursive let.






--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Edward Z. Yang
In my opinion, when you are rebinding a variable with the same name,
there is usually another way to structure your code which eliminates
the variable.

If you would like to write:

let x = foo input in
let x = bar x in
let x = baz x in

instead, write

baz . bar . foo $ input

If you would like to write

let (x,s) = foo 1 [] in
let (y,s) = bar x s in
let (z,s) = baz x y s in

instead, use a state monad.

Clearly this will not work in all cases, but it goes pretty far,
in my experience.

Edward

Excerpts from Andreas Abel's message of Wed Jul 10 00:47:48 -0700 2013:
 Hi Oleg,
 
 just now I wrote a message to haskell-pr...@haskell.org to propose a 
 non-recursive let.  Unfortunately, the default let is recursive, so we 
 only have names like let' for it.  I also mentioned the ugly workaround 
 (- return $) that I was shocked to see the first time, but use myself 
 sometimes now.
 
 Cheers,
 Andreas
 
 On 10.07.2013 09:34, o...@okmij.org wrote:
  Andreas wrote:
  The greater evil is that Haskell does not have a non-recursive let.
  This is source of many non-termination bugs, including this one here.
  let should be non-recursive by default, and for recursion we could have
  the good old let rec.
 
  Hear, hear! In OCaml, I can (and often do) write
 
   let (x,s) = foo 1 [] in
   let (y,s) = bar x s in
   let (z,s) = baz x y s in ...
 
  In Haskell I'll have to uniquely number the s's:
 
   let (x,s1)  = foo 1 [] in
   let (y,s2)  = bar x s1 in
   let (z,s3)  = baz x y s2 in ...
 
  and re-number them if I insert a new statement. BASIC comes to mind. I
  tried to lobby Simon Peyton-Jones for the non-recursive let a couple
  of years ago. He said, write a proposal. It's still being
  written... Perhaps you might want to write it now.
 
  In the meanwhile, there is a very ugly workaround:
 
   test = runIdentity $ do
(x,s) - return $ foo 1 []
(y,s) - return $ bar x s
(z,s) - return $ baz x y s
return (z,s)
 
  After all, bind is non-recursive let.
 
 
 
 

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Ertugrul Söylemez
o...@okmij.org wrote:

 Hear, hear! In OCaml, I can (and often do) write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

 In Haskell I'll have to uniquely number the s's:

 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...

This isn't a case for non-recursive let.  It is one of the rare cases
where you might actually consider using a state monad.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Andreas Abel

On 10.07.2013 10:16, Ertugrul Söylemez wrote:

o...@okmij.org wrote:


Hear, hear! In OCaml, I can (and often do) write

 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

In Haskell I'll have to uniquely number the s's:

 let (x,s1)  = foo 1 [] in
 let (y,s2)  = bar x s1 in
 let (z,s3)  = baz x y s2 in ...


This isn't a case for non-recursive let.  It is one of the rare cases
where you might actually consider using a state monad.


Except when you are implementing the state monad (giggle):


http://hackage.haskell.org/packages/archive/mtl/2.1/doc/html/src/Control-Monad-State-Class.html#state


--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Alberto G. Corona
I think that a non-non recursive let could be not compatible with the pure
nature of Haskell.

Let is recursive because, unlike in the case of other
languages, variables are not locations for storing values, but the
expressions on the right side of the equality themselves. And obviously it
is not possible for a variable-expression to be two expressions at the same
time. The recursiveness is buildt-in. It comes from its pure nature.

For a non recursive version of let, it would be necessary to create a new
closure on each line, to create a new variable-expression with the same
name, but within the new closure. A different variable after all. That is
what the example with the Identity (and the state monad) does.

So I think that the ugly return example or the more elegant state monad
alternative is the right thing to do.


2013/7/10 Ertugrul Söylemez e...@ertes.de

 o...@okmij.org wrote:

  Hear, hear! In OCaml, I can (and often do) write
 
  let (x,s) = foo 1 [] in
  let (y,s) = bar x s in
  let (z,s) = baz x y s in ...
 
  In Haskell I'll have to uniquely number the s's:
 
  let (x,s1)  = foo 1 [] in
  let (y,s2)  = bar x s1 in
  let (z,s3)  = baz x y s2 in ...

 This isn't a case for non-recursive let.  It is one of the rare cases
 where you might actually consider using a state monad.


 Greets,
 Ertugrul

 --
 Not to be or to be and (not to be or to be and (not to be or to be and
 (not to be or to be and ... that is the list monad.

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




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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Ertugrul Söylemez
o...@okmij.org wrote:

  If you would like to write
 
  let (x,s) = foo 1 [] in
  let (y,s) = bar x s in
  let (z,s) = baz x y s in
 
  instead, use a state monad.

 Incidentally I did write almost exactly this code once. Ironically, it
 was meant as a lead-on to the State monad.

 But there have been other cases where State monad was better
 avoided. For instance, functions like foo and bar are already written
 and they are not in the state monad.

It's fine to use `state` or the StateT constructor here.


 For example, foo may take a non-empty Set and return the minimal
 element and the set without the minimal element. There are several
 such handy functions in Data.Set and Data.Map. Injecting such
 functions into a Set monad for the sake of three lines seems overkill.

Not a Set monad, but a state monad.  Other examples include 'random' and
'randomR', where you can just apply 'state':

getRandom  = state random
getRandomR = state . randomR

I do this a lot.


 Also, in the code above s's don't have to have the same type.

For this purpose we have indexed state monads.


 I particularly like repeated lets when I am writing the code to apply
 transformations to it. Being explicit with state passing improves the
 confidence. It is simpler to reason with the pure code.

Really?  I'm more confident that I got the updates right when I use a
state monad, possibly together with lenses.  The idea is to disallow
`get` and only allow `modify` and `put`.

The thing is, your code is really imperative, and it exhibits all the
usual effects of imperative programming:  If you mess up the order of
things, you get wrong results.  In fact the let-style makes things worse
by requiring you to renumber your variables all the time.  A
non-recursive let would really just cover up this problem by imposing an
arbitrary constraint on you.  I think we are all aware that shadowing is
a bad idea, no matter whether you do it through Identity or
non-recursive let.

Also if you are serious about this, you would have to make non-recursive
let the default to get OCaml-style behavior, which would be an extremely
invasive change.  We would have to fix pretty much all packages, all
tutorials, all books, all wiki pages, etc.  Otherwise just like you may
forget to renumber your variables, you may just as well forget to add
the norec keyword or whatever the syntax would be.

State monads are actually a nice abstraction to limit the number of
things that could go wrong in this setting.  I suggest using them
instead of changing the language.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Andreas Abel

On 10.07.13 11:42 AM, Ertugrul Söylemez wrote:

I think we are all aware that shadowing is
a bad idea, no matter whether you do it through Identity or
non-recursive let.


WHAT??

[This is Richard Bird's WHAT?? when someone said that using folds is 
like programming in assembly language.]


How can you think this if we say we WANT shadowing?!


Also if you are serious about this, you would have to make non-recursive
let the default to get OCaml-style behavior, which would be an extremely
invasive change.  We would have to fix pretty much all packages, all
tutorials, all books, all wiki pages, etc.  Otherwise just like you may
forget to renumber your variables, you may just as well forget to add
the norec keyword or whatever the syntax would be.


Wow, this is getting really dramatic now.  Don't be afraid, now one will 
force you to shadow any of your identifiers...


--
Andreas AbelDu bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.a...@ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/

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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread Richard A. O'Keefe

On 10/07/2013, at 8:42 PM, Andreas Abel wrote:
 
 Hear, hear! In OCaml, I can (and often do) write
 
 let (x,s) = foo 1 [] in
 let (y,s) = bar x s in
 let (z,s) = baz x y s in ...

I really wish you wouldn't do that.

After reading Dijkstra's paper on the fact that we have
small heads many years ago -- long enough to forget the
actual title, sorry -- I realised that I too was a Bear
of Very Little Brain and Get Confused Very Easily.

I find that that when the same name gets reused like
that I get very confused indeed about which one I am
looking at right now.

If the variable is hidden (as by the DCG transformation
in Prolog, or a state monad, I don't get confused about
the variable because it isn't visible.

If each instance of the variable is labelled with a
sequence number, I don't get confused because each
variable has a different name and I can *see* which
one this is.

Yes, sequence numbering variable states is a chore for
the person writing the code, but it's a boon for the
person reading the code.

Me, I'd be perfectly happy with

setup (x,s) = state (\_ - (x,s))

(setup $ foo 1 []) = \x -
bar x = \y -
baz x y = \z -
...

One reason for this is that it makes refactorings like
extracting bar ... = ... baz ... thinkable.  A long
sequence of updates is probably crying out for such a
refactoring.


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


Re: [Haskell-cafe] Non-recursive let [Was: GHC bug? Let with guards loops]

2013-07-10 Thread oleg

Alberto G. Corona wrote:
 I think that a non-non recursive let could be not compatible with the pure
 nature of Haskell.

I have seen this sentiment before. It is quite a mis-understanding. In
fact, the opposite is true. One may say that Haskell is not quite pure
_because_ it has recursive let.

Let's take pure the simply-typed lambda-calculus, or System F, or
System Fomega. Or the Calculus of Inductive Constructions. These
calculi are pure in the sense that the result of evaluation of each
expression does not depend on the evaluation strategy. One can use
call-by-name, call-by-need, call-by-value, pick the next redex at
random or some other evaluation strategy -- and the result will be
just the same. Although the simply-typed lambda-calculus is quite
limited in its expressiveness, already System F is quite powerful
(e.g., allowing for the list library), to say nothing of CIC. In all
these systems, the non-recursive let

let x = e1 in e2
is merely the syntactic sugar for
(\x. e2) e1

OTH, the recursive let is not expressible. (Incidentally, although
System F and above express self-application (\x.x x), a fix-point
combinator is not typeable.) Adding the recursive let introduces
general recursion and hence the dependence on the evaluation
strategy. There are a few people who say non-termination is an
effect. The language with non-termination is no longer pure.


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