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

Don Stewart dons at galois.com
Fri Dec 21 13:29:59 EST 2007


derek.a.elkins:
> On Fri, 2007-12-21 at 09:56 -0800, David Benbennick wrote:
> > On Dec 21, 2007 9:51 AM, Justin Bailey <jgbailey at gmail.com> wrote:
> > > I think its [1..] which is building up the unevaluated thunk. Using
> > > this definition of dropTest does not blow the stack:
> > 
> > It also works if you do [(1::Int) ..] !! n, but not with [(1::Integer) ..] !! n
> > 
> > Sounds like GHC is being smart about strictness for Ints, but doesn't
> > know that Integer is equally strict.  If that's right, it's a bug in
> > GHC.
> 
> It is a bug in GHC. From
> http://darcs.haskell.org/packages/base/GHC/Enum.lhs
> 
>     enumFrom (I# x) = eftInt x maxInt#
>         where I# maxInt# = maxInt
> 	-- Blarg: technically I guess enumFrom isn't strict!
> 
> ...
> 
> eftInt x y | x ># y    = []
> 	   | otherwise = go x
> 	       where
> 		 go x = I# x : if x ==# y then [] else go (x +# 1#)
> 

As usual, this is an issue with the irregular numeric-operation
strictness applied to Integer.

Consider this Integer enumFrom:

    main = print x
        where x = head (drop 1000000 (enumFrom' 1))

    ------------------------------------------------------------------------

    enumFrom' :: Integer -> [Integer]
    enumFrom' x = enumDeltaInteger  x 1

    enumDeltaInteger :: Integer -> Integer -> [Integer]
    enumDeltaInteger x d = x `seq` x : enumDeltaInteger (x+d) d

Is fine. The Int instance is already strict like this.

I'll file a patch. I hate these slightly too lazy issues
with Integer, that aren't present with Int.

The atomic strictness of Integer is only irregularly
applied through the base libraries. For example,
in Data.List, this was considered acceptable:

    maximum                 :: (Ord a) => [a] -> a
    maximum []              =  errorEmptyList "maximum"
    maximum xs              =  foldl1 max xs
       
    {-# RULES              
      "maximumInt"     maximum = (strictMaximum :: [Int]     -> Int);
      "maximumInteger" maximum = (strictMaximum :: [Integer] -> Integer)
     #-}

Really, if we let Int be strict on (+) and (*)-style operations,
and Integer sometimes strict on those, we should just declare
that these atomic numeric types (and Word, Word8,..) 
should be strict on (+) and so on. 

-- Don


More information about the Haskell-Cafe mailing list