Proposal (breaking change, but probably not one that will break any real code): strictify genericLength
Bertram Felgenhauer
bertram.felgenhauer at googlemail.com
Sun Aug 3 02:29:26 UTC 2014
David Feuer wrote:
> 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.
The motivating example I've seen is using lazy natural numbers,
data Nat = Z | S Nat
instance Num Nat where
...
Z + y = y
S x + y = S (x + y)
instance Ord Nat where
compare Z Z = EQ
compare Z _ = LT
compare _ Z = GT
compare (S x) (S y) = compare x y
and then
foo xs = genericLength xs < (5 :: Nat)
which will evaluate no more than 5 conses of xs.
> 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).
That said, I'm neutral on this propsal.
Cheers,
Bertram
More information about the Libraries
mailing list