Re: [Haskell-cafe] Proposal: Non-recursive let

2013-08-02 Thread Andreas Abel

On 26.07.13 6:44 PM, Andreas Abel wrote:

headers0 - M.fromList $ do
  forM fields_header $ \ (n, fld) - do
(n,) $ reflect $ fld ast


Ah, I forgot one more 'do' to override the stronger binding of $:

  (n,) $ do reflect $ fld ast


Great satisfaction!  I killed all long-ranging parentheses! ;-)

-- Andreas


   let headers = M.insert _report_ranges (format_two_tstamps rv)
headers0
   foldM write_period (rv,headers,(snd rv,snd rv)) asts
   return ()
  where
  write_period (rv,headers,mv) ast = do
   pv@(p_valid_from,p_valid_until) - reflect $ get_trange TRange ast
   check_inside pv rv
   let prevailing = M.lookup PREVAILING ast
   (mv,pv) - case prevailing of
 Just _  - return (pv,pv)-- set the major valid period
 -- Make sure each VAR period occurs later than the prevailing
 -- period. If exactly at the same time add 1 min
 Nothing - case () of
  _ | fst mv  p_valid_from  - return (mv,pv)
  _ | fst mv == p_valid_from - return (mv,(p_valid_from + 60,
  p_valid_until))
  _  - gthrow . InvalidData . unwords $ [
   VAR period begins before prevailing:,
  show ast, ; prevailing TRange, show mv]
   let token  = maybe (M.findWithDefault  VAR ast) id prevailing
   let ast1 = M.insert _token token .
M.insert _period_valid (format_two_tstamps pv) .
  M.unionWith (\_ x - x) headers $ ast
   let title  = M.member Title ast
   let headers1 = if title then headers else
M.delete _limit_to  . M.delete _limit_recd $ headers

   write_fields h ast1 fields

   return (rv,headers1,mv)


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






--
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] Proposal: Non-recursive let

2013-07-31 Thread Erik Hesselink
On Fri, Jul 26, 2013 at 6:44 PM, Andreas Abel andreas.a...@ifi.lmu.de wrote:
   mapSnd f = (id *** f)

As a very small aside, this is just `second` from Control.Arrow.

Erik

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-31 Thread Edward Kmett
Or fmap in this case =)

On Wed, Jul 31, 2013 at 11:33 AM, Erik Hesselink hessel...@gmail.comwrote:

 On Fri, Jul 26, 2013 at 6:44 PM, Andreas Abel andreas.a...@ifi.lmu.de
 wrote:
mapSnd f = (id *** f)

 As a very small aside, this is just `second` from Control.Arrow.

 Erik

 ___
 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] Proposal: Non-recursive let

2013-07-26 Thread Siraaj Khandkar

On 07/23/2013 03:37 PM, i c wrote:

let's consider the following:

let fd = Unix.open ...
let fd = Unix.open ...

At this point one file descriptor cannot be closed. Static analysis will
have trouble catching these bugs, so do humans.
Disallowing variable shadowing prevents this.
The two fd occur in different contexts and should have different names.




$ cat shadow_fd.ml
let () =
  let fd = Unix.openfile foo_1.txt [] 0o640 in
  let fd = Unix.openfile foo_2.txt [] 0o640 in
  Unix.close fd


$ ocamlfind ocamlopt -linkpkg -package unix shadow_fd.ml -o shadow_fd
File shadow_fd.ml, line 2, characters 6-8:
Warning 26: unused variable fd.


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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-26 Thread Andreas Abel
Mmh, true, for polymorphic definitions there is not a lot to see.  This 
probably diminishes the applicability of a strictness analysis quite a 
bit.  Maybe it is entirely useless at this point.


It would make more sense after whole-program optimization.  Ghc does not 
have this, I heard the Intel Research Compiler does such things.


This is becoming a very high-hanging fruit...

--Andreas

On 24.07.2013 20:22, Edward Kmett wrote:

You only have a Num constraint when type checking that code:

(+) :: Num a = a - a - a

For better or worse, you don't get strictness in the type signatures in
Haskell.

We do not separate codata from data here.

Without knowing about the particular instance of Num and even the
direction of recursion on (+) there is no information for such a
strictness analyzer to work with.

many :: Alternative m = m a - m [a]
many p = ps where
   ps = (:) $ p * ps
| pure []

is another perfectly cromulent example of value recursion, and one
that is far nearer and dearer to my heart and is similarly opaque to any
such analysis.

-Edward



On Wed, Jul 24, 2013 at 4:14 AM, Andreas Abel andreas.a...@ifi.lmu.de
mailto:andreas.a...@ifi.lmu.de wrote:

Sure.  I have not looked a concrete strictness analyses, but I
expect they would treat Conat differently than Integer.  In particular,

   x   does *not* appear strictly in  S x

if S is a lazy constructor.


On 22.07.13 4:54 PM, Edward Kmett wrote:

let x = x +1

is perfectly cromulent when x is sufficiently lazy, e.g. in the
one point compactification of the naturals:

data Conat = S Conat | Z

There it represents infinity with proper sharing.

-Edward

On Jul 22, 2013, at 10:24 AM, Andreas Abel
andreas.a...@ifi.lmu.de mailto:andreas.a...@ifi.lmu.de wrote:

On 22.07.2013 10:50, MigMit wrote:


On Jul 22, 2013, at 12:27 PM, Andreas Abel
andreas.a...@ifi.lmu.de mailto:andreas.a...@ifi.lmu.de
wrote:

On 20.07.13 9:36 PM, Evan Laforge wrote:

However, I'm also not agitating for a
non-recursive let, I think
that ship has sailed.  Besides, if it were added
people would
start wondering about non-recursive where, and
it would introduce
an exception to haskell's pretty consistently
order-independent
declaration style.


For functions, recursive-by-default let makes sense.
  But for
*values*, intended recursion is rather the
exception.  It is useful
for infinite lists and the like.  For values of
atomic type like
Int or Bool, recursive let is a bug.


It seems hard to distinguish between them. What about
values that
contain functions, like data T = T Int (Int - Int)?
What about
polymorphic values, that could be functions and could be
not?


I agree.  It cannot be implemented like that.  A thing that
could be implemented is that

   let x = e

is an error if x appears strictly in e.  In practice, this
could catch some unintended cases of recursion like

   let x = x +1

, but not all of them.

Cheers,
Andreas

--
Andreas AbelDu bist der geliebte Mensch.

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

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

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



--
Andreas AbelDu bist der geliebte Mensch.

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

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





--
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] Proposal: Non-recursive let

2013-07-26 Thread Andreas Abel

On 25.07.2013 09:09, o...@okmij.org wrote:


Here is a snippet from a real code that could benefit from
non-recursive let. The example is notable because it incrementally
constructs not one but two structures (both maps), ast and headers.
The maps are constructed in a bit interleaved fashion, and stuffing
them into the same State would be ungainly. In my real code

-- Add an update record to a buffer file
do_update :: String - Handle - Parsed - [Parsed] - IO ()
do_update TAF h ast asts@(_:_) = do
   rv - reflect $ get_trange TRange ast



   headers0 - return . M.fromList = sequence
  (map (\ (n,fld) - reflect (fld ast) = \v - return (n,v))
  fields_header)


This is a mouth-full.  The = \v - return (n,v) can be more 
elegantly expressed with tuple section


   (map (\ (n,fld) - (n,) $ reflect (fld ast)) fields_header)

Maybe even use

  mapSnd f = (id *** f)

and write

   (map (mapSnd $ \ fld - reflect (fld ast)) fields_header)

and, getting into lambda-killing rush :-)

   (map (mapSnd $ reflect . ($ ast)) fields_header)

(ok, now we overdid it).

Also, was not mapM = sequence . map ?
And  return . f = m   the same as f $ m?  Then we are at

   headers0 - M.fromList $ do
 mapM (\ (n,fld) - (n,) $ reflect (fld ast)) fields_header

Actually, I prefer for-loops:

   headers0 - M.fromList $ do
 forM fields_header $ \ (n, fld) - do
   (n,) $ reflect $ fld ast

Great satisfaction!  I killed all long-ranging parentheses! ;-)

-- Andreas


   let headers = M.insert _report_ranges (format_two_tstamps rv) headers0
   foldM write_period (rv,headers,(snd rv,snd rv)) asts
   return ()
  where
  write_period (rv,headers,mv) ast = do
   pv@(p_valid_from,p_valid_until) - reflect $ get_trange TRange ast
   check_inside pv rv
   let prevailing = M.lookup PREVAILING ast
   (mv,pv) - case prevailing of
 Just _  - return (pv,pv)   -- set the major valid period
 -- Make sure each VAR period occurs later than the prevailing
 -- period. If exactly at the same time add 1 min
 Nothing - case () of
  _ | fst mv  p_valid_from  - return (mv,pv)
  _ | fst mv == p_valid_from - return (mv,(p_valid_from + 60,
  p_valid_until))
  _  - gthrow . InvalidData . unwords $ [
   VAR period begins before prevailing:,
  show ast, ; prevailing TRange, show mv]
   let token  = maybe (M.findWithDefault  VAR ast) id prevailing
   let ast1 = M.insert _token token .
M.insert _period_valid (format_two_tstamps pv) .
  M.unionWith (\_ x - x) headers $ ast
   let title  = M.member Title ast
   let headers1 = if title then headers else
M.delete _limit_to  . M.delete _limit_recd $ headers

   write_fields h ast1 fields

   return (rv,headers1,mv)


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




--
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] Proposal: Non-recursive let

2013-07-25 Thread oleg

ivan.chollet wrote:
 let's consider the following:

 let fd = Unix.open ...
 let fd = Unix.open ...

 At this point one file descriptor cannot be closed. Static analysis will
 have trouble catching these bugs, so do humans.

