Shouldn't this loop indefinitely => take (last [0..]) [0..]

Hi all, If you compile and run this: main = do putStrLn $ show $ take (last [0..]) [0..] or simply run: take (last [0..]) [0..] in ghci, it first hang for about one minute and then starts to generate an infinite list. I was expecting "last [0..]" to never produce a value and the "take" function to never take from the [0..] list. I found that line of code in a friend's "Skype Message", lauched it in ghci and forgot it. When I came back to my ghci window a couple minutes later it was listing numbers, which was really unexpected. If I just run "last [0..]" it doesn't return a value and my computer will quickly start to paginate to death. Am I missing something? Some laziness magic? Rewrite rules? Thanks, Olivier.

olivier.boudry:
Hi all,
If you compile and run this:
main = do putStrLn $ show $ take (last [0..]) [0..]
or simply run:
take (last [0..]) [0..]
in ghci, it first hang for about one minute and then starts to generate an infinite list. I was expecting "last [0..]" to never produce a value and the "take" function to never take from the [0..] list.
I can't reproduce this with ghc 6.8.2 on a 64 bit arch, both just sit running in constant space, at full cpu. Are you perhaps constraining it to an Int type somewhere (so that [0..] terminates at maxBound)? I.e. this kind of thing: Prelude> last [1..] :: Int8 127 but for maxBound on Int32? -- Don

Olivier Boudry wrote:
main = do putStrLn $ show $ take (last [0..]) [0..]
or simply run:
take (last [0..]) [0..]
in ghci, it first hang for about one minute and then starts to generate an infinite list.
It's not an infinite list. It's a list of length maxBound::Int, as required by the fact that take's first argument is an Int. The second argument is probably defaulting to Integer.

On Thu, Apr 3, 2008 at 10:35 PM, Bryan O'Sullivan
It's not an infinite list. It's a list of length maxBound::Int, as required by the fact that take's first argument is an Int. The second argument is probably defaulting to Integer.
Right! The first arg of "take" makes the first list into a int list. I did not wait long enough to see the end of the list and I'm so used to represent infinite lists with [0..] that I didn't think it could be limited. Thanks for the explanation! Olivier.

Bryan O'Sullivan wrote:
It's not an infinite list. It's a list of length maxBound::Int, as required by the fact that take's first argument is an Int. The second argument is probably defaulting to Integer.
Which, incidentally, also explains why Don couldn't reproduce it on a 64- bit system. There, instead of hanging for about a minute before printing out the list, it would hang for about 4 billion minutes. -- Chris Smith

cdsmith:
Bryan O'Sullivan wrote:
It's not an infinite list. It's a list of length maxBound::Int, as required by the fact that take's first argument is an Int. The second argument is probably defaulting to Integer.
Which, incidentally, also explains why Don couldn't reproduce it on a 64- bit system. There, instead of hanging for about a minute before printing out the list, it would hang for about 4 billion minutes.
It's also interesting how our 32 bit machines are fast enough now to make Int indices noticeably problematic. And thankfully, 64 bit machines are common enough now that the 32 bit Int issues are less of an issue. length, take, drop and index working on machine-sized Ints by default are really a bit of a wart, aren't they? -- Don

Don Stewart wrote:
Which, incidentally, also explains why Don couldn't reproduce it on a 64- bit system. There, instead of hanging for about a minute before printing out the list, it would hang for about 4 billion minutes.
A billion minutes here, a billion minutes there, and pretty soon you're talking about enough time to brew a nice cup of tea.
It's also interesting how our 32 bit machines are fast enough now to make Int indices noticeably problematic. And thankfully, 64 bit machines are common enough now that the 32 bit Int issues are less of an issue.
Alas, we've swapped that for a big performance slowdown due to the doubled size of pointers, courtesy of STG's addiction thereto.

