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

Edward Kmett ekmett at gmail.com
Mon Jun 20 20:03:09 CEST 2011


+1 and I would vote again if I didn't think folks would catch me stuffing
the ballot box. ;)

On Mon, Jun 20, 2011 at 1:02 PM, Duncan Coutts <duncan.coutts at googlemail.com
> wrote:

> 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
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20110620/a7145bd1/attachment-0001.htm>


More information about the Libraries mailing list