Both sentences express false propositions.

The given code, if Haskell, does not open any file descriptors, so
there is nothing to close. In the following OCaml code

let fd = open_in /tmp/a in
let fd = open_in /tmp/v in
...

the first open channel becomes unreachable. When GC collects it (which
will happen fairly soon, on a minor collection, because the channel
died young), GC will finalize the channel and close its file
descriptor.

The corresponding Haskell code
do
h - openFile ...
h - openFile ...

works similarly to OCaml. Closing file handles upon GC is codified in
the Haskell report because Lazy IO crucially depends on such behavior.

If one is interested in statically tracking open file descriptors and
making sure they are closed promptly, one could read large literature
on this topic. Google search for monadic regions should be a good
start. Some of the approaches are implemented and used in Haskell.


Now about static analysis. Liveness analysis has no problem whatsoever
determining that a variable fd in our examples has been shadowed and
the corresponding value is dead. We are all familiar with liveness
analysis -- it's the one responsible for `unused variable'
warnings. The analysis is useful for many other things (e.g., if it
determines that a created value dies within the function activation,
the value could be allocated on stack rather than on heap.). Here is
example from C:

#include stdio.h

void foo(void) {
  char x[4]  = abc; /* Intentional copying! */
  {
  char x[4]  = cde; /* Intentional copying and shadowing */
  x[0] = 'x';
  printf(result %s\n,x);
  }
}

Pretty old GCC (4.2.1) had no trouble detecting the shadowing. With
the optimization flag -O4, GCC acted on this knowledge. The generated
assembly code reveals no traces of the string abc, not even in the
.rodata section of the code. The compiler determined the string is
really unused and did not bother even compiling it in.


 Disallowing variable shadowing prevents this.
 The two fd occur in different contexts and should have different names.
 Usage of shadowing is generally bad practice. It is error-prone. Hides
 obnoxious bugs like file descriptors leaks.
 The correct way is to give different variables that appear in different
 contexts a different name, although this is arguably less convenient and
 more verbose.

CS would be better as science if we refrain from passing our
personal opinions and prejudices as ``the correct way''.

I can't say better than the user Kranar in a recent discussion on a
similar `hot topic':

The issue is that much of what we do as developers is simply based on
anecdotal evidence, or statements made by so called evangelicals who
blog about best practices and people believe them because of how
articulate they are or the cache and prestige that the person carries.
...
It's unfortunate that computer science is still advancing the same way
medicine advanced with witch doctors, by simply trusting the wisest
and oldest of the witch doctors without any actual empirical data,
without any evidence, just based on the reputation and overall
charisma or influence of certain bloggers or big names in the field.

http://www.reddit.com/r/programming/comments/1iyp6v/is_there_a_really_an_empirical_difference_between/cb9mf6f



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


[Haskell-cafe] Proposal: Non-recursive let

2013-07-25 Thread oleg

Here is a snippet from a real code that could benefit from
non-recursive let. The example is notable because it incrementally
constructs not one but two structures (both maps), ast and headers.
The maps are constructed in a bit interleaved fashion, and stuffing
them into the same State would be ungainly. In my real code

-- Add an update record to a buffer file
do_update :: String - Handle - Parsed - [Parsed] - IO ()
do_update TAF h ast asts@(_:_) = do
  rv - reflect $ get_trange TRange ast
  headers0 - return . M.fromList = sequence 
 (map (\ (n,fld) - reflect (fld ast) = \v - return (n,v)) 
  fields_header)
  let headers = M.insert _report_ranges (format_two_tstamps rv) headers0
  foldM write_period (rv,headers,(snd rv,snd rv)) asts
  return ()
 where
 write_period (rv,headers,mv) ast = do
  pv@(p_valid_from,p_valid_until) - reflect $ get_trange TRange ast
  check_inside pv rv
  let prevailing = M.lookup PREVAILING ast
  (mv,pv) - case prevailing of
Just _  - return (pv,pv)   -- set the major valid period
 -- Make sure each VAR period occurs later than the prevailing 
 -- period. If exactly at the same time add 1 min
Nothing - case () of
 _ | fst mv  p_valid_from  - return (mv,pv)
 _ | fst mv == p_valid_from - return (mv,(p_valid_from + 60,
  p_valid_until))
 _  - gthrow . InvalidData . unwords $ [
  VAR period begins before prevailing:,
  show ast, ; prevailing TRange, show mv]
  let token  = maybe (M.findWithDefault  VAR ast) id prevailing
  let ast1 = M.insert _token token .
   M.insert _period_valid (format_two_tstamps pv) .
 M.unionWith (\_ x - x) headers $ ast
  let title  = M.member Title ast
  let headers1 = if title then headers else
M.delete _limit_to  . M.delete _limit_recd $ headers

  write_fields h ast1 fields  

  return (rv,headers1,mv)


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


Re: [Haskell-cafe] Proposal: Non-recursive let

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

On 25/07/2013, at 7:09 PM, o...@okmij.org wrote:
 Here is a snippet from a real code that could benefit from
 non-recursive let. 

[[A big blob of extremely dense code.]]

_Nothing_ is going to make that easy to read.

And I say that as someone who loves Haskell and is in *awe* of
Oleg.  I mean, if the functional rain is pouring down and Oleg
says Hey, sunny!, I normally furl my umbrella...

One of the things that I find makes it hard for _me_ to read
is the coding style where do is sneaked away out of sight.
Am I alone in wanting do at the _beginning_ of a line so
that it stands out?  Do real Haskell experts just get used to
using do so much that they don't feel it's _worth_ making
visible?

It's a queer thing, I always feel that the advice about
keeping function bodies small is patronising nonsense for
beginners and that *my* code is perfectly readable no matter
how big it is, but end up wishing that *other* people kept
*their* functions small.  It's not as if my code were bug-free...
Must be something in the water.

That's relevant though.  If your functions are small, you don't
get enough versions of a variable for non-recursive let to pay off.

In this specific example, as a _reader_, a much less competent
reader than Oleg, the only problem I can see with using ast1
and header1 is that th names are not different *ENOUGH* from
ast1 and header.  I'd like names that go some towards
explaining *why* 'ast1' has _token and _period_values slots
that 'ast' doesn't (and for that matter, something a bit longer
than 'ast', which doesn't seem to stand for Abstract Syntax Tree
here), and *why* 'headers1' shouldn't include _limit_to and
_limit_rcvd slots unless there is a title.

All in all, a good example of code where using non-recursive let
would have DECREASED readability by one person strange to the code.

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-25 Thread Tom Ellis
On Thu, Jul 25, 2013 at 07:34:55PM +1200, Richard A. O'Keefe wrote:
 It's a queer thing, I always feel that the advice about
 keeping function bodies small is patronising nonsense for
 beginners and that *my* code is perfectly readable no matter
 how big it is, but end up wishing that *other* people kept
 *their* functions small.

For example, breaking this code into smaller functions could make it
transparent that 'token' is only used in 'ast1', 'title' is only used in
'headers1' and that the 'mv' that is the argument to 'write_period' is only
used in the Nothing branch of the massive case statement.

It seems there are a number of straightforward ways to make this code much
clearer that do not require non-recursive let.

Tom

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-25 Thread David Fox
On Wed, Jul 24, 2013 at 1:11 AM, Andreas Abel andreas.a...@ifi.lmu.de wrote:
 On 23.07.13 4:34 AM, Richard A. O'Keefe wrote:


 On 22/07/2013, at 8:14 PM, Andreas Abel wrote:

 Just today, my student asked me why the following program does nothing:


 Did you ask your student why their code should not be torn into pieces,
 burned to ashes, and incorporated into a pot for radioactive waste?

 All those occurrences of unsafePerformIO!


 No, here they are intended, to simulate something like uniqueness types in
 Clean, which incidentially has been mentioned on this thread before.

 The loop has nothing to do with unsafePerformIO, but stems from Haskell's
 idiosyncratic recursive let, which is a trap for all that come from another
 functional language.

Have your students turn on -fwarn-name-shadowing -Werror:

[1 of 1] Compiling Main ( foo.hs, interpreted )

foo.hs:53:16: Warning:
This binding for `arr' shadows the existing binding
  bound at foo.hs:50:28

foo.hs:62:18: Warning:
This binding for `arr' shadows the existing binding
  bound at foo.hs:56:24

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-25 Thread i c
Although your post is a bit trollish, I answer below to clear any confusion.


On Thu, Jul 25, 2013 at 7:18 AM,  o...@okmij.org wrote:

 ivan.chollet wrote:
 let's consider the following:

 let fd = Unix.open ...
 let fd = Unix.open ...

 At this point one file descriptor cannot be closed. Static analysis will
 have trouble catching these bugs, so do humans.

 Both sentences express false propositions.

Nope, they both express true propositions, as shown below.


 The given code, if Haskell, does not open any file descriptors, so
 there is nothing to close.

I gave the code in caml syntax since your original post was about caml.


In the following OCaml code

 let fd = open_in /tmp/a in
 let fd = open_in /tmp/v in
 ...

 the first open channel becomes unreachable. When GC collects it (which
 will happen fairly soon, on a minor collection, because the channel
 died young), GC will finalize the channel and close its file
 descriptor.

This is not the code I posted. I explicitly used Unix.open, not
open_in. This dishonest rewrite of my trivial code snippet is
trollish and ridiculous.
In your code, your fds are not file descriptors, they are channels.
It's funny that you use a variable name fd for a channel, shows
confusion at the very least, since they are completely different
objects and concepts. I assume that for a file descriptor, you
invariably use a variable name ch?
In my code, the fd are not garbage collected, they are not subject to
garbage collection since they don't live in the runtime, they are
purely OS objects that need to be closed with an explicit Unix.close
system call.

As a result, your comment is completely wrong, the first file
descriptor in my code snippet gets invariably leaked as I said.

This proves the first sentence.


 The corresponding Haskell code
 do
 h - openFile ...
 h - openFile ...

 works similarly to OCaml. Closing file handles upon GC is codified in
 the Haskell report because Lazy IO crucially depends on such behavior.

 If one is interested in statically tracking open file descriptors and
 making sure they are closed promptly, one could read large literature
 on this topic. Google search for monadic regions should be a good
 start. Some of the approaches are implemented and used in Haskell.


 Now about static analysis. Liveness analysis has no problem whatsoever
 determining that a variable fd in our examples has been shadowed and
 the corresponding value is dead. We are all familiar with liveness
 analysis -- it's the one responsible for `unused variable'
 warnings. The analysis is useful for many other things (e.g., if it
 determines that a created value dies within the function activation,
 the value could be allocated on stack rather than on heap.). Here is
 example from C:

 #include stdio.h

 void foo(void) {
   char x[4]  = abc; /* Intentional copying! */
   {
   char x[4]  = cde; /* Intentional copying and shadowing */
   x[0] = 'x';
   printf(result %s\n,x);
   }
 }

 Pretty old GCC (4.2.1) had no trouble detecting the shadowing. With
 the optimization flag -O4, GCC acted on this knowledge. The generated
 assembly code reveals no traces of the string abc, not even in the
 .rodata section of the code. The compiler determined the string is
 really unused and did not bother even compiling it in.


