Sorry, should have cc'ed this to [email protected] in the first place...
Please send any replies to the version sent to the libraries list.



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

diff --git a/Data/Foldable.hs b/Data/Foldable.hs
index 354bd8b..500ce8c 100644
--- a/Data/Foldable.hs
+++ b/Data/Foldable.hs
@@ -22,8 +22,6 @@ module Data.Foldable (
     -- * Folds
     Foldable(..),
     -- ** Special biased folds
-    foldr',
-    foldl',
     foldrM,
     foldlM,
     -- ** Folding actions
@@ -61,6 +59,7 @@ import Prelude hiding (foldl, foldr, foldl1, foldr1, mapM_, sequence_,
                 elem, notElem, concat, concatMap, and, or, any, all,
                 sum, product, maximum, minimum)
 import qualified Prelude (foldl, foldr, foldl1, foldr1)
+import qualified Data.List as List (foldl')
 import Control.Applicative
 import Control.Monad (MonadPlus(..))
 import Data.Maybe (fromMaybe, listToMaybe)
@@ -121,12 +120,26 @@ class Foldable t where
     foldr :: (a -> b -> b) -> b -> t a -> b
     foldr f z t = appEndo (foldMap (Endo . f) t) z
 
+    -- | Right-associative fold of a structure, 
+    -- but with strict application of the operator.
+    foldr' :: (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
+
     -- | Left-associative fold of a structure.
     --
     -- @'foldl' f z = 'Prelude.foldl' f z . 'toList'@
     foldl :: (a -> b -> a) -> a -> t b -> a
     foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
 
+    -- | Left-associative fold of a structure.
+    -- but with strict application of the operator.
+    --
+    -- @'foldl' f z = 'List.foldl'' f z . 'toList'@
+    foldl' :: (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
+
     -- | A variant of 'foldr' that has no base case,
     -- and thus may only be applied to non-empty structures.
     --
@@ -161,6 +174,7 @@ instance Foldable Maybe where
 instance Foldable [] where
     foldr = Prelude.foldr
     foldl = Prelude.foldl
+    foldl' = List.foldl'
     foldr1 = Prelude.foldr1
     foldl1 = Prelude.foldl1
 
@@ -170,24 +184,12 @@ instance Ix i => Foldable (Array i) where
     foldr1 f = Prelude.foldr1 f . elems
     foldl1 f = Prelude.foldl1 f . elems
 
--- | Fold over the elements of a structure,
--- associating to the right, but strictly.
-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
-
 -- | Monadic fold over the elements of a structure,
 -- associating to the right, i.e. from right to left.
 foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b
 foldrM f z0 xs = foldl f' return xs z0
   where f' k x z = f x z >>= k
 
--- | Fold over the elements of a structure,
--- associating to the left, but strictly.
-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
-
 -- | Monadic fold over the elements of a structure,
 -- associating to the left, i.e. from left to right.
 foldlM :: (Foldable t, Monad m) => (a -> b -> m a) -> a -> t b -> m a
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to