
Hi all, I was surprised to find out that the following piece of code:
length [1..] > 10
isnt lazily evaluated! I wouldnt expect this to be a bug, but in this case, shouldnt the computation end when the length function evaluation goes something like:
10 + length [11..]
? -- -- Vimal

Hi Vimal,
I was surprised to find out that the following piece of code:
length [1..] > 10
isnt lazily evaluated!
The problem is that Int and Integer are both eager. It is possible to write a lazy peano number based data type, but I'm not aware of anyone who has - I have half the code (in joint work with Matt Naylor and Greg Manning) but none of us have taken the time to finish it off properly. For details about why we should have lazy naturals read http://citeseer.ist.psu.edu/45669.html - Colin Runciman, What About the Natural Numbers (1989) Thanks Neil

Vimal wrote:
Hi all,
I was surprised to find out that the following piece of code:
length [1..] > 10
isnt lazily evaluated! I wouldnt expect this to be a bug, but in this case, shouldnt the computation end when the length function evaluation goes something like:
10 + length [11..]
10", *we* are smart enough to break apart the left-hand argument to (>) and inspect the arguments to (+), observe that "length" will never return a negative value, and concluded that we can stop evaluating. But
I suspect that > when defined on integers is strict in both arguments, i.e., defined to not be lazily evaluated. Even if it's not, when the reduction gets as far as "11 + length [12..] the implementation of (>) is not so smart.

Vimal wrote:
I was surprised to find out that the following piece of code:
length [1..] > 10
isnt lazily evaluated! I wouldnt expect this to be a bug, but in this case, shouldnt the computation end when the length function evaluation goes something like:
10 + length [11..]
That's the spirit, but you still need the right integer type for that :) I mean, Haskell does not magically detect that the 32(64)-bit integer (10 + length [11..]) :: Int is bigger than 10 :: Int . But by using peano numbers, the comparison function can detect that, see also http://article.gmane.org/gmane.comp.lang.haskell.cafe/26329 Regards, apfelmus

On Mon, Sep 24, 2007 at 06:28:59PM +0200, apfelmus wrote:
I mean, Haskell does not magically detect that the 32(64)-bit integer (10 + length [11..]) :: Int is bigger than 10 :: Int .
That's partly because it's not true. There are arbitrarily large finite lists for which the equivalent is false, e.g. on a 32bit machine: Prelude> 10 + length (replicate maxBound 'a') -2147483639 Thanks Ian

Vimal wrote:
Hi all,
I was surprised to find out that the following piece of code:
length [1..] > 10
isnt lazily evaluated! I wouldnt expect this to be a bug, but in this case, shouldnt the computation end when the length function evaluation goes something like:
10 + length [11..]
?
In an ideal world, yes. In this world, use "length (take 11 [1..]) > 10"...

On Mon, 2007-09-24 at 17:35 +0100, Andrew Coppin wrote:
Vimal wrote:
Hi all,
I was surprised to find out that the following piece of code:
length [1..] > 10
isnt lazily evaluated! I wouldnt expect this to be a bug, but in this case, shouldnt the computation end when the length function evaluation goes something like:
10 + length [11..]
?
In an ideal world, yes.
In this world, use "length (take 11 [1..]) > 10"...
not (null (drop 10 [1..])) is surely faster (not tested...) jcc

Jonathan Cast wrote:
On Mon, 2007-09-24 at 17:35 +0100, Andrew Coppin wrote:
In an ideal world, yes.
In this world, use "length (take 11 [1..]) > 10"...
not (null (drop 10 [1..])) is surely faster (not tested...)
Faster? There might be a few microseconds in it. Clearer? Possibly... ;-)

Hi
In this world, use "length (take 11 [1..]) > 10"...
not (null (drop 10 [1..])) is surely faster (not tested...)
Faster? There might be a few microseconds in it.
Clearer? Possibly... ;-)
lengthNat [1..] > 10 Couldn't be clearer, and can be made to work perfectly. If anyone does want to pick up the lazy naturals work, I can send over the code (or write it yourself - its not hard!) Thanks Neil

Neil Mitchell wrote:
Hi
lengthNat [1..] > 10
Couldn't be clearer, and can be made to work perfectly. If anyone does want to pick up the lazy naturals work, I can send over the code (or write it yourself - its not hard!)
Um... isn't a lazy natural just a list with no data, where the list length encodes a number?

Hi
lengthNat [1..] > 10
Couldn't be clearer, and can be made to work perfectly. If anyone does want to pick up the lazy naturals work, I can send over the code (or write it yourself - its not hard!)
Um... isn't a lazy natural just a list with no data, where the list length encodes a number?
Pretty much, yes. Thanks Neil