Detecting shadowing is trivial as I said in a previous post and is not
the problem here. The compiler can always throw a warning about the
shadowing, but not much else.

There is no algorithm that can tell you (by static analysis or not by
the way) whether a program is leaking file descriptors or not. This is
a corollary of Rice's theorem.
For example if you put your file descriptors in a list, then shadow
some of them, static analysis will be of no help to tell you if your
program is leaking file descriptors or not.

This proves the second sentence.



 Disallowing variable shadowing prevents this.
 The two fd occur in different contexts and should have different names.
 Usage of shadowing is generally bad practice. It is error-prone. Hides
 obnoxious bugs like file descriptors leaks.
 The correct way is to give different variables that appear in different
 contexts a different name, although this is arguably less convenient and
 more verbose.

 CS would be better as science if we refrain from passing our
 personal opinions and prejudices as ``the correct way''.


CS would be better as a science if we refrained from using flawed
logic and trollish behaviors, as you did in your quoted post.


 I can't say better than the user Kranar in a recent discussion on a
 similar `hot topic':

 The issue is that much of what we do as developers is simply based on
 anecdotal evidence, or statements made by so called evangelicals who
 blog about best practices and people believe them because of how
 articulate they are or the cache and prestige that the person carries.
 ...
 It's unfortunate that computer 

Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-25 Thread Edward Kmett
I'm just going to say that I'd rather we didn't resort to calling each
others trolls.

I happen to disagree with Oleg on this particular issue and find that it is
better resolved by just using -Wall or a 2-line combinator, but I find that
across the breadth and depth of issues in the Haskell ecosystem I find
myself agreeing with him more often than not.

-Edward

On Thu, Jul 25, 2013 at 1:41 PM, i c ivan.chol...@gmail.com wrote:

 Although your post is a bit trollish, I answer below to clear any
 confusion.


 On Thu, Jul 25, 2013 at 7:18 AM,  o...@okmij.org wrote:
 
  ivan.chollet wrote:
  let's consider the following:
 
  let fd = Unix.open ...
  let fd = Unix.open ...
 
  At this point one file descriptor cannot be closed. Static analysis will
  have trouble catching these bugs, so do humans.
 
  Both sentences express false propositions.

 Nope, they both express true propositions, as shown below.

 
  The given code, if Haskell, does not open any file descriptors, so
  there is nothing to close.

 I gave the code in caml syntax since your original post was about caml.


 In the following OCaml code
 
  let fd = open_in /tmp/a in
  let fd = open_in /tmp/v in
  ...
 
  the first open channel becomes unreachable. When GC collects it (which
  will happen fairly soon, on a minor collection, because the channel
  died young), GC will finalize the channel and close its file
  descriptor.

 This is not the code I posted. I explicitly used Unix.open, not
 open_in. This dishonest rewrite of my trivial code snippet is
 trollish and ridiculous.
 In your code, your fds are not file descriptors, they are channels.
 It's funny that you use a variable name fd for a channel, shows
 confusion at the very least, since they are completely different
 objects and concepts. I assume that for a file descriptor, you
 invariably use a variable name ch?
 In my code, the fd are not garbage collected, they are not subject to
 garbage collection since they don't live in the runtime, they are
 purely OS objects that need to be closed with an explicit Unix.close
 system call.

 As a result, your comment is completely wrong, the first file
 descriptor in my code snippet gets invariably leaked as I said.

 This proves the first sentence.

 
  The corresponding Haskell code
  do
  h - openFile ...
  h - openFile ...
 
  works similarly to OCaml. Closing file handles upon GC is codified in
  the Haskell report because Lazy IO crucially depends on such behavior.
 
  If one is interested in statically tracking open file descriptors and
  making sure they are closed promptly, one could read large literature
  on this topic. Google search for monadic regions should be a good
  start. Some of the approaches are implemented and used in Haskell.
 
 
  Now about static analysis. Liveness analysis has no problem whatsoever
  determining that a variable fd in our examples has been shadowed and
  the corresponding value is dead. We are all familiar with liveness
  analysis -- it's the one responsible for `unused variable'
  warnings. The analysis is useful for many other things (e.g., if it
  determines that a created value dies within the function activation,
  the value could be allocated on stack rather than on heap.). Here is
  example from C:
 
  #include stdio.h
 
  void foo(void) {
char x[4]  = abc; /* Intentional copying! */
{
char x[4]  = cde; /* Intentional copying and shadowing */
x[0] = 'x';
printf(result %s\n,x);
}
  }
 
  Pretty old GCC (4.2.1) had no trouble detecting the shadowing. With
  the optimization flag -O4, GCC acted on this knowledge. The generated
  assembly code reveals no traces of the string abc, not even in the
  .rodata section of the code. The compiler determined the string is
  really unused and did not bother even compiling it in.
 

 Detecting shadowing is trivial as I said in a previous post and is not
 the problem here. The compiler can always throw a warning about the
 shadowing, but not much else.

 There is no algorithm that can tell you (by static analysis or not by
 the way) whether a program is leaking file descriptors or not. This is
 a corollary of Rice's theorem.
 For example if you put your file descriptors in a list, then shadow
 some of them, static analysis will be of no help to tell you if your
 program is leaking file descriptors or not.

 This proves the second sentence.


 
  Disallowing variable shadowing prevents this.
  The two fd occur in different contexts and should have different
 names.
  Usage of shadowing is generally bad practice. It is error-prone. Hides
  obnoxious bugs like file descriptors leaks.
  The correct way is to give different variables that appear in different
  contexts a different name, although this is arguably less convenient and
  more verbose.
 
  CS would be better as science if we refrain from passing our
  personal opinions and prejudices as ``the correct way''.
 

 CS would be better as a 

Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-24 Thread Andreas Abel

On 23.07.13 4:34 AM, Richard A. O'Keefe wrote:


On 22/07/2013, at 8:14 PM, Andreas Abel wrote:


Just today, my student asked me why the following program does nothing:


Did you ask your student why their code should not be torn into pieces,
burned to ashes, and incorporated into a pot for radioactive waste?

All those occurrences of unsafePerformIO!


No, here they are intended, to simulate something like uniqueness types 
in Clean, which incidentially has been mentioned on this thread before.


The loop has nothing to do with unsafePerformIO, but stems from 
Haskell's idiosyncratic recursive let, which is a trap for all that come 
from another functional language.


--
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] Proposal: Non-recursive let

2013-07-24 Thread Andreas Abel
Sure.  I have not looked a concrete strictness analyses, but I expect 
they would treat Conat differently than Integer.  In particular,


  x   does *not* appear strictly in  S x

if S is a lazy constructor.

On 22.07.13 4:54 PM, Edward Kmett wrote:

let x = x +1

is perfectly cromulent when x is sufficiently lazy, e.g. in the one point 
compactification of the naturals:

data Conat = S Conat | Z

There it represents infinity with proper sharing.

-Edward

On Jul 22, 2013, at 10:24 AM, Andreas Abel andreas.a...@ifi.lmu.de wrote:


On 22.07.2013 10:50, MigMit wrote:


On Jul 22, 2013, at 12:27 PM, Andreas Abel andreas.a...@ifi.lmu.de
wrote:


On 20.07.13 9:36 PM, Evan Laforge wrote:

However, I'm also not agitating for a non-recursive let, I think
that ship has sailed.  Besides, if it were added people would
start wondering about non-recursive where, and it would introduce
an exception to haskell's pretty consistently order-independent
declaration style.


For functions, recursive-by-default let makes sense.  But for
*values*, intended recursion is rather the exception.  It is useful
for infinite lists and the like.  For values of atomic type like
Int or Bool, recursive let is a bug.


It seems hard to distinguish between them. What about values that
contain functions, like data T = T Int (Int - Int)? What about
polymorphic values, that could be functions and could be not?


I agree.  It cannot be implemented like that.  A thing that could be 
implemented is that

  let x = e

is an error if x appears strictly in e.  In practice, this could catch some 
unintended cases of recursion like

  let x = x +1

, but not all of them.

Cheers,
Andreas

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




--
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] Proposal: Non-recursive let

2013-07-24 Thread Edward Kmett
You only have a Num constraint when type checking that code:

(+) :: Num a = a - a - a

For better or worse, you don't get strictness in the type signatures in
Haskell.

We do not separate codata from data here.

Without knowing about the particular instance of Num and even the direction
of recursion on (+) there is no information for such a strictness analyzer
to work with.

