It would also make sense to export the already defined strictGenericLength.2. RULES replace lazy genericLength with strictGenericLength for some Int-like types, but not for all. It is at least inconsistent.1. There is already strictGenericLength but it is simply not exportedI see. This point wasn't obvious to me before. This seems like a bug though, given the definitions given in Data.List for genericLength. It goes:We can see that:
-- | The 'genericLength' function is an overloaded version of 'length'. In
-- particular, instead of returning an 'Int', it returns any type which is
-- an instance of 'Num'. It is, however, less efficient than 'length'.
genericLength :: (Num i) => [a] -> i
{-# NOINLINE [1] genericLength #-}
genericLength [] = 0
genericLength (_:l) = 1 + genericLength l
{-# RULES
"genericLengthInt" genericLength = (strictGenericLength :: [a] -> Int);
"genericLengthInteger" genericLength = (strictGenericLength :: [a] -> Integer);
#-}
strictGenericLength :: (Num i) => [b] -> i
strictGenericLength l = gl l 0
where
gl [] a = a
gl (_:xs) a = let a' = a + 1 in a' `seq` gl xs a'
Given that genericLength xs == strictGenericLength xs for strict Num types, unless the former diverges, it would make sense to expand the RULES to more types. I wouldn't make it default for all types though...
On Sun, Aug 3, 2014 at 8:44 AM, David Feuer <david.feuer@gmail.com> wrote:
Forcing the result does not even begin to fix anything. The problem is
that calculating the genericLength of a long list using typical number
types will cause a stack overflow. For example, typing
genericLength $ [1..(20000000::Int)] :: Int64
will lead to a stack overflow.
On Sun, Aug 3, 2014 at 2:05 AM, Krzysztof Skrzętnicki <gtener@gmail.com> wrote:
> Personally I dont see any good reason for doing this change. It will likely
> break peoples code and force us to increase maintenance costs.
>
> *If* you want strict output you can always force the result.
>
> There is also an option of providing new function with semantics you
> propose: genericLength'
>
> Krzysztof
>
> 03-08-2014 04:03, "David Feuer" <david.feuer@gmail.com> napisał(a):
>>
>> As far as I can tell, Haskell 2010 does not specify anything about the
>> strictness of genericLength. Currently, it is maximally lazy. This is good,
>> I suppose, if you want to support lists that are very long and are using
>> floating point or some similarly broken Num instance.
>>
>> But this is not something many (any?) people have any interest in doing.
>> As a result, the genericLength function is on a nice little list I found of
>> Haskell functions one should never use. I therefore propose that we change
>> it to something nice and simple, like
>>
>> genericLength = foldl' 0 (\x _ -> x + 1)
>>
>> Admittedly, this may not be optimal for Int8, Int16, Word8, or Word16, so
>> we may need to use rules to rewrite these four to narrow the result of
>> length (or some such).
>>
>>
>> _______________________________________________
>> Libraries mailing list
>> Libraries@haskell.org
>> http://www.haskell.org/mailman/listinfo/libraries
>>
>