Neil Mitchell wrote:
Hi
Um... isn't a lazy natural just a list with no data, where the list length encodes a number?
Pretty much, yes.
So I just need to write newtype LazyNatural = LazyNatural [()] and then add some suitable instances. ;-) (Woah... that's one bizzare-looking type there!) Hey, the "length" function would then just be ln_length :: [x] -> LazyNatural ln_length = LazyNatural . map (const ()) Ooo, that's hard.

Hi
Pretty much, yes.
So I just need to write
newtype LazyNatural = LazyNatural [()]
or data Nat = Zero | Succ Nat it's your choice really.
and then add some suitable instances. ;-)
Yes. Lots of them. Lots of instances and lots of methods.
Hey, the "length" function would then just be
ln_length :: [x] -> LazyNatural ln_length = LazyNatural . map (const ())
Ooo, that's hard.
Nope, its really easy. Its just quite a bit of work filling in all the instances. I bet you can't do it and upload the results to hackage within 24 hours :-) Thanks Neil

Neil Mitchell wrote:
Hi
Pretty much, yes.
So I just need to write
newtype LazyNatural = LazyNatural [()]
or
data Nat = Zero | Succ Nat
it's your choice really.
I'm guessing there's going to be fairly minimal performance difference. (Or maybe there is. My way uses a few additional pointers. But it also allows me to elegantly recycle existing Prelude list functions, so...)
and then add some suitable instances. ;-)
Yes. Lots of them. Lots of instances and lots of methods.
Hey, the "length" function would then just be
ln_length :: [x] -> LazyNatural ln_length = LazyNatural . map (const ())
Ooo, that's hard.
Nope, its really easy. Its just quite a bit of work filling in all the instances. I bet you can't do it and upload the results to hackage within 24 hours :-)
*ALL* the instances? No. A small handful of them? Sure. How about this... module LazyNatural (LazyNatural ()) where import Data.List newtype LazyNatural = LN [()] instance Show LazyNatural where show (LN x) = "LN " ++ show (length x) instance Eq LazyNatural where (LN x) == (LN y) = x == y instance Ord LazyNatural where compare (LN x) (LN y) = raw_compare x y raw_compare ([]) (_:_) = LT raw_compare ([]) ([]) = EQ raw_compare (_:_) ([]) = GT raw_compare (_:x) (_:y) = raw_compare x y instance Num LazyNatural where (LN x) + (LN y) = LN (x ++ y) (LN x) - (LN y) = LN (raw_minus x y) (LN x) * (LN y) = LN (concatMap (const x) y) negate _ = error "negate is not defined for LazyNatural" abs = id signum (LN []) = LN [] signum (LN _) = LN [()] fromInteger = LN . flip genericReplicate () raw_minus (_:a) (_:b) = raw_minus a b raw_minus (a) ([]) = a raw_minus _ _ = error "negative result from subtraction"

Hi
I'm guessing there's going to be fairly minimal performance difference. (Or maybe there is. My way uses a few additional pointers. But it also allows me to elegantly recycle existing Prelude list functions, so...)
I think we can safely assume that people using peano numbers aren't actually overly interested in performance...
*ALL* the instances? No.
A small handful of them? Sure. How about this...
How about creating a darcs repo, a cabal package and uploading it to hackage? Two design decisions you made could have been done differently (not sure which is best) If you read the lazy naturals paper it says that 4 - 8 should be 0. This follows the whole drop 8 [] = [], not _|_ Your show function is strict. Not sure whether this is a good idea or not. You could also include the constant infinity in your library: infinity = LN (repeat ()) Thanks Neil

Since natural numbers are trivial to implement (inefficiently) I took 15
minutes and added them to my numbers package in Hackage.
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/numbers-2007.9.24
-- Lennart
On 9/24/07, Andrew Coppin
Neil Mitchell wrote:
Hi
Pretty much, yes.
So I just need to write
newtype LazyNatural = LazyNatural [()]
or
data Nat = Zero | Succ Nat
it's your choice really.
I'm guessing there's going to be fairly minimal performance difference. (Or maybe there is. My way uses a few additional pointers. But it also allows me to elegantly recycle existing Prelude list functions, so...)
and then add some suitable instances. ;-)
Yes. Lots of them. Lots of instances and lots of methods.
Hey, the "length" function would then just be
ln_length :: [x] -> LazyNatural ln_length = LazyNatural . map (const ())
Ooo, that's hard.
Nope, its really easy. Its just quite a bit of work filling in all the instances. I bet you can't do it and upload the results to hackage within 24 hours :-)
*ALL* the instances? No.
A small handful of them? Sure. How about this...
module LazyNatural (LazyNatural ()) where
import Data.List
newtype LazyNatural = LN [()]
instance Show LazyNatural where show (LN x) = "LN " ++ show (length x)
instance Eq LazyNatural where (LN x) == (LN y) = x == y
instance Ord LazyNatural where compare (LN x) (LN y) = raw_compare x y
raw_compare ([]) (_:_) = LT raw_compare ([]) ([]) = EQ raw_compare (_:_) ([]) = GT raw_compare (_:x) (_:y) = raw_compare x y
instance Num LazyNatural where (LN x) + (LN y) = LN (x ++ y) (LN x) - (LN y) = LN (raw_minus x y) (LN x) * (LN y) = LN (concatMap (const x) y) negate _ = error "negate is not defined for LazyNatural" abs = id signum (LN []) = LN [] signum (LN _) = LN [()] fromInteger = LN . flip genericReplicate ()
raw_minus (_:a) (_:b) = raw_minus a b raw_minus (a) ([]) = a raw_minus _ _ = error "negative result from subtraction"
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