many :: Alternative m = m a - m [a]
many p = ps where
  ps = (:) $ p * ps
   | pure []

is another perfectly cromulent example of value recursion, and one that
is far nearer and dearer to my heart and is similarly opaque to any such
analysis.

-Edward



On Wed, Jul 24, 2013 at 4:14 AM, Andreas Abel andreas.a...@ifi.lmu.dewrote:

 Sure.  I have not looked a concrete strictness analyses, but I expect they
 would treat Conat differently than Integer.  In particular,

   x   does *not* appear strictly in  S x

 if S is a lazy constructor.


 On 22.07.13 4:54 PM, Edward Kmett wrote:

 let x = x +1

 is perfectly cromulent when x is sufficiently lazy, e.g. in the one point
 compactification of the naturals:

 data Conat = S Conat | Z

 There it represents infinity with proper sharing.

 -Edward

 On Jul 22, 2013, at 10:24 AM, Andreas Abel andreas.a...@ifi.lmu.de
 wrote:

  On 22.07.2013 10:50, MigMit wrote:


 On Jul 22, 2013, at 12:27 PM, Andreas Abel andreas.a...@ifi.lmu.de
 wrote:

  On 20.07.13 9:36 PM, Evan Laforge wrote:

 However, I'm also not agitating for a non-recursive let, I think
 that ship has sailed.  Besides, if it were added people would
 start wondering about non-recursive where, and it would introduce
 an exception to haskell's pretty consistently order-independent
 declaration style.


 For functions, recursive-by-default let makes sense.  But for
 *values*, intended recursion is rather the exception.  It is useful
 for infinite lists and the like.  For values of atomic type like
 Int or Bool, recursive let is a bug.


 It seems hard to distinguish between them. What about values that
 contain functions, like data T = T Int (Int - Int)? What about
 polymorphic values, that could be functions and could be not?


 I agree.  It cannot be implemented like that.  A thing that could be
 implemented is that

   let x = e

 is an error if x appears strictly in e.  In practice, this could catch
 some unintended cases of recursion like

   let x = x +1

 , but not all of them.

 Cheers,
 Andreas

 --
 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/ http://www2.tcs.ifi.lmu.de/~abel/

 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



 --
 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/ 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] Proposal: Non-recursive let

2013-07-23 Thread John van Groningen

On 22-7-2013 17:09, i c wrote:

On Wed, Jul 10, 2013 at 9:47 AM,o...@okmij.org  wrote:



Jon Fairbairn wrote:

It just changes forgetting to use different variable names because of
recursion (which is currently uniform throughout the language) to
forgetting to use non recursive let instead of let.


Let me bring to the record the message I just wrote on Haskell-cafe

http://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

and repeat the example:

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.


Not if you use pattern guards:

{-# LANGUAGE PatternGuards #-}

| ~(x,s) = foo 1 []
, ~(y,s) = bar x s
, ~(z,s) = baz x y s
= ...


Usage of shadowing is generally bad practice. It is error-prone. Hides
obnoxious bugs like file descriptors leaks.
The correct way is to give different variables that appear in different
contexts a different name, although this is arguably less convenient and
more verbose.




___
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] Proposal: Non-recursive let

2013-07-23 Thread John van Groningen


| ~(x,s) = foo 1 []
, ~(y,s) = bar x s
, ~(z,s) = baz x y s
= ...

in my previous message should be:

| ~(x,s) - foo 1 []
, ~(y,s) - bar x s
, ~(z,s) - baz x y s
= ...

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-23 Thread Bardur Arantsson
On 2013-07-22 17:09, i c wrote:
 Usage of shadowing is generally bad practice. It is error-prone. Hides
 obnoxious bugs like file descriptors leaks.

These claims need to be substantiated, I think.