Hi
length, take, drop and index working on machine-sized Ints by default are really a bit of a wart, aren't they?
Yes. Also, having strict Int's by default is a bit ugly, in an otherwise lazy-by-default language. It's a place where Haskell decided to remove mathematical elegance for pragmatic speed... (Not that it isn't a worthwhile trade off, but it is still loosing something to gain something else) Thanks Neil

On Fri, Apr 04, 2008 at 12:34:54PM +0100, Neil Mitchell wrote:
length, take, drop and index working on machine-sized Ints by default are really a bit of a wart, aren't they?
Yes. Also, having strict Int's by default is a bit ugly, in an otherwise lazy-by-default language. It's a place where Haskell decided to remove mathematical elegance for pragmatic speed...
(Not that it isn't a worthwhile trade off, but it is still loosing something to gain something else)
Personally, I like Ints. -- David Roundy Department of Physics Oregon State University

Also, having strict Int's by default is a bit ugly, in an otherwise lazy-by-default language.
I meant: (\x (y :: Int) -> x + 1) 1 (1/0 :: Int) <=> _|_ ?
Division by 0 is still an error. What I mean is: length xs == length ys Where length xs = 1 and ys = 1000. This takes 1000 steps to tell the Int's aren't equal, since we don't have proper lazy naturals. If we did, it would take 2 steps. Read this: http://citeseer.ist.psu.edu/45669.html - it argues the point I am trying to make, but much better. Thanks Neil

2008/4/4, Neil Mitchell
Also, having strict Int's by default is a bit ugly, in an otherwise lazy-by-default language.
I meant: (\x (y :: Int) -> x + 1) 1 (1/0 :: Int) <=> _|_ ?
Division by 0 is still an error. What I mean is:
Yes, but this particular one need not be performed. Will it be?
length xs == length ys
Where length xs = 1 and ys = 1000. This takes 1000 steps to tell the Int's aren't equal, since we don't have proper lazy naturals. If we did, it would take 2 steps.
Err, really? I mean, could we calculate this equality without reducing length ys to weak head normal form (and then to plain normal form)? What do you mean by "proper Lazy naturals"? Peano ones? Loup

Hi
I meant: (\x (y :: Int) -> x + 1) 1 (1/0 :: Int) <=> _|_ ?
Division by 0 is still an error. What I mean is:
Yes, but this particular one need not be performed. Will it be?
Oh, sorry, I misread that. Even with current Haskell's Int's that is lazy enough to work, and won't crash.
Where length xs = 1 and ys = 1000. This takes 1000 steps to tell the Int's aren't equal, since we don't have proper lazy naturals. If we did, it would take 2 steps.
Err, really? I mean, could we calculate this equality without reducing length ys to weak head normal form (and then to plain normal form)?
Not without lazy naturals, or some other way of returning the result of length lazily.
What do you mean by "proper Lazy naturals"? Peano ones?
Yes Thanks Neil

On 2008-04-04, Neil Mitchell
What do you mean by "proper Lazy naturals"? Peano ones?
Yes
Not _strictly_ necessary. And I'd definitely like some suitable typeclass put in place. This represents positive arithmetic with a list homomorphism that forgets the elements and remembers only length. It's pretty much exactly equivalent to the function "map (const ())". This essentially unary representation isn't the only way to way to manipulate numbers by structure. You can do the same thing with many other data structures, such as trees, heaps, etc. In this case, yes, lists are the cleanest, being the underlying structure we're getting information about. (Aside: might as well just define the "less than" operation directly on the lists in this case -- or for any other arithmetic operation where we're not getting a list back. When we are, we usually can too, but it's a bit more fraught with concerns over whether that's really what we want -- we're throwing away information by replacing all elements with (), and perhaps we should have the typechecker warn us.[1]) But we can pull this trick with any container class. + corresponds to some merger or catenation, * to some cross product, zero to an empty data structure, and so forth. If you do this with Binomial heaps, out pop binary numbers. If you do this to certain types of efficient queues, "skew binary numbers" which support efficient increment and decrument pop out. This isn't surprising, as they were built using skew binary number for precisely this property. Those that haven't should take a look at Okasaki's _Purely Functional Data Structures_, particularly chapter 9: "Numerical Structures". http://books.google.com/books?id=SxPzSTcTalAC [1]: smallerThan :: [a] -> [b] -> Bool smallerThan [] [] = False smallerThan [] _ = True smallerThan _ [] = False smallerThan (_:as) (_:bs) = smallerThan as bs noGreaterThan :: [a] -> [b] -> Bool noGreaterThan [] _ = True noGreaterThan _ [] = False noGreaterThan (_:as) (_:bs) = noGreaterThan as bs are perfectly reasonable, but it's less clear that nattify = map const () (+) xs ys = (++) (nattify xs) (nattify ys) would be good universal definitions. -- Aaron Denney -><-

On Apr 4, 2008, at 11:31 AM, Loup Vaillant wrote:
I mean, could we calculate this equality without reducing length ys to weak head normal form (and then to plain normal form)?
Yes. Suppose equality over Nat is defined something like: Z == Z = True S x == S y = x == y x == y = False And also suppose the length function actually returns a Nat instead of an Int. Now the expression reduces as: length xs == length ys S (length xs') == S (length ys') Z == S (length ys'') False That would not be possible without lazy Nats. - Jake

On Fri, Apr 4, 2008 at 7:14 PM, Jake Mcarthur
On Apr 4, 2008, at 11:31 AM, Loup Vaillant wrote:
I mean, could we calculate this equality without reducing length ys to weak head normal form (and then to plain normal form)?
Yes. Suppose equality over Nat is defined something like:
Z == Z = True S x == S y = x == y x == y = False
And also suppose the length function actually returns a Nat instead of an Int. Now the expression reduces as:
length xs == length ys S (length xs') == S (length ys') Z == S (length ys'') False
That would not be possible without lazy Nats.
One thing to notice is that with lazy Nats this code: length [] == length [1..] would terminate, while on 64 bit platform it is "almost bottom" :-) Theoretically it is even worse: genericLength [] == genericLength [1..] :: Integer will never terminate and eat infinite amount of memory along the way, while genericLength [] == genericLength [1..] :: Nat will do just fine. We can however write function like this: eqLengths [] [] = True eqLengths (x:xs) (y:ys) = eqLengths ys xs eqLengths _ _ = False which looks just fine for me. Christopher Skrzętnicki

Hi
We can however write function like this:
eqLengths [] [] = True eqLengths (x:xs) (y:ys) = eqLengths ys xs eqLengths _ _ = False
which looks just fine for me.
I have this defined function. I also have lenEq1, lenGt1, and a few other variants. It works, but it just doesn't feel elegant. Note: In case anyone gets the wrong impression, I am not suggesting lazy naturals be the standard numeric type in Haskell, just that by not going that way we have paid a cost in terms of elegance. Thanks Neil

ndmitchell:
Hi
We can however write function like this:
eqLengths [] [] = True eqLengths (x:xs) (y:ys) = eqLengths ys xs eqLengths _ _ = False
which looks just fine for me.
I have this defined function. I also have lenEq1, lenGt1, and a few other variants. It works, but it just doesn't feel elegant.
Note: In case anyone gets the wrong impression, I am not suggesting lazy naturals be the standard numeric type in Haskell, just that by not going that way we have paid a cost in terms of elegance.
I'd be happy if we had an (unbounded) Nat type in the first place... -- Don

On Fri, Apr 4, 2008 at 5:45 PM, Don Stewart
ndmitchell:
Note: In case anyone gets the wrong impression, I am not suggesting lazy naturals be the standard numeric type in Haskell, just that by not going that way we have paid a cost in terms of elegance.
I'd be happy if we had an (unbounded) Nat type in the first place...
The problem with Nat is that we can't comfortably make it an instance
of Num. (Well, that's arguably a problem with Num.)
--
Dave Menendez

Hi, Am Freitag, den 04.04.2008, 22:44 +0100 schrieb Neil Mitchell:
Hi
We can however write function like this:
eqLengths [] [] = True eqLengths (x:xs) (y:ys) = eqLengths ys xs eqLengths _ _ = False
which looks just fine for me.
I have this defined function. I also have lenEq1, lenGt1, and a few other variants. It works, but it just doesn't feel elegant.
Note: In case anyone gets the wrong impression, I am not suggesting lazy naturals be the standard numeric type in Haskell, just that by not going that way we have paid a cost in terms of elegance.
How about something like this:
data Length a = Length [a]
instance Ord (Length a) where > compare (Length []) (Length []) = EQ > compare (Length []) (Length (_:_)) = LT > compare (Length (_:_)) (Length []) = GT > compare (Length (_:xs)) (Length (_:ys)) = compare (Length xs) (Length ys)
> instance Eq (Length a) where > l1 == l2 = compare l1 l2 == EQ then you can do at least lazy lengths comparisons relatively nice by writing
if Length list1 >= Length list2 then print "list1" else print "list2"
(just a quick idea) Greetings Joachim -- Joachim Breitner e-Mail: mail@joachim-breitner.de Homepage: http://www.joachim-breitner.de ICQ#: 74513189 Jabber-ID: nomeata@joachim-breitner.de

On Fri, Apr 04, 2008 at 04:46:22PM +0100, Neil Mitchell wrote:
Where length xs = 1 and ys = 1000. This takes 1000 steps to tell the Int's aren't equal, since we don't have proper lazy naturals. If we did, it would take 2 steps.
Read this: http://citeseer.ist.psu.edu/45669.html - it argues the point I am trying to make, but much better.
I implemented this efficient lazy natural class once upon a time. it even has things like lazy multiplication: -- Copyright (c) 2007 John Meacham (john at repetae dot net) -- -- Permission is hereby granted, free of charge, to any person obtaining a -- copy of this software and associated documentation files (the -- "Software"), to deal in the Software without restriction, including -- without limitation the rights to use, copy, modify, merge, publish, -- distribute, sublicense, and/or sell copies of the Software, and to -- permit persons to whom the Software is furnished to do so, subject to -- the following conditions: -- -- The above copyright notice and this permission notice shall be included -- in all copies or substantial portions of the Software. -- -- THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS -- OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -- MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. -- IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY -- CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, -- TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE -- SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -- efficient lazy naturals module Util.LazyNum where -- Nat data type is eqivalant to a type restricted lazy list that is strict in -- its elements. -- -- Invarients: (Sum x _) => x > 0 -- in particular (Sum 0 _) is _not_ valid and must not occur. data Nat = Sum !Integer Nat | Zero deriving(Show) instance Eq Nat where Zero == Zero = True Zero == _ = False _ == Zero = False Sum x nx == Sum y ny = case compare x y of EQ -> nx == ny LT -> nx == Sum (y - x) ny GT -> Sum (x - y) nx == ny instance Ord Nat where Zero <= _ = True _ <= Zero = False Sum x nx <= Sum y ny = case compare x y of EQ -> nx <= ny LT -> nx <= Sum (y - x) ny GT -> Sum (x - y) nx <= ny Zero `compare` Zero = EQ Zero `compare` _ = LT _ `compare` Zero = GT Sum x nx `compare` Sum y ny = case compare x y of EQ -> nx `compare` ny LT -> nx `compare` Sum (y - x) ny GT -> Sum (x - y) nx `compare` ny x < y = not (x >= y) x >= y = y <= x x > y = y < x instance Num Nat where Zero + y = y Sum x n1 + y = Sum x (y + n1) --x + Zero = x --Sum x n1 + Sum y n2 = Sum (x + y) (n1 + n2) Zero - _ = zero x - Zero = x Sum x n1 - Sum y n2 = case compare x y of GT -> Sum (x - y) n1 - n2 EQ -> n1 - n2 LT -> n1 - Sum (y - x) n2 negate _ = zero abs x = x signum Zero = zero signum _ = one fromInteger x = if x <= 0 then zero else Sum x Zero Zero * _ = Zero _ * Zero = Zero (Sum x nx) * (Sum y ny) = Sum (x*y) ((f x ny) + (nx * (fint y + ny))) where f y Zero = Zero f y (Sum x n) = Sum (x*y) (f y n) instance Real Nat where toRational n = toRational (toInteger n) instance Enum Nat where succ x = Sum 1 x pred Zero = Zero pred (Sum n x) = if n == 1 then x else Sum (n - 1) x enumFrom x = x:[ Sum n x | n <- [1 ..]] enumFromThen x y = x:y:f (y + z) where z = y - x f x = x:f (x + z) toEnum = fromIntegral fromEnum = fromIntegral -- d > 0 doDiv :: Nat -> Integer -> Nat doDiv n d = f 0 n where f _ Zero = 0 f cm (Sum x nx) = sum d (f m nx) where (d,m) = (x + cm) `quotRem` d sum 0 x = x sum n x = Sum n x doMod :: Nat -> Integer -> Nat doMod n d = f 0 n where f 0 Zero = Zero f r Zero = fint r f r (Sum x nx) = f ((r + x) `rem` d) nx instance Integral Nat where _ `div` Zero = infinity n1 `div` n2 | n1 < n2 = 0 | otherwise = doDiv n1 (toInteger n2) n1 `mod` Zero = n1 -- XXX n1 `mod` n2 | n1 < n2 = n1 | otherwise = doMod n1 (toInteger n2) n `divMod` Zero = (infinity,n) n `divMod` d | n < d = (0,n) | otherwise = let d' = toInteger d in (doDiv n d',doMod n d') quotRem = divMod quot = div rem = mod toInteger n = f 0 n where f n _ | n `seq` False = undefined f n Zero = n f n (Sum x n1) = let nx = n + x in nx `seq` f nx n1 -- convert to integer unless it is too big, in which case Nothing is returned natToInteger :: Integer -> Nat -> Maybe Integer natToInteger limit n = f 0 n where f n _ | n > limit = Nothing f n Zero = Just n f n (Sum x n1) = let nx = n + x in nx `seq` f nx n1 natShow :: Nat -> String natShow n = case natToInteger bigNum n of Nothing -> "(too big)" Just v -> show v natFoldr :: (Integer -> b -> b) -> b -> Nat -> b natFoldr cons nil n = f n where f Zero = nil f (Sum x r) = cons x (f r) -- some utility routines natEven :: Nat -> Bool natEven n = f True n where f r Zero = r f r (Sum x n) = if even x then f r n else f (not r) n natOdd :: Nat -> Bool natOdd n = not (natEven n) {-# RULES "even/natEven" even = natEven #-} {-# RULES "odd/natOdd" odd = natOdd #-} zero = Zero one = Sum 1 Zero infinity = Sum bigNum infinity bigNum = 100000000000 fint x = Sum x Zero -- random testing stuff for ghci ti op x y = (toInteger $ x `op` y, toInteger x `op` toInteger y) depth n | n <= 0 = error "depth exceeded" | otherwise = Sum n (depth $ n - 1) depth' n | n <= 0 = Zero | otherwise = Sum n (depth' $ n - 1)

On Sun, Apr 6, 2008 at 11:12 AM, John Meacham
I implemented this efficient lazy natural class once upon a time. it even has things like lazy multiplication: [...] instance Num Nat where Zero + y = y Sum x n1 + y = Sum x (y + n1) --x + Zero = x --Sum x n1 + Sum y n2 = Sum (x + y) (n1 + n2) [...]
May I ask you why the last line above was commented out? Thanks! -- Felipe.

On Sun, Apr 06, 2008 at 11:30:20AM -0300, Felipe Lessa wrote:
On Sun, Apr 6, 2008 at 11:12 AM, John Meacham
wrote: I implemented this efficient lazy natural class once upon a time. it even has things like lazy multiplication: [...] instance Num Nat where Zero + y = y Sum x n1 + y = Sum x (y + n1) --x + Zero = x --Sum x n1 + Sum y n2 = Sum (x + y) (n1 + n2) [...]
May I ask you why the last line above was commented out?
Notice it flips the order of the arguments with each iteration. This allows it to avoid space leaks in some cases, for instance if you have infinity + (space wasting thunk), the space wasting thunk will never be deallocated even though it isn't used. It also means that the strictness properties are more symmetric than they would be otherwise as people expect of (+). John -- John Meacham - ⑆repetae.net⑆john⑈

On Sun, Apr 06, 2008 at 07:12:24AM -0700, John Meacham wrote:
On Fri, Apr 04, 2008 at 04:46:22PM +0100, Neil Mitchell wrote:
Where length xs = 1 and ys = 1000. This takes 1000 steps to tell the Int's aren't equal, since we don't have proper lazy naturals. If we did, it would take 2 steps.
Read this: http://citeseer.ist.psu.edu/45669.html - it argues the point I am trying to make, but much better.
I implemented this efficient lazy natural class once upon a time. it even has things like lazy multiplication:
I wonder about the efficiency of this implementation. It seems that for most uses the result is that the size of a Nat n is O(n), which means that in practice you probably can't use it for large numbers. e.g. it seems like last [1..n :: Nat] should use O(n) space, where last [1..n :: Integer] should take O(1) space. And I can't help but imagine that there must be scenarios where the memory use goes from O(N) to O(N^2), which seems pretty drastic. I imagine this is an inherent cost in the use of lazy numbers? Which is probably why they're not a reasonable default, since poor space use is often far more devastating then simple inefficiency. And of course it is also not always more efficient than strict numbers. -- David Roundy Department of Physics Oregon State University

On Mon, Apr 07, 2008 at 04:45:31AM -0700, David Roundy wrote:
I wonder about the efficiency of this implementation. It seems that for most uses the result is that the size of a Nat n is O(n), which means that in practice you probably can't use it for large numbers.
e.g. it seems like
last [1..n :: Nat]
should use O(n) space, where
last [1..n :: Integer]
should take O(1) space. And I can't help but imagine that there must be scenarios where the memory use goes from O(N) to O(N^2), which seems pretty drastic. I imagine this is an inherent cost in the use of lazy numbers? Which is probably why they're not a reasonable default, since poor space use is often far more devastating then simple inefficiency. And of course it is also not always more efficient than strict numbers.
Oh, yes. I certainly wouldn't recommend them as some sort of default, they were sort of a fun project and might come in handy some day. By efficient, I meant more efficient than the standard lazy number formulation of data Num = Succ Num | Zero not more efficient than strict types, which it very much is not. :) John -- John Meacham - ⑆repetae.net⑆john⑈

On Mon, Apr 07, 2008 at 04:52:51AM -0700, John Meacham wrote:
On Mon, Apr 07, 2008 at 04:45:31AM -0700, David Roundy wrote:
I wonder about the efficiency of this implementation. It seems that for most uses the result is that the size of a Nat n is O(n), which means that in practice you probably can't use it for large numbers.
e.g. it seems like
last [1..n :: Nat]
should use O(n) space, where
last [1..n :: Integer]
should take O(1) space. And I can't help but imagine that there must be scenarios where the memory use goes from O(N) to O(N^2), which seems pretty drastic. I imagine this is an inherent cost in the use of lazy numbers? Which is probably why they're not a reasonable default, since poor space use is often far more devastating then simple inefficiency. And of course it is also not always more efficient than strict numbers.
Oh, yes. I certainly wouldn't recommend them as some sort of default, they were sort of a fun project and might come in handy some day.
By efficient, I meant more efficient than the standard lazy number formulation of
data Num = Succ Num | Zero
not more efficient than strict types, which it very much is not. :)
Ah, that makes sense. And yes, they're definitely more efficient than that. :) The trouble (I suppose) is that for the common case in which lazy naturals are called for, which is situations where you compute (1+1+1+1...+1+0), you can't be more space-efficient than the standard lazy numbers without losing some of the laziness. Or at least, I can't see how you could do so. -- David Roundy Department of Physics Oregon State University

"Neil Mitchell"
length, take, drop and index working on machine-sized Ints by default are really a bit of a wart, aren't they?
Yes. Also, having strict Int's by default is a bit ugly, [..] (Not that it isn't a worthwhile trade off, but it is still loosing something to gain something else)
Presumably you refer to the latter point - Int strictness - here? I don't think "optimizing" list operations (take, length etc) to Int buys you much performance - traversing the list is going to be far more expensive. (Or so I believe - anybody care to benchmark it?) Unfortunately, the "genericLenght" name is about as clumsy syntactically as Int is semantically, so it's about an even trade-off :-) -k -- If I haven't seen further, it is by standing in the footprints of giants