PS.
Prelude Data.List Data.Number.Natural> genericLength [1..] > (10 :: Natural)
True
On 9/24/07, Lennart Augustsson
Since natural numbers are trivial to implement (inefficiently) I took 15 minutes and added them to my numbers package in Hackage. http://hackage.haskell.org/cgi-bin/hackage-scripts/package/numbers-2007.9.24
-- Lennart
On 9/24/07, Andrew Coppin
wrote: Neil Mitchell wrote:
Hi
Pretty much, yes.
So I just need to write
newtype LazyNatural = LazyNatural [()]
or
data Nat = Zero | Succ Nat
it's your choice really.
I'm guessing there's going to be fairly minimal performance difference. (Or maybe there is. My way uses a few additional pointers. But it also allows me to elegantly recycle existing Prelude list functions, so...)
and then add some suitable instances. ;-)
Yes. Lots of them. Lots of instances and lots of methods.
Hey, the "length" function would then just be
ln_length :: [x] -> LazyNatural ln_length = LazyNatural . map (const ())
Ooo, that's hard.
Nope, its really easy. Its just quite a bit of work filling in all the instances. I bet you can't do it and upload the results to hackage within 24 hours :-)
*ALL* the instances? No.
A small handful of them? Sure. How about this...
module LazyNatural (LazyNatural ()) where
import Data.List
newtype LazyNatural = LN [()]
instance Show LazyNatural where show (LN x) = "LN " ++ show (length x)
instance Eq LazyNatural where (LN x) == (LN y) = x == y
instance Ord LazyNatural where compare (LN x) (LN y) = raw_compare x y
raw_compare ([]) (_:_) = LT raw_compare ([]) ([]) = EQ raw_compare (_:_) ([]) = GT raw_compare (_:x) (_:y) = raw_compare x y
instance Num LazyNatural where (LN x) + (LN y) = LN (x ++ y) (LN x) - (LN y) = LN (raw_minus x y) (LN x) * (LN y) = LN (concatMap (const x) y) negate _ = error "negate is not defined for LazyNatural" abs = id signum (LN []) = LN [] signum (LN _) = LN [()] fromInteger = LN . flip genericReplicate ()
raw_minus (_:a) (_:b) = raw_minus a b raw_minus (a) ([]) = a raw_minus _ _ = error "negative result from subtraction"
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 2007-09-24, Andrew Coppin
Neil Mitchell wrote:
Hi
lengthNat [1..] > 10
Couldn't be clearer, and can be made to work perfectly. If anyone does want to pick up the lazy naturals work, I can send over the code (or write it yourself - its not hard!)
Um... isn't a lazy natural just a list with no data, where the list length encodes a number?
That's one particularly simple representation, yes. "Lazy Unary". One can also construct other representations that may be more efficient in certain situations. -- Aaron Denney -><-

On Mon, 24 Sep 2007, Neil Mitchell wrote:
Hi
In this world, use "length (take 11 [1..]) > 10"...
not (null (drop 10 [1..])) is surely faster (not tested...)
Faster? There might be a few microseconds in it.
Clearer? Possibly... ;-)
lengthNat [1..] > 10
Couldn't be clearer, and can be made to work perfectly. If anyone does want to pick up the lazy naturals work, I can send over the code (or write it yourself - its not hard!)
E.g. http://darcs.haskell.org/htam/src/Number/PeanoNumber.hs

On Mon, 24 Sep 2007, Vimal wrote:
Hi all,
I was surprised to find out that the following piece of code:
length [1..] > 10
isnt lazily evaluated! I wouldnt expect this to be a bug, but in this case, shouldnt the computation end when the length function evaluation goes something like:
10 + length [11..]
?
If you used genericLength and had it returning this type with an appropriate Num instance: data Nat = Zero | Succ Nat then it'd be sufficiently lazy. As it is, an Int is something you either have or don't - you can't only evaluate "is it less than x" without having to fully evaluate it. -- flippa@flippac.org "The reason for this is simple yet profound. Equations of the form x = x are completely useless. All interesting equations are of the form x = y." -- John C. Baez