(Not that I disagree, I just think that asserting this without evidence
isn't going to convince anyone who is of the opposite mindset.)

Regards,



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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-23 Thread i c
let's consider the following:

let fd = Unix.open ...
let fd = Unix.open ...

At this point one file descriptor cannot be closed. Static analysis will
have trouble catching these bugs, so do humans.
Disallowing variable shadowing prevents this.
The two fd occur in different contexts and should have different names.



On Tue, Jul 23, 2013 at 8:17 PM, Bardur Arantsson s...@scientician.netwrote:

 On 2013-07-22 17:09, i c wrote:
  Usage of shadowing is generally bad practice. It is error-prone. Hides
  obnoxious bugs like file descriptors leaks.

 These claims need to be substantiated, I think.

 (Not that I disagree, I just think that asserting this without evidence
 isn't going to convince anyone who is of the opposite mindset.)

 Regards,



 ___
 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] Proposal: Non-recursive let

2013-07-23 Thread David Thomas
It strikes me as unlikely static analysis would be confused by shadowing.


On Tue, Jul 23, 2013 at 12:37 PM, i c ivan.chol...@gmail.com wrote:

 let's consider the following:

 let fd = Unix.open ...
 let fd = Unix.open ...

 At this point one file descriptor cannot be closed. Static analysis will
 have trouble catching these bugs, so do humans.
 Disallowing variable shadowing prevents this.
 The two fd occur in different contexts and should have different names.



 On Tue, Jul 23, 2013 at 8:17 PM, Bardur Arantsson s...@scientician.netwrote:

 On 2013-07-22 17:09, i c wrote:
  Usage of shadowing is generally bad practice. It is error-prone. Hides
  obnoxious bugs like file descriptors leaks.

 These claims need to be substantiated, I think.

 (Not that I disagree, I just think that asserting this without evidence
 isn't going to convince anyone who is of the opposite mindset.)

 Regards,



 ___
 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


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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-23 Thread Donn Cave
quoth David Thomas davidleotho...@gmail.com,

 It strikes me as unlikely static analysis would be confused by shadowing.

Not to mention that the example only created two expressions of type IO Fd?
(I.e., no file descriptors were opened, let alone leaked.)

But in any case, I would have guessed that the idea here is that much more
than a few examples and counter-examples will be needed to validate something
like `shadowing is bad.'  If the assertion isn't too simplistic, the examples
sure will be.

Donn

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-23 Thread Bardur Arantsson
On 2013-07-23 21:37, i c wrote:
 let's consider the following:
 
 let fd = Unix.open ...
 let fd = Unix.open ...
 
 At this point one file descriptor cannot be closed. Static analysis will
 have trouble catching these bugs, so do humans.
 Disallowing variable shadowing prevents this.
 The two fd occur in different contexts and should have different names.
 

I think you've misunderstood my challenge.

I'm not talking about examples of either good or bad, but empirical
*evidence* for sample sizes greater than 1.

As in: If there was an article title Is shadowing easier to understand
than explicitly named intermediate variables? with an empirically
supported conclusion, I think everybody would be happy, but I just don't
think we're quite there...

Regards,




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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-23 Thread i c
Static analysis is not confused by shadowing, it is confused by the file
descriptor leak, which it can't find in the general case.
Static analysis can only go as far as warning you that some variables are
shadowed, and you will ignore such warning since you're doing variable
shadowing purposely.
This was what I meant by my comment.


On Tue, Jul 23, 2013 at 9:02 PM, David Thomas davidleotho...@gmail.comwrote:

 It strikes me as unlikely static analysis would be confused by shadowing.


 On Tue, Jul 23, 2013 at 12:37 PM, i c ivan.chol...@gmail.com wrote:

 let's consider the following:

 let fd = Unix.open ...
 let fd = Unix.open ...

 At this point one file descriptor cannot be closed. Static analysis will
 have trouble catching these bugs, so do humans.
 Disallowing variable shadowing prevents this.
 The two fd occur in different contexts and should have different names.



 On Tue, Jul 23, 2013 at 8:17 PM, Bardur Arantsson 
 s...@scientician.netwrote:

 On 2013-07-22 17:09, i c wrote:
  Usage of shadowing is generally bad practice. It is error-prone. Hides
  obnoxious bugs like file descriptors leaks.

 These claims need to be substantiated, I think.

 (Not that I disagree, I just think that asserting this without evidence
 isn't going to convince anyone who is of the opposite mindset.)

 Regards,



 ___
 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



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


Re: [Haskell-cafe] Proposal: Non-recursive let

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

On 21/07/2013, at 7:36 AM, Evan Laforge wrote:
 Just by coincidence, I recently wrote this:

This is a BEAUTIFUL example.
I think we may disagree about what it's an example OF,
however.  I found the code a little difficult to
follow, but when that's fixed up, there's no longer
any reason to want non-recursive let, OR a monad.

I've run out of time tonight, but hope to say more tomorrow.


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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-22 Thread Andreas Abel

Just today, my student asked me why the following program does nothing:

{-# LANGUAGE CPP, GeneralizedNewtypeDeriving, BangPatterns #-}

import Control.Monad
import System.IO.Unsafe
import Data.Array.IO
import Data.IORef
import Debug.Trace


type LinearArray a = (Int, IORef Int, IOArray Int a)

initLinearArray :: Int - a - LinearArray a
initLinearArray l a =
  trace init (
   unsafePerformIO (do version - newIORef 0
   array - newArray (0, l - 1) a
   return (0, version, array)))

readLinearArray :: Int - (LinearArray a) - a
readLinearArray l !(ver, realver, arr) =
  trace read (
   unsafePerformIO (do version - readIORef realver
   element - readArray arr l
   if (version == ver) then
 return element
 else error Non-Linear read of linear Array))

writeLinearArray :: Int - a - LinearArray a - LinearArray a
writeLinearArray l e !(ver, realver, arr) =
  trace write (
   unsafePerformIO (do version - readIORef realver
   if (version == ver)
 then
 do writeIORef realver $ ver + 1
writeArray arr l e
return (ver + 1, realver, arr)
 else error Non-Linear write of linear Array))

linearArrayToList :: Int - Int - (LinearArray a) - [a]
linearArrayToList c m !a =
  trace toList (
if (c = m) then []
else (readLinearArray c a) : (linearArrayToList (c + 1) m a))

eratostenesTest :: Int - [Bool]
eratostenesTest length =
  let
strikeMult :: Int - Int - Int - (LinearArray Bool) - 
(LinearArray Bool)

strikeMult div cur len arr = trace smStart (
  if (cur = len)
  then trace arr arr
  else let arr = trace write $ writeLinearArray cur False arr
   in trace strikeMult2 $ strikeMult div (cur + div) len arr)
nextPrime :: Int - Int - (LinearArray Bool) - (LinearArray Bool)
nextPrime cur len !arr =
  if (cur = len)
  then
arr
  else if (readLinearArray cur arr)
   then
 let arr = trace strikeMult $ strikeMult cur (cur + cur) 
len arr

 in trace nextPrime $ nextPrime (cur + 1) len arr
   else
 nextPrime (cur + 1) len arr
ini = trace ini (initLinearArray length True)
theArray = trace nextPrimeCall $ nextPrime 2 length ini
  in
   linearArrayToList 0 length theArray

On 22.07.13 9:01 AM, Richard A. O'Keefe wrote:


On 21/07/2013, at 7:36 AM, Evan Laforge wrote:

Just by coincidence, I recently wrote this:


This is a BEAUTIFUL example.
I think we may disagree about what it's an example OF,
however.  I found the code a little difficult to
follow, but when that's fixed up, there's no longer
any reason to want non-recursive let, OR a monad.

I've run out of time tonight, but hope to say more tomorrow.


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



--
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] Proposal: Non-recursive let

2013-07-22 Thread Andreas Abel

On 20.07.13 9:36 PM, Evan Laforge wrote:

However, I'm also not agitating for a non-recursive let, I think that
ship has sailed.  Besides, if it were added people would start
wondering about non-recursive where, and it would introduce an
exception to haskell's pretty consistently order-independent
declaration style.


For functions, recursive-by-default let makes sense.  But for *values*, 
intended recursion is rather the exception.  It is useful for infinite 
lists and the like.  For values of atomic type like Int or Bool, 
recursive let is a bug.


Of course, if you want to do scope-checking before type-checking, which 
also makes sense, you cannot make recursiveness type-dependent.


Distinguishing 'let' into 'fun', 'val' and 'val rec' could help here:

Non-recursive:

  val x = e
  in  e'

Recursive:

  fun f x = e
  in  e'

  val rec x = e(x)
  in  e'

--
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] Proposal: Non-recursive let

2013-07-22 Thread MigMit

On Jul 22, 2013, at 12:27 PM, Andreas Abel andreas.a...@ifi.lmu.de wrote:

 On 20.07.13 9:36 PM, Evan Laforge wrote:
 However, I'm also not agitating for a non-recursive let, I think that
 ship has sailed.  Besides, if it were added people would start
 wondering about non-recursive where, and it would introduce an
 exception to haskell's pretty consistently order-independent
 declaration style.
 
 For functions, recursive-by-default let makes sense.  But for *values*, 
 intended recursion is rather the exception.  It is useful for infinite lists 
 and the like.  For values of atomic type like Int or Bool, recursive let is a 
 bug.

It seems hard to distinguish between them. What about values that contain 
functions, like data T = T Int (Int - Int)? What about polymorphic values, 
that could be functions and could be not?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-22 Thread Andreas Abel

On 22.07.2013 10:50, MigMit wrote:


On Jul 22, 2013, at 12:27 PM, Andreas Abel andreas.a...@ifi.lmu.de
wrote:


On 20.07.13 9:36 PM, Evan Laforge wrote:

However, I'm also not agitating for a non-recursive let, I think
that ship has sailed.  Besides, if it were added people would
start wondering about non-recursive where, and it would introduce
an exception to haskell's pretty consistently order-independent
declaration style.


For functions, recursive-by-default let makes sense.  But for
*values*, intended recursion is rather the exception.  It is useful
for infinite lists and the like.  For values of atomic type like
Int or Bool, recursive let is a bug.


It seems hard to distinguish between them. What about values that
contain functions, like data T = T Int (Int - Int)? What about
polymorphic values, that could be functions and could be not?


I agree.  It cannot be implemented like that.  A thing that could be 
implemented is that


  let x = e

is an error if x appears strictly in e.  In practice, this could catch 
some unintended cases of recursion like


  let x = x +1

, but not all of them.

Cheers,
Andreas

--
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] Proposal: Non-recursive let

2013-07-22 Thread Edward Kmett
let x = x +1

is perfectly cromulent when x is sufficiently lazy, e.g. in the one point 
compactification of the naturals:

data Conat = S Conat | Z

There it represents infinity with proper sharing.

-Edward

On Jul 22, 2013, at 10:24 AM, Andreas Abel andreas.a...@ifi.lmu.de wrote:

 On 22.07.2013 10:50, MigMit wrote:
 
 On Jul 22, 2013, at 12:27 PM, Andreas Abel andreas.a...@ifi.lmu.de
 wrote:
 
 On 20.07.13 9:36 PM, Evan Laforge wrote:
 However, I'm also not agitating for a non-recursive let, I think
 that ship has sailed.  Besides, if it were added people would
 start wondering about non-recursive where, and it would introduce
 an exception to haskell's pretty consistently order-independent
 declaration style.
 
 For functions, recursive-by-default let makes sense.  But for
 *values*, intended recursion is rather the exception.  It is useful
 for infinite lists and the like.  For values of atomic type like
 Int or Bool, recursive let is a bug.
 
 It seems hard to distinguish between them. What about values that
 contain functions, like data T = T Int (Int - Int)? What about
 polymorphic values, that could be functions and could be not?
 
 I agree.  It cannot be implemented like that.  A thing that could be 
 implemented is that
 
  let x = e
 
 is an error if x appears strictly in e.  In practice, this could catch some 
 unintended cases of recursion like
 
  let x = x +1
 
 , but not all of them.
 
 Cheers,
 Andreas
 
 -- 
 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

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-22 Thread i c
On Wed, Jul 10, 2013 at 9:47 AM, o...@okmij.org wrote:


 Jon Fairbairn wrote:
  It just changes forgetting to use different variable names because of
  recursion (which is currently uniform throughout the language) to
  forgetting to use non recursive let instead of let.

 Let me bring to the record the message I just wrote on Haskell-cafe

 http://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

 and repeat the example:

 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.



Usage of shadowing is generally bad practice. It is error-prone. Hides
obnoxious bugs like file descriptors leaks.
The correct way is to give different variables that appear in different
contexts a different name, although this is arguably less convenient and
more verbose.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: Non-recursive let

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

On 22/07/2013, at 8:14 PM, Andreas Abel wrote:

 Just today, my student asked me why the following program does nothing:

Did you ask your student why their code should not be torn into pieces,
burned to ashes, and incorporated into a pot for radioactive waste?

All those occurrences of unsafePerformIO!

(OK, so I wouldn't _really_ be rude to a student like that.
 But I'd have a hard time controlling my face...)


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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-20 Thread Evan Laforge
On Tue, Jul 16, 2013 at 5:20 PM, Richard A. O'Keefe o...@cs.otago.ac.nz wrote:
 Brian Marick sent me a couple of his stickers.
 The one I have on my door reads to be less wrong than yesterday.
 The other one I keep free to bring out and wave around:

 An example would be handy about now.

Just by coincidence, I recently wrote this:

midi_to_pitch :: TheoryFormat.Format - Maybe Pitch.Key
- Pitch.NoteNumber - Maybe Theory.Pitch
midi_to_pitch fmt key nn =
either (const Nothing) Just $
TheoryFormat.fmt_to_absolute fmt key pitch
where
-- TODO if I support frac I can use this for twelve too
(semis, _frac) = properFraction (Pitch.nn_to_double nn)
Theory.Pitch oct (Theory.Note pc accs) =
Theory.semis_to_pitch_sharps TheoryFormat.piano_layout
(Theory.nn_to_semis semis)
(oct1, pc1) = adjust_octave (TheoryFormat.fmt_pc_per_octave fmt) 7 oct pc
pitch = Theory.Pitch oct1 (Theory.Note pc1 accs)

kbd_to_pitch :: Theory.PitchClass - Pitch.Octave - Theory.PitchClass
- Theory.Accidentals - Theory.Pitch
kbd_to_pitch pc_per_octave oct pc accidentals =
Theory.Pitch (add_oct + oct1) (Theory.Note pc2 accidentals)
where
(oct1, pc1) = adjust_octave pc_per_octave 10 oct pc
-- If the scale is shorter than the kbd, go up to the next octave on the
-- same row.
(add_oct, pc2) = pc1 `divMod` pc_per_octave

adjust_octave :: Theory.PitchClass - Theory.PitchClass - Pitch.Octave
- Theory.PitchClass - (Pitch.Octave, Theory.PitchClass)
adjust_octave pc_per_octave kbd_per_octave oct pc = (oct2, pc2)
where
rows = ceiling $ fromIntegral pc_per_octave / fromIntegral kbd_per_octave
(oct2, offset) = oct `divMod` rows
pc2 = offset * kbd_per_octave + pc


Also, fragments like this are fairly common:

Right pitch_ -
let pitch = pitch_
{ Theory.pitch_note = (Theory.pitch_note pitch_)
{ Theory.note_accidentals = 0 }
}
accs = Theory.pitch_accidentals pitch_
in Just $ ScaleDegree.scale_degree_just
(smap_named_intervals smap)
(smap_accidental_interval smap ^^ accs)
(pitch_nn smap pitch) (pitch_note fmt pitch)

My convention is when I have a a series of transformations that have
to be named for whatever reason, I suffix with numbers.  When I have a
function argument (or case-bound variable as in this case) that has to
be cooked before it can be used, I suffix it with _.  That way code
inside the function is not likely to accidentally use the un-cooked
version (this has happened when I left the uncooked version normal and
suffixed the cooked version with a 1 or something).  In monadic style,
I use 'x - return $ f x' a fair amount.

I'm just sending this to point out that it actually is a real issue.
And on the odd chance that someone wants to tell me that I'm doing it
wrong and here's a better idea :)  I'm not about to import Monad.State
and wrap the whole expression in a state call just to replace one or
two variables, both the syntactic overhead and the conversion
overhead make it not worth it.

However, I'm also not agitating for a non-recursive let, I think that
ship has sailed.  Besides, if it were added people would start
wondering about non-recursive where, and it would introduce an
exception to haskell's pretty consistently order-independent
declaration style.

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-18 Thread Andreas Abel

On 17.07.13 9:46 PM, Edward Kmett wrote:

FWIW, I maintain, according to wc and sloccount, 220841 lines worth of
Haskell code at present.


Thanks, this is great service to our community.  And you produce 
excellent quality!



I have been bitten this error one time, so it affects me .45% of the
time and that was only because it was in the only package I was not
using -Wall on.

-Edward

On Wed, Jul 17, 2013 at 12:23 PM, Andreas Abel andreas.a...@ifi.lmu.de
mailto:andreas.a...@ifi.lmu.de wrote:

Here, again, is your ACTUAL CODE, commented, deployed, looping, and
maybe linked into your projects, if you are not careless about the
cabal constraints:


http://hackage.haskell.org/__packages/archive/mtl/2.1/doc/__html/src/Control-Monad-State-__Class.html#state

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

 -- | Embed a simple state action into the monad.
 state :: (s - (a, s)) - m a
 state f = do
   s - get
   let ~(a, s) = f s
   put s
   return a

Have fun with it,
Andreas


On 17.07.2013 02:20, Richard A. O'Keefe wrote:

Brian Marick sent me a couple of his stickers.
The one I have on my door reads to be less wrong than yesterday.
The other one I keep free to bring out and wave around:

 An example would be handy about now.

All of the arguing to and fro -- including mine! -- about
non-recursive let has been just so much hot air.  I could
go on about how the distinction between 'val' and 'val rec'
in ML was one of the things I came to dislike intensely,
and how Haskell's single coherent approach is one of the
things that attracted me to Haskell.

But why should anyone else care?

When presented with a difficulty, it is very common for some
functional language users to propose adding just one more
feature from some other language, commonly an imperative one
(which ML, Caml, and F# arguably are).  Typically this is
something that _would_ solve the immediate problem but would
create worse problems elsewhere, and there is some other
solution, either one already available in the language, or a
better one that would solve additional problems or cause
fewer ones.

The best help for any discussion is A CONCRETE EXAMPLE OF
REAL CODE.  Not little sketches hacked up for the purpose
of discussion, but ACTUAL CODE.  The person who initially
proposes a problem may think some details are not relevant,
whereas someone else may see them as the key to the solution.

For example, looking at some code in another mostly-
functional language, which had been presented as reason why
we needed a new construct, I rewrote it in less than half
the number of lines using existing constructors, using only
existing features.

Without seeing THE ACTUAL CODE that prompted this thread,
it is impossible to tell whether that might be the case here.

In this specific case, we are seeing state being threaded
through a bunch of updates, and IN THE ABSENCE OF THE ACTUAL
CODE, it seems to me that monad notation is the most
intention-revealing notation available for the purpose in
Haskell, and if Haskell did have non-recursive let it would
STILL be best to write such code using a state monad so that
human beings reading the Haskell code would have some idea
of what was happening, because that's how state changes are
supposed to be expressed in Haskell, and anything else
counts as obfuscation.

But THE ACTUAL CODE might show that this case was different
in some important way.



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



--
Andreas AbelDu bist der geliebte Mensch.

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

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

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




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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-17 Thread Markus Läll
For what it's worth, I think a non-recursive in the language would
just bring more confusion, in forums, IRC and whereever. The benefits
don't seem important at all, and the same effect can be achieved
through other means.

On Wed, Jul 17, 2013 at 2:20 AM, Richard A. O'Keefe o...@cs.otago.ac.nz wrote:
 Brian Marick sent me a couple of his stickers.
 The one I have on my door reads to be less wrong than yesterday.
 The other one I keep free to bring out and wave around:

 An example would be handy about now.

 All of the arguing to and fro -- including mine! -- about
 non-recursive let has been just so much hot air.  I could
 go on about how the distinction between 'val' and 'val rec'
 in ML was one of the things I came to dislike intensely,
 and how Haskell's single coherent approach is one of the
 things that attracted me to Haskell.

 But why should anyone else care?

 When presented with a difficulty, it is very common for some
 functional language users to propose adding just one more
 feature from some other language, commonly an imperative one
 (which ML, Caml, and F# arguably are).  Typically this is
 something that _would_ solve the immediate problem but would
 create worse problems elsewhere, and there is some other
 solution, either one already available in the language, or a
 better one that would solve additional problems or cause
 fewer ones.

 The best help for any discussion is A CONCRETE EXAMPLE OF
 REAL CODE.  Not little sketches hacked up for the purpose
 of discussion, but ACTUAL CODE.  The person who initially
 proposes a problem may think some details are not relevant,
 whereas someone else may see them as the key to the solution.

 For example, looking at some code in another mostly-
 functional language, which had been presented as reason why
 we needed a new construct, I rewrote it in less than half
 the number of lines using existing constructors, using only
 existing features.

 Without seeing THE ACTUAL CODE that prompted this thread,
 it is impossible to tell whether that might be the case here.

 In this specific case, we are seeing state being threaded
 through a bunch of updates, and IN THE ABSENCE OF THE ACTUAL
 CODE, it seems to me that monad notation is the most
 intention-revealing notation available for the purpose in
 Haskell, and if Haskell did have non-recursive let it would
 STILL be best to write such code using a state monad so that
 human beings reading the Haskell code would have some idea
 of what was happening, because that's how state changes are
 supposed to be expressed in Haskell, and anything else
 counts as obfuscation.

 But THE ACTUAL CODE might show that this case was different
 in some important way.



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



-- 
Markus Läll

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-17 Thread Andreas Abel
Here, again, is your ACTUAL CODE, commented, deployed, looping, and 
maybe linked into your projects, if you are not careless about the cabal 
constraints:


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

-- | Embed a simple state action into the monad.
state :: (s - (a, s)) - m a
state f = do
  s - get
  let ~(a, s) = f s
  put s
  return a

Have fun with it,
Andreas

On 17.07.2013 02:20, Richard A. O'Keefe wrote:

Brian Marick sent me a couple of his stickers.
The one I have on my door reads to be less wrong than yesterday.
The other one I keep free to bring out and wave around:

An example would be handy about now.

All of the arguing to and fro -- including mine! -- about
non-recursive let has been just so much hot air.  I could
go on about how the distinction between 'val' and 'val rec'
in ML was one of the things I came to dislike intensely,
and how Haskell's single coherent approach is one of the
things that attracted me to Haskell.

But why should anyone else care?

When presented with a difficulty, it is very common for some
functional language users to propose adding just one more
feature from some other language, commonly an imperative one
(which ML, Caml, and F# arguably are).  Typically this is
something that _would_ solve the immediate problem but would
create worse problems elsewhere, and there is some other
solution, either one already available in the language, or a
better one that would solve additional problems or cause
fewer ones.

The best help for any discussion is A CONCRETE EXAMPLE OF
REAL CODE.  Not little sketches hacked up for the purpose
of discussion, but ACTUAL CODE.  The person who initially
proposes a problem may think some details are not relevant,
whereas someone else may see them as the key to the solution.

For example, looking at some code in another mostly-
functional language, which had been presented as reason why
we needed a new construct, I rewrote it in less than half
the number of lines using existing constructors, using only
existing features.

Without seeing THE ACTUAL CODE that prompted this thread,
it is impossible to tell whether that might be the case here.

In this specific case, we are seeing state being threaded
through a bunch of updates, and IN THE ABSENCE OF THE ACTUAL
CODE, it seems to me that monad notation is the most
intention-revealing notation available for the purpose in
Haskell, and if Haskell did have non-recursive let it would
STILL be best to write such code using a state monad so that
human beings reading the Haskell code would have some idea
of what was happening, because that's how state changes are
supposed to be expressed in Haskell, and anything else
counts as obfuscation.

But THE ACTUAL CODE might show that this case was different
in some important way.



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




--
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] Proposal: Non-recursive let

2013-07-17 Thread Edward Kmett
This happened because I copied the surrounding style blindly. I fucked up.

state f = get = \s - case f s of
   (a, s) - do
 put s
 return a

would not have the problem and would have given a warning about name
shadowing.

I for one am somewhat neutral on the *adding* a non-recursive let to the
language, but I personally think case serves this purpose, and folks have
shown above that you can get it from a simple

x  f = f x

combinator. But I do not think that let should be non-recursive by default.
I commonly give a soup of possibly-recursive definitions using let or where
and the story for how to write such functions in a language where let is
non-recursive is much more painful.

-Edward

On Wed, Jul 17, 2013 at 12:23 PM, Andreas Abel andreas.a...@ifi.lmu.dewrote:

 Here, again, is your ACTUAL CODE, commented, deployed, looping, and maybe
 linked into your projects, if you are not careless about the cabal
 constraints:

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

 -- | Embed a simple state action into the monad.
 state :: (s - (a, s)) - m a
 state f = do
   s - get
   let ~(a, s) = f s
   put s
   return a

 Have fun with it,
 Andreas


 On 17.07.2013 02:20, Richard A. O'Keefe wrote:

 Brian Marick sent me a couple of his stickers.
 The one I have on my door reads to be less wrong than yesterday.
 The other one I keep free to bring out and wave around:

 An example would be handy about now.

 All of the arguing to and fro -- including mine! -- about
 non-recursive let has been just so much hot air.  I could
 go on about how the distinction between 'val' and 'val rec'
 in ML was one of the things I came to dislike intensely,
 and how Haskell's single coherent approach is one of the
 things that attracted me to Haskell.

 But why should anyone else care?

 When presented with a difficulty, it is very common for some
 functional language users to propose adding just one more
 feature from some other language, commonly an imperative one
 (which ML, Caml, and F# arguably are).  Typically this is
 something that _would_ solve the immediate problem but would
 create worse problems elsewhere, and there is some other
 solution, either one already available in the language, or a
 better one that would solve additional problems or cause
 fewer ones.

 The best help for any discussion is A CONCRETE EXAMPLE OF
 REAL CODE.  Not little sketches hacked up for the purpose
 of discussion, but ACTUAL CODE.  The person who initially
 proposes a problem may think some details are not relevant,
 whereas someone else may see them as the key to the solution.

 For example, looking at some code in another mostly-
 functional language, which had been presented as reason why
 we needed a new construct, I rewrote it in less than half
 the number of lines using existing constructors, using only
 existing features.

 Without seeing THE ACTUAL CODE that prompted this thread,
 it is impossible to tell whether that might be the case here.

 In this specific case, we are seeing state being threaded
 through a bunch of updates, and IN THE ABSENCE OF THE ACTUAL
 CODE, it seems to me that monad notation is the most
 intention-revealing notation available for the purpose in
 Haskell, and if Haskell did have non-recursive let it would
 STILL be best to write such code using a state monad so that
 human beings reading the Haskell code would have some idea
 of what was happening, because that's how state changes are
 supposed to be expressed in Haskell, and anything else
 counts as obfuscation.

 But THE ACTUAL CODE might show that this case was different
 in some important way.



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



 --
 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/ http://www2.tcs.ifi.lmu.de/~abel/

 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] Proposal: Non-recursive let

2013-07-17 Thread Edward Kmett
FWIW, I maintain, according to wc and sloccount, 220841 lines worth of
Haskell code at present.

I have been bitten this error one time, so it affects me .45% of the
time and that was only because it was in the only package I was not using
-Wall on.

-Edward

On Wed, Jul 17, 2013 at 12:23 PM, Andreas Abel andreas.a...@ifi.lmu.dewrote:

 Here, again, is your ACTUAL CODE, commented, deployed, looping, and maybe
 linked into your projects, if you are not careless about the cabal
 constraints:

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

 -- | Embed a simple state action into the monad.
 state :: (s - (a, s)) - m a
 state f = do
   s - get
   let ~(a, s) = f s
   put s
   return a

 Have fun with it,
 Andreas


 On 17.07.2013 02:20, Richard A. O'Keefe wrote:

 Brian Marick sent me a couple of his stickers.
 The one I have on my door reads to be less wrong than yesterday.
 The other one I keep free to bring out and wave around:

 An example would be handy about now.

 All of the arguing to and fro -- including mine! -- about
 non-recursive let has been just so much hot air.  I could
 go on about how the distinction between 'val' and 'val rec'
 in ML was one of the things I came to dislike intensely,
 and how Haskell's single coherent approach is one of the
 things that attracted me to Haskell.

 But why should anyone else care?

 When presented with a difficulty, it is very common for some
 functional language users to propose adding just one more
 feature from some other language, commonly an imperative one
 (which ML, Caml, and F# arguably are).  Typically this is
 something that _would_ solve the immediate problem but would
 create worse problems elsewhere, and there is some other
 solution, either one already available in the language, or a
 better one that would solve additional problems or cause
 fewer ones.

 The best help for any discussion is A CONCRETE EXAMPLE OF
 REAL CODE.  Not little sketches hacked up for the purpose
 of discussion, but ACTUAL CODE.  The person who initially
 proposes a problem may think some details are not relevant,
 whereas someone else may see them as the key to the solution.

 For example, looking at some code in another mostly-
 functional language, which had been presented as reason why
 we needed a new construct, I rewrote it in less than half
 the number of lines using existing constructors, using only
 existing features.

 Without seeing THE ACTUAL CODE that prompted this thread,
 it is impossible to tell whether that might be the case here.

 In this specific case, we are seeing state being threaded
 through a bunch of updates, and IN THE ABSENCE OF THE ACTUAL
 CODE, it seems to me that monad notation is the most
 intention-revealing notation available for the purpose in
 Haskell, and if Haskell did have non-recursive let it would
 STILL be best to write such code using a state monad so that
 human beings reading the Haskell code would have some idea
 of what was happening, because that's how state changes are
 supposed to be expressed in Haskell, and anything else
 counts as obfuscation.

 But THE ACTUAL CODE might show that this case was different
 in some important way.



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



 --
 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/ http://www2.tcs.ifi.lmu.de/~abel/

 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] Proposal: Non-recursive let

2013-07-16 Thread Andreas Abel

Ah, now I have the solution:

{-# LANGUAGE CPP #-}

(|) = flip ($)

#define LET(p, e) (e) | \ (p) -

bla = LET(x, 5)
  LET(Just x, Just (x+1))
  x

#define MLET(p, e) (e) | \ (p) - do

main = do
  MLET((x, y), (5, 3))
  print (x + y)

Beautiful, ain't it?  Sigh.

--Andreas

On 11.07.2013 17:40, Carter Schonwald wrote:

Yup. Nested cases *are* non recursive lets.

(Can't believe I forgot about that )

On Thursday, July 11, 2013, Edward Kmett wrote:


blah = case foo 1 [] of
   (x, s) - case bar x s of
  (y, s) - case baz x y s of
(z, s) - ...

-Edward



--
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] Proposal: Non-recursive let

2013-07-16 Thread Timon Gehr

On 07/11/2013 08:37 AM, AntC wrote:

oleg at okmij.org writes:
...
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.

I once wrote about 50-100 lines of code with the fragment like the
above and the only problem was my messing up the numbering (at one
place I used s2 where I should've used s3). ...


Oleg, I hope you are not saying that in production code you use names like
x, y, z, s1, s2, s3, s4, ...



Depending on context, those can be perfectly good names, modulo the 
numbering. I'd be more worried about 'foo', 'bar', 'baz'. :o)



It leads to opaque code.


Questionable. Typically there tends to be more relevant information in 
the name of an arrow than in the name of a point, with the arrows 
connecting the points and thus clarifying their meaning.



If even you can mess up, what hope for us with only nano-Oleg brain capacity?



Non-recursive let.


(On a less tongue-in-cheek note, IMHO, assuming that there is something 
like a constant 'brain capacity' significantly varying between persons 
that limits how well one can master a certain discipline is a good start 
for painting oneself into a corner.)



Next you'll be wanting GOTO  and destructive assignment.



Unlikely. Haskell already has constructs which are more expressive than 
goto and destructive assignment, without requiring the language to give 
up the benefits of the absence of those features in direct code.



Who knows: one day somebody modifying your code might need to insert a
line. (That 'somebody' might be your future self.)



(That was part of his point.)


Just don't do that! Use long_and_meaningful names.



'meaningful' is long enough.


50-100 near-identical lines of code sounds like an opportunity for an
algorithm.
...


He expressed that he wrote 50-100 lines of code containing such a short 
fragment and the only problem was inside that fragment. Since the goal 
of that anecdote presumably was to establish the relevance of a pitfall 
that a non-recursive let would make less severe, I think this is a more 
natural way to interpret the only slightly ambiguous wording.



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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-16 Thread Richard A. O'Keefe
Brian Marick sent me a couple of his stickers.
The one I have on my door reads to be less wrong than yesterday.
The other one I keep free to bring out and wave around:

An example would be handy about now.

All of the arguing to and fro -- including mine! -- about
non-recursive let has been just so much hot air.  I could
go on about how the distinction between 'val' and 'val rec'
in ML was one of the things I came to dislike intensely,
and how Haskell's single coherent approach is one of the
things that attracted me to Haskell.

But why should anyone else care?

When presented with a difficulty, it is very common for some
functional language users to propose adding just one more
feature from some other language, commonly an imperative one
(which ML, Caml, and F# arguably are).  Typically this is
something that _would_ solve the immediate problem but would
create worse problems elsewhere, and there is some other
solution, either one already available in the language, or a
better one that would solve additional problems or cause
fewer ones.

The best help for any discussion is A CONCRETE EXAMPLE OF
REAL CODE.  Not little sketches hacked up for the purpose
of discussion, but ACTUAL CODE.  The person who initially
proposes a problem may think some details are not relevant,
whereas someone else may see them as the key to the solution.

For example, looking at some code in another mostly-
functional language, which had been presented as reason why
we needed a new construct, I rewrote it in less than half
the number of lines using existing constructors, using only
existing features.

Without seeing THE ACTUAL CODE that prompted this thread,
it is impossible to tell whether that might be the case here.

In this specific case, we are seeing state being threaded
through a bunch of updates, and IN THE ABSENCE OF THE ACTUAL
CODE, it seems to me that monad notation is the most
intention-revealing notation available for the purpose in
Haskell, and if Haskell did have non-recursive let it would
STILL be best to write such code using a state monad so that
human beings reading the Haskell code would have some idea
of what was happening, because that's how state changes are
supposed to be expressed in Haskell, and anything else
counts as obfuscation.

But THE ACTUAL CODE might show that this case was different
in some important way.



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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-11 Thread AntC
 oleg at okmij.org writes:
 ...
 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. 
 
 I once wrote about 50-100 lines of code with the fragment like the
 above and the only problem was my messing up the numbering (at one
 place I used s2 where I should've used s3). ...

Oleg, I hope you are not saying that in production code you use names like 
x, y, z, s1, s2, s3, s4, ...

It leads to opaque code. If even you can mess up, what hope for us with 
only nano-Oleg brain capacity?

Next you'll be wanting GOTO and destructive assignment.

Who knows: one day somebody modifying your code might need to insert a 
line. (That 'somebody' might be your future self.)

Just don't do that! Use long_and_meaningful names.

50-100 near-identical lines of code sounds like an opportunity for an 
algorithm.

AntC


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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-11 Thread Edward Kmett
On Wed, Jul 10, 2013 at 3:47 AM, o...@okmij.org wrote:


 Jon Fairbairn wrote:
  It just changes forgetting to use different variable names because of
  recursion (which is currently uniform throughout the language) to
  forgetting to use non recursive let instead of let.

 Let me bring to the record the message I just wrote on Haskell-cafe

 http://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

 and repeat the example:

 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.


blah = case foo 1 [] of
  (x, s) - case bar x s of
 (y, s) - case baz x y s of
   (z, s) - ...

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-11 Thread Carter Schonwald
Yup. Nested cases *are* non recursive lets.

(Can't believe I forgot about that )

On Thursday, July 11, 2013, Edward Kmett wrote:

 On Wed, Jul 10, 2013 at 3:47 AM, o...@okmij.org javascript:_e({},
 'cvml', 'o...@okmij.org'); wrote:


 Jon Fairbairn wrote:
  It just changes forgetting to use different variable names because of
  recursion (which is currently uniform throughout the language) to
  forgetting to use non recursive let instead of let.

 Let me bring to the record the message I just wrote on Haskell-cafe

 http://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

 and repeat the example:

 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.


 blah = case foo 1 [] of
   (x, s) - case bar x s of
  (y, s) - case baz x y s of
(z, s) - ...

 -Edward

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-11 Thread Andreas Abel

I can do this without extra indentation:

  (|) = flip ($)

  f = 5 | \ x -
  6 | \ y -
  x + y

Non-recursive let is as superfluous as the do-notation.

On 11.07.2013 17:40, Carter Schonwald wrote:

Yup. Nested cases *are* non recursive lets.

(Can't believe I forgot about that )

On Thursday, July 11, 2013, Edward Kmett wrote:

On Wed, Jul 10, 2013 at 3:47 AM, o...@okmij.org javascript:_e({},
'cvml', 'o...@okmij.org'); wrote:


Jon Fairbairn wrote:
  It just changes forgetting to use different variable names
because of
  recursion (which is currently uniform throughout the language) to
  forgetting to use non recursive let instead of let.

Let me bring to the record the message I just wrote on Haskell-cafe
http://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

and repeat the example:

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.


blah = case foo 1 [] of
   (x, s) - case bar x s of
  (y, s) - case baz x y s of
(z, s) - ...

-Edward



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




--
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] Proposal: Non-recursive let

2013-07-11 Thread Edward Kmett
Lens even supplies this as ()

On Thu, Jul 11, 2013 at 5:18 PM, Andreas Abel andreas.a...@ifi.lmu.dewrote:

 I can do this without extra indentation:

   (|) = flip ($)

   f = 5 | \ x -
   6 | \ y -
   x + y

 Non-recursive let is as superfluous as the do-notation.


 On 11.07.2013 17:40, Carter Schonwald wrote:

 Yup. Nested cases *are* non recursive lets.

 (Can't believe I forgot about that )

 On Thursday, July 11, 2013, Edward Kmett wrote:

 On Wed, Jul 10, 2013 at 3:47 AM, o...@okmij.org javascript:_e({},

 'cvml', 'o...@okmij.org'); wrote:


 Jon Fairbairn wrote:
   It just changes forgetting to use different variable names
 because of
   recursion (which is currently uniform throughout the language)
 to
   forgetting to use non recursive let instead of let.

 Let me bring to the record the message I just wrote on
 Haskell-cafe
 http://www.haskell.org/**pipermail/haskell-cafe/2013-**
 July/109116.htmlhttp://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

 and repeat the example:

 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.


 blah = case foo 1 [] of
(x, s) - case bar x s of
   (y, s) - case baz x y s of
 (z, s) - ...

 -Edward



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



 --
 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/ http://www2.tcs.ifi.lmu.de/~abel/

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


[Haskell-cafe] Proposal: Non-recursive let

2013-07-10 Thread oleg

Jon Fairbairn wrote:
 It just changes forgetting to use different variable names because of
 recursion (which is currently uniform throughout the language) to
 forgetting to use non recursive let instead of let.

Let me bring to the record the message I just wrote on Haskell-cafe
http://www.haskell.org/pipermail/haskell-cafe/2013-July/109116.html

and repeat the example:

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. 

I once wrote about 50-100 lines of code with the fragment like the
above and the only problem was my messing up the numbering (at one
place I used s2 where I should've used s3). In the chain of lets, it
becomes quite a chore to use different variable names -- especially as
one edits the code and adds new let statements.

I have also had problems with non-termination, unintended recursion. 
The problem is not caught statically and leads to looping, which may
be quite difficult to debug. Andreas should tell his story.

In my OCaml experience, I don't ever remember writing let rec by
mistake. Occasionally I write let where let rec is meant, and the type
checker very quickly points out a problem (an unbound identifier).
No need to debug anything.

Incidentally, time and again people ask on the Caml list why 'let' in
OCaml is by default non-recursive. The common answer is that the
practitioners find in their experience the non-recursive let to be a
better default. Recursion should be intended and explicit -- more
errors are caught that way.

Let me finally disagree with the uniformity principle. It may be
uniform to have equi-recursive types. OCaml has equi-recursive types;
internally the type checker treats _all_ types as (potentially)
equi-recursive. At one point OCaml allowed equi-recursive types in
user programs as well. They were introduced for the sake of objects;
so the designers felt uniformly warrants to offer them in all
circumstances. The users vocally disagreed. Equi-recursive types mask
many common type errors, making them much more difficult to find. As
the result, OCaml developers broke the uniformity. Now, equi-recursive
types may only appear in surface programs in very specific
circumstances (where objects or their duals are involved). Basically,
the programmer must really intend to use them.

Here is an example from the natural language, English. Some verbs go from
regular (uniform conjugation) to irregular:
http://en.wiktionary.org/wiki/dive


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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-10 Thread Ezra e. k. Cooper
I support Oleg's proposal. A shadowing, non-recursive let would be a
useful tool.

As starter suggestions for the keyword or syntax, I submit:

  let new x = expr in body   -- Not the old x!

  let shadowing x = expr in body

  shadow x = expr in body

  let x =! expr in body  -- The explosive bang gives an imperative
  flavor.

Other suggestions would be welcome.

Ezra

On Wed, Jul 10, 2013, at 01:47 AM, o...@okmij.org wrote:
 
 I have also had problems with non-termination, unintended recursion. 
 The problem is not caught statically and leads to looping, which may
 be quite difficult to debug. Andreas should tell his story.

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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-10 Thread Ertugrul Söylemez
Ezra e. k. Cooper e...@ezrakilty.net wrote:

 As starter suggestions for the keyword or syntax, I submit:

   let new x = expr in body   -- Not the old x!

It's not the old x in either case (recursive and non-recursive).


   let shadowing x = expr in body

   shadow x = expr in body

It's shadowing in either case.


   let x =! expr in body  -- The explosive bang gives an imperative
   flavor.

(=!) is a valid operator name.


 Other suggestions would be welcome.

My suggestion:  Don't add a non-recursive let.  See my other post about
general recursion and totality checking.


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] Proposal: Non-recursive let

2013-07-10 Thread Carter Schonwald
theres a very simple way to do non recursive let already! do notation in
the identity monad. I use it quite a lot lately.


On Wed, Jul 10, 2013 at 1:49 PM, Ertugrul Söylemez e...@ertes.de wrote:

 Ezra e. k. Cooper e...@ezrakilty.net wrote:

  As starter suggestions for the keyword or syntax, I submit:
 
let new x = expr in body   -- Not the old x!

 It's not the old x in either case (recursive and non-recursive).


let shadowing x = expr in body
 
shadow x = expr in body

 It's shadowing in either case.


let x =! expr in body  -- The explosive bang gives an imperative
flavor.

 (=!) is a valid operator name.


  Other suggestions would be welcome.

 My suggestion:  Don't add a non-recursive let.  See my other post about
 general recursion and totality checking.


 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


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


Re: [Haskell-cafe] Proposal: Non-recursive let

2013-07-10 Thread Andreas Abel

On 10.07.13 9:31 PM, Carter Schonwald wrote:

theres a very simple way to do non recursive let already! do notation in
the identity monad. I use it quite a lot lately.


Yeah, the hack

  x - return $ e

instead of

  let x = e

has been discussed already.

If you put everything into the Identity monad, you lose if-then-else and 
direct use of case, instead of


  case me of {branches }

you need to write

   e - me; case e of { branches }

This gets a bit better with the new \case, if you can afford to only 
compile on the newest ghc.


  me = \case { branches }



On Wed, Jul 10, 2013 at 1:49 PM, Ertugrul Söylemez e...@ertes.de
mailto:e...@ertes.de wrote:

Ezra e. k. Cooper e...@ezrakilty.net mailto:e...@ezrakilty.net
wrote:

  As starter suggestions for the keyword or syntax, I submit:
 
let new x = expr in body   -- Not the old x!

It's not the old x in either case (recursive and non-recursive).


let shadowing x = expr in body
 
shadow x = expr in body

It's shadowing in either case.


let x =! expr in body  -- The explosive bang gives an imperative
flavor.

(=!) is a valid operator name.


  Other suggestions would be welcome.

My suggestion:  Don't add a non-recursive let.  See my other post about
general recursion and totality checking.


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.



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