Proposal: Foldable typeclass: make foldl' and foldr' class methods

Duncan Coutts duncan.coutts at googlemail.com
Mon Jun 20 19:02:22 CEST 2011


All,

This issue was brought up again recently by Milan's questions about what
to do with folds for the containers package.

Currently the Foldable type class has:

class Foldable t where
    fold :: Monoid m => t m -> m
    foldMap :: Monoid m => (a -> m) -> t a -> m

    foldr :: (a -> b -> b) -> b -> t a -> b
    foldl :: (a -> b -> a) -> a -> t b -> a

    foldr1 :: (a -> a -> a) -> t a -> a
    foldl1 :: (a -> a -> a) -> t a -> a

with default implementations for each in terms of the others. Then it
defines:

foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> b
foldr' f z0 xs = foldl f' id xs z0
  where f' k x z = k $! f x z

foldl' :: Foldable t => (a -> b -> a) -> a -> t b -> a
foldl' f z0 xs = foldr f' id xs z0
  where f' x k z = k $! f z x

That is, they are fixed definitions so specialised implementations
cannot be provided.

Note also that these are the classic higher-order "foldl in terms of
foldr" definitions. Current releases of GHC cannot optimises these
higher-order definitions into efficient versions using accumulating
parameters. Since one of the main purposes of foldl' is performance
(other purpose being to avoid space leaks) then that's rather
unfortunate.

The proposal is simple: move these two functions into the Foldable type
class itself.

They would keep their existing default definitions but since they are
then class methods they can have efficient implementations provided by
the class instances.

This should not break much code. In particular it should not break
existing type class instance declarations since there is a default
definition for instances that don't defined the new methods.

The only potential breakage is that foldl' and foldr' are exported via
Foldable(..) rather than directly. This could affect modules that use
explicit imports.  (I consider this fact to be a slightly unfortunate
quirk of the Haskell module system).

Patch attached.

Deadline: 2 weeks: Monday 4th July.


Unresolved: what is a good concise specification of foldr' to use in the
documentation? For foldl' we can say:
  foldl' f z = List.foldl' f z . toList

Related issues not covered by this simple proposal: providing foldl1'
and foldr1', updating instances to define foldl' and foldr' if possible
(e.g. array could provide an efficient impl of foldr').

Duncan
-------------- next part --------------
A non-text attachment was scrubbed...
Name: Foldable.hs.diff
Type: text/x-patch
Size: 2967 bytes
Desc: not available
URL: <http://www.haskell.org/pipermail/libraries/attachments/20110620/2b179a76/attachment.bin>


More information about the Libraries mailing list