Don Stewart wrote:
length, take, drop and index working on machine-sized Ints by default are really a bit of a wart, aren't they?
Definitely. See http://cdsmith.wordpress.com/2007/07/05/find-the-bug/ for my account of this problem when I ran into it last summer. In particular, the combination of these functions using Int and too much reliance on type inference can be fatal. Overflow is possible in most languages; but in Haskell you get used to not dealing with it by assuming that numeric types default to Integer. Then, in some remote corner somewhere, just one use of 'length' may result in an inferred type of Int for half the numbers in the program. The problem is likely to be in a piece of code completely unrelated to where the symptoms occur. -- Chris Smith

Hello, Sadly, as others have pointed out, [0..] is not an infinite list in that context, so nothing too exciting is happening. You can making something almost exciting happen if you define some Peano numbers:
data P = Z | S P
inf = S Z
[bunch of class instances skipped]
main = print $ genericTake (inf :: P) [0..]
you still can not get output from:
main = print $ genericTake (last [0..] :: P) [0..] -- wont produce output
because the compiler won't recognize that (last [0..]) is equalivent to 'inf'. You could add a rewrite rule which turned: last [0..] -> inf however, I think that would be a bit bogus, because, in Haskell, the value returned isn't really the same: last [0..] === _|_ inf = S S S S S S S S S ... I think this is a bit of an interesting case to consider. As proponents of declarative programming, we often talk about how declarative languages free you from having to tell the machine how to do everything (as compared to imperative languages). So, I think it is interesting to note that even in declarative languages, there is a still a degree of describing how to do a computation. I wonder if there are any dependently types languages where: last [0..] === inf Assuming that statement is true, of course. It seems like it ought to be provable, but my proof skills are weak. (I suppose in a strict language, you might consider them to both be _|_, but that is the less exciting case). j. ps. I have attached a working demo. I did not finish all the instance declarations, only enough to run the example. import Data.List main = do -- print $ genericTake (last [0..] :: P) [0..] -- wont produce output print $ genericTake (inf :: P) [0..] -- will produce output inf :: P inf = S inf data P = Z | S P instance Show P where show Z = "Z" show (S n) = "S " ++ show n instance Enum P where toEnum 0 = Z toEnum n = S (toEnum (n - 1)) fromEnum Z = 0 fromEnum (S p) = 1 + (fromEnum p) instance Ord P where (S x) > Z = True Z > Z = False (S x) > (S y) = x > y Z <= _ = True _ <= Z = False (S x) <= (S y) = x <= y instance Eq P where Z == Z = True (S x) == Z = False x == (S y) = False (S x) == (S y) = x == y instance Num P where Z + y = Z (S x) + y = S (x + y) x - Z = x Z - _ = error "negative numbers not supported." (S x) - (S y) = x - y fromInteger n | n < 0 = error "negative numbers not supported." fromInteger 0 = Z fromInteger n = S (fromInteger (n - 1)) instance Real P instance Integral P where At Thu, 3 Apr 2008 22:27:17 +0100, Olivier Boudry wrote:
[1
] [1.1 ] Hi all, If you compile and run this:
main = do putStrLn $ show $ take (last [0..]) [0..]
or simply run:
take (last [0..]) [0..]
in ghci, it first hang for about one minute and then starts to generate an infinite list. I was expecting "last [0..]" to never produce a value and the "take" function to never take from the [0..] list.
I found that line of code in a friend's "Skype Message", lauched it in ghci and forgot it. When I came back to my ghci window a couple minutes later it was listing numbers, which was really unexpected.
If I just run "last [0..]" it doesn't return a value and my computer will quickly start to paginate to death. Am I missing something? Some laziness magic? Rewrite rules?
Thanks,
Olivier. [1.2
] [2
] _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (16)
-
Aaron Denney
-
Bryan O'Sullivan
-
Chris Smith
-
David Menendez
-
David Roundy
-
Don Stewart
-
Felipe Lessa
-
Jake Mcarthur
-
Jeremy Shaw
-
Joachim Breitner
-
John Meacham
-
Ketil Malde
-
Krzysztof Skrzętnicki
-
Loup Vaillant
-
Neil Mitchell
-
Olivier Boudry