
Erlang's equivalent of [m..n] is lists:seq(M, N), which is currently defined to raise an exception when N < M. In particular, lists:seq(1, N) returns a list of length N when N > 0, but not when N = 0. I'm currently arguing that lists:seq(1, 0) should be [], not an exception. Oddly enough, I'm being beaten over the head with Haskell, of all things. In Haskell, "The sequence enumFromTo e1 e3 is the list [e1,e1+1,e1+2,...e3]. The list is empty if e1 > e3." It is being claimed that the reason for this is that "exceptions are problematic" in Hasell, so the Haskell designers went out of their way to make this function total whether it made sense or not. I am currently suggesting that it's to keep the specification (for integers) simple: "[m..n] is the set of integers x such that m<=x<=n, listed in ascending order". There's also the nice equivalence between [m..n] and takeWhile (<= n) [m..]. Unfortunately, no such "abstract" characterisation of [m..n] is mentioned in the report, and the takeWhile connection is inferred from numericEnumFromTo. Does anyone remember why the definition of enumFromTo is the way it is? -- If stupidity were a crime, who'd 'scape hanging?

G'day all.
Quoting "Richard A. O'Keefe"
I'm currently arguing that lists:seq(1, 0) should be [], not an exception. Oddly enough, I'm being beaten over the head with Haskell, of all things. [...] Does anyone remember why the definition of enumFromTo is the way it is?
I don't know if this is the reason, but there's another nice property that enumerations have, namely: [p..q-1] ++ [q..r-1] == [p..r-1] -- if p <= q <= r If you think of the abstract semantics of ranges, this makes perfect sense. There needs to be a notation for empty ranges. Having said that, I don't know of a good reason why [5,5..5] is an infinte list of 5's. Cheers, Andrew Bromage

ajb@spamcop.net wrote:
Having said that, I don't know of a good reason why [5,5..5] is an infinte list of 5's.
I'm sure you know *why* it's an infinite list[1], but as for why that's useful I can't say. It has the feel of a bug in implementation, though it is ...consistent. As for the OP, like Python, Perl also takes [m..n] to be [] when n < m. They may not be as principled as Haskell or Erlang, but it does seem to be the consensus view. [1] Because the "5,5.." yields an (unfoldr (Just . (\x -> (x,x)) . (+0)) 5) stream but the "..5" only causes termination just as soon as the stream is surpassing 5, which it never will. -- Live well, ~wren

G'day.
Quoting wren ng thornton
I'm sure you know *why* it's an infinite list[1], but as for why that's useful I can't say. It has the feel of a bug in implementation, though it is ...consistent.
Right. I have no problem with [5,5..5] being logically an anamorphism, but thinking abstractly about what I'd want it to mean, I'm pretty sure I don't want it to mean an infinite list of 5's. I asked a class of about a dozen bright undergrads about 10 years ago what they thought it should mean, and IIRC the consensus seemed to be split between [5] and [5,5]. Nobody correctly guessed what it actually did. So whether the behaviour is technically right or wrong, it violates the Principle of Least Surprise. Cheers, Andrew Bromage

In Haskell, "The sequence enumFromTo e1 e3 is the list [e1,e1+1,e1+2,...e3]. The list is empty if e1 > e3."
I like it, since it means that things like [n .. n + length m - 1] work as expected when m is []. Or say 'map (array!) [bsearch x .. bsearch y - 1]'. Tangent: Of course, I would prefer the range be half-open, which is a pretty consistent standard in the rest of the world. I've had a number of off by one errors from this, and from Array.bounds. I guess it's too late to fix those, though, even if there were agreement that they need to be fixed. This is similar to the way python considers that xs[4:2] is valid, and is []. Of course python uses half-open ranges so xs[4:4] is still [].

Darn, I sent this as personal mail the first time. Evan Laforge wrote:
In Haskell, "The sequence enumFromTo e1 e3 is the list [e1,e1+1,e1+2,...e3]. The list is empty if e1 > e3."
I like it, since it means that things like [n .. n + length m - 1] work as expected when m is []. Or say 'map (array!) [bsearch x .. bsearch y - 1]'.
Tangent: Of course, I would prefer the range be half-open, which is a pretty consistent standard in the rest of the world. I've had a number of off by one errors from this, and from Array.bounds. I guess it's too late to fix those, though, even if there were agreement that they need to be fixed.
It causes problems with types that have an upper bound. You can't express Haskell's [False .. True] as a half-open range for example. --- One solution would be a new syntax for half-open ranges distinct from that for closed ranges, or maybe a couple of operators. Sketching without a compiler: lo <. hi = takeWhile (< hi) [lo ..] data EnumStart a = a :& a (lo :& mid) <: hi = takeWhile (< hi) [lo, mid ..] So you can do things like (0 <. 10) or (0 :& 2 <: 10) Or one could use the same operator for both, if one defined something like: class OpenEnum bot top where (<.) :: bot -> top -> [top] instance (Enum e) => OpenEnum e e where lo <. hi = takeWhile (< hi) [lo ..] instance (Enum e) => OpenEnum (EnumStart a) a ... (lo :& mid) <. hi = takeWhile (< hi) [lo, mid ..] A better choice of line noise for the operator could still be made though. -- src/

