[Haskell-cafe] Why does this blow the stack?

Thomas Hartman tphyahoo at gmail.com
Wed Dec 26 16:15:51 EST 2007


The (extremely enlightening) discussion so far has focused on the
inconsistent (arguably buggy) behavior of [a,b..c] enumeration sugar.

I think it's worth pointing out that the code could also be made to
run by making the drop function strict. I got to thinking, in a
"strictness" debugging scenario like this, it seems like you can get
the behavior you want by making things strict at various levels. You
can make the inner level (enumeration sugar) stricter, or you can
leave the enumeration stuff lazy and make the drop stricter. Maybe I
didn't express that very well, so here's code:

(I would argue that this discussion could be the basis of a
"strictness kata" exercise, following up from a cafe post I made a
while ago.)

{-# LANGUAGE BangPatterns #-}
import Data.List
import Testing
import Test.QuickCheck
import Test.QuickCheck.Batch

tDrop = ( head . drop n ) ( edi1 1 2 )
tStrictDrop = ( head . strictDrop n ) ( edi1 1 2 )
n = 10^6

--edi: enum delta integer
-- stack overflow on 10^6 el list if use drop
-- ok with strictDrop
edi1 start next = start : edi1 next (next + delta)
  where delta = next - start

-- ok (no overflow) for drop, of course also okay for strictDrop
edi2 !start next = start : edi2 next (next + delta)
  where delta = next - start


ediWithMax start next bound = takeWhile p $ edi start next
  where p i | delta > 0 = i <= bound
            | delta < 0 = i >= bound
            | otherwise = i <= bound
        delta = next - start
        edi = edi1

strictDrop _ [] = []
strictDrop n l | n <= 0 = l
strictDrop n (!x:xs) | n>0 = strictDrop (n-1) xs

pStrictDropSameAsDrop n xs = drop n xs == strictDrop n xs
  where types = (n::Int,xs::[Integer])


pEdi1 start next max =
    abs(next-start) > 0 ==> -- otherwise hits bottom because of eg [0,0..0]
    ediWithMax start next max == [start,next..max]
  where types = (start :: Integer, next :: Integer, max :: Integer)

pEdi2 start next max = ( take 1000 $ ediWithMax start next max ) == (
take 1000 $ [start,next..max] )
  where types = (start :: Integer, next :: Integer, max :: Integer)


t2 = runTests "edi" testOptions
     [run pEdi1,
      run pEdi2,
      run pStrictDropSameAsDrop]
  where testOptions = TestOptions
                { no_of_tests = 100		-- number of tests to run
                , length_of_tests = 1	-- 1 second max per check
                                               -- where a check == n tests
                , debug_tests = False	-- True => debugging info
                }





2007/12/21, Justin Bailey <jgbailey at gmail.com>:
> Given this function:
>
>   dropTest n = head . drop n $ [1..]
>
> I get a stack overflow when n is greater than ~ 550,000 . Is that
> inevitable behavior for large n? Is there a better way to do it?
>
> Justin
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list