Wow, half an hour, about 7 replies :) I dont know which one to quote! Okay. So, why is GHC finding it difficult to conclude that length is always > 0? Suppose I define length like: length [] = 0 length (x:xs) = 1 + length xs Hmm, well, I think the fact that we, as humans, expecting GHC to infer length (any list) > 0 is pretty unfair :) What I had in mind was, when GHC was able to do so many things like pattern matching, data type inference, why not this! Nice! Now I dont know what to say :)

On Mon, 24 Sep 2007, Vimal wrote:
Wow, half an hour, about 7 replies :) I dont know which one to quote!
Okay. So, why is GHC finding it difficult to conclude that length is always > 0? Suppose I define length like:
length [] = 0 length (x:xs) = 1 + length xs
Hmm, well, I think the fact that we, as humans, expecting GHC to infer length (any list) > 0 is pretty unfair :)
What I had in mind was, when GHC was able to do so many things like pattern matching, data type inference, why not this!
Pattern matching is much easier than you might think. If you'll let me handwave at you a little, all pattern matches can be translated into a series of case statements where each pattern consists of either a variable or a constructor with variables to bind each of the constructor's parameters to. This isn't actually much more complicated than an old-fashioned switch statement! Type inference is a little more complicated, but largely revolves around a process similar to (but more powerful than) pattern-matching called unification. There's no magic involved, just sufficiently advanced technology. That part applies especially to lazy evaluation! Every time a pattern-match is done, evaluation proceeds far enough to find the constructor involved in order to select the right branch. Conceptually, the Int type looks like data Int = 1 | 2 | 3 | ... which means that an Int is either fully evaluated or completely unevaluated - if you try to evaluate "just enough to know it's > 0" then you'll still fully evaluate it. A good rule of thumb is to never expect (or perhaps, never require) GHC to do anything that requires it to prove something you're not extremely sure you've already written an explicit proof for in the code. -- flippa@flippac.org The task of the academic is not to scale great intellectual mountains, but to flatten them.

On Mon, 24 Sep 2007, Vimal wrote:
Hi all,
I was surprised to find out that the following piece of code:
length [1..] > 10
isnt lazily evaluated!
http://www.haskell.org/haskellwiki/Things_to_avoid#Don.27t_ask_for_the_lengt...

From the wiki: If you write it, you force Haskell to create all list nodes. ...
Alright. Now, lets look at the definition again:
length [] = 0 length (x:xs) = 1 + length xs
We see that the value of *x* isnt needed at all. So, why does GHC allocate so much memory creating all those *x*s? because, if we have: length [1..] = 1 + length [2...] = 1 + 1 + length [3...] This should go on, into an infinite loop. GHC doesnt need to create all nodes! The wiki also claims that *x* isnt evaluated. So, why allocate space for it when its not evaluated?

Vimal wrote:
From the wiki: If you write it, you force Haskell to create all list nodes. ...
Alright. Now, lets look at the definition again:
length [] = 0 length (x:xs) = 1 + length xs
We see that the value of *x* isnt needed at all. So, why does GHC allocate so much memory creating all those *x*s? because, if we have:
length [1..] = 1 + length [2...] = 1 + 1 + length [3...]
This should go on, into an infinite loop. GHC doesnt need to create all nodes! The wiki also claims that *x* isnt evaluated. So, why allocate space for it when its not evaluated?
*x* isn't allocated. What is allocated is the list cell, that is, the ":". The ":" is conceptually a two-cell, with room for a pointer to the 'x' and a pointer to the 'xs'. The 'x' itself isn't evaluated, so that pointer remains as a pointer to some code a.k.a. an unevaluated thunk. Jules

length [1..] > 10
isnt lazily evaluated! I wouldnt expect this to be a bug, but in this case, shouldnt the computation end when the length function evaluation goes something like:
No. You want GHC to deduce that length would only increase in future. This property is relatively complex and GHC isn't so smart. Moreover, this property isn't even true: for example, if numeric overflow occurs. More importantly, this property doesn't make sense: length [1..] is (_|_) - undefined value, so this inequality is also meaningless.
participants (13)
-
Aaron Denney
-
Andrew Coppin
-
apfelmus
-
Henning Thielemann
-
Ian Lynagh
-
Jonathan Cast
-
Jules Bean
-
Lennart Augustsson
-
Miguel Mitrofanov
-
Neil Mitchell
-
Philippa Cowderoy
-
Seth Gordon
-
Vimal