On Sat, 2008-09-27 at 02:09 +0100, Simon Richard Clarkstone wrote:
Darn, I sent this as personal mail the first time.
Evan Laforge wrote:
In Haskell, "The sequence enumFromTo e1 e3 is the list [e1,e1+1,e1+2,...e3]. The list is empty if e1 > e3."
I like it, since it means that things like [n .. n + length m - 1] work as expected when m is []. Or say 'map (array!) [bsearch x .. bsearch y - 1]'.
Tangent: Of course, I would prefer the range be half-open, which is a pretty consistent standard in the rest of the world. I've had a number of off by one errors from this, and from Array.bounds. I guess it's too late to fix those, though, even if there were agreement that they need to be fixed.
It causes problems with types that have an upper bound. You can't express Haskell's [False .. True] as a half-open range for example.
[False .. ] works great, though, whether ranges are closed or half-open. jcc

Jonathan Cast wrote:
On Sat, 2008-09-27 at 02:09 +0100, Simon Richard Clarkstone wrote:
Darn, I sent this as personal mail the first time.
Evan Laforge wrote:
In Haskell, "The sequence enumFromTo e1 e3 is the list [e1,e1+1,e1+2,...e3]. The list is empty if e1 > e3." I like it, since it means that things like [n .. n + length m - 1] work as expected when m is []. Or say 'map (array!) [bsearch x .. bsearch y - 1]'.
Tangent: Of course, I would prefer the range be half-open, which is a pretty consistent standard in the rest of the world. I've had a number of off by one errors from this, and from Array.bounds. I guess it's too late to fix those, though, even if there were agreement that they need to be fixed. It causes problems with types that have an upper bound. You can't express Haskell's [False .. True] as a half-open range for example.
[False .. ] works great, though, whether ranges are closed or half-open.
You get problems though if you want to tell a function about a range, passing in a low and a high by some means, and it is expecting a half-open range, but you want to tell it [False..]. For example, creating a new array. BTW, why isn't [..] the notation for the entirety of a Bounded type? --- This mailing list is odd; thunderbird defaults to replying to sender rather than to the whole list. -- src/

"Richard A. O'Keefe"
Erlang's equivalent of [m..n] is lists:seq(M, N), which is currently defined to raise an exception when N < M. In particular, lists:seq(1, N) returns a list of length N when N > 0, but not when N = 0. I'm currently arguing that lists:seq(1, 0) should be [], not an exception. Oddly enough, I'm being beaten over the head with Haskell, of all things.
In Haskell, "The sequence enumFromTo e1 e3 is the list [e1,e1+1,e1+2,...e3]. The list is empty if e1 > e3."
It is being claimed that the reason for this is that "exceptions are problematic" in Hasell, so the Haskell designers went out of their way to make this function total whether it made sense or not.
I'm pretty sure that's not true. I'd like to be able to say "I know, I was there", but although I was there it was so long ago that my memory isn't clear. But it's clearly the case that [5 .. 6] is [5, 6] (length 2) and [5 .. 5] has to be [5] (length 1), so it's not unreasonable to expect that [5, 4] be [] (length 0) -- having the induction extend down to there makes most sense. I'm fairly certain it was arguments about induction and what constituted sensible behaviour rather than our admitted dislike for exceptions that carried the argument. -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On 2008 Sep 22, at 5:46, Jon Fairbairn wrote:
"Richard A. O'Keefe"
writes: It is being claimed that the reason for this is that "exceptions are problematic" in Hasell, so the Haskell designers went out of their way to make this function total whether it made sense or not.
I'm pretty sure that's not true. I'd like to be able to say "I know, I was there", but although I was there it was so long ago that my memory isn't clear. But it's clearly the
I would say it's more a matter of Haskell programmers thinking partial functions are evil as a general (mathematical) principle. And the claimant above is thinking of needing to catch exceptions in IO, and probably comes from the school of programming that says that invalid values should raise exceptions. Which sounds like a good idea until you see how often people do try {mumble()} catch {} or similar. (Go look at some Java programs; Java goes even farther with that idea and requires programmers to declare the exceptions they can throw, so many programmers shortcircuit the exceptions away to avoid having to deal with it.) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH
participants (8)
-
ajb@spamcop.net
-
Brandon S. Allbery KF8NH
-
Evan Laforge
-
Jon Fairbairn
-
Jonathan Cast
-
Richard A. O'Keefe
-
Simon Richard Clarkstone
-
wren ng thornton