
I'm sure this has been done a hundred times before, but a simple generalization of foldl just occurred to me and I wonder if there's anything like it in the standard libraries (I couldn't find anything). Basically, I was trying to define the "any" function in terms of a fold, and my first try was this:
any :: (a -> Bool) -> [a] -> Bool any p = foldl (\b x -> b || p x) False
This is inefficient, because if (p x) is ever True the rest of the list is scanned unnecessarily. So I wrote a more general foldl with an "escape" predicate which terminates the evaluation, along with a function which tells what to return in that case (given an argument of the running total 'z'):
foldle :: (b -> Bool) -> (a -> a) -> (a -> b -> a) -> a -> [b] -> a foldle _ _ _ z [] = z foldle p h f z (x:xs) = if p x then h z else foldle p h f (f z x) xs
Using this function, "foldl" is:
foldl' = foldle (const False) id
and "any" is just:
any p = foldle p (const True) const False
I also thought of an even more general fold:
foldle' :: (b -> Bool) -> (a -> b -> [b] -> a) -> (a -> b -> a) -> a -> [b] -> a foldle' _ _ _ z [] = z foldle' p h f z (x:xs) = if p x then h z x xs else foldle' p h f (f z x) xs
Using this definition, you can write "dropWhile" as:
dropWhile :: (a -> Bool) -> [a] -> [a] dropWhile p = foldle' (not . p) (\_ x xs -> x:xs) const []
Again, I'm sure this has been done before (and no doubt better); I'd appreciate any pointers to previous work along these lines. Mike

On Wed, Jul 04, 2007 at 04:20:20PM -0700, Michael Vanier wrote:
I'm sure this has been done a hundred times before, but a simple generalization of foldl just occurred to me and I wonder if there's anything like it in the standard libraries (I couldn't find anything). Basically, I was trying to define the "any" function in terms of a fold, and my first try was this:
any :: (a -> Bool) -> [a] -> Bool any p = foldl (\b x -> b || p x) False
This is inefficient, because if (p x) is ever True the rest of the list is scanned unnecessarily.
Rather than create a new escape fold, it's much easier, simpler, and faster just to use a right fold: any p = foldr (\x b -> p x || b) False That will short-ciruit well by laziness, and is made tailrecursive by same. Stefan

That's cool -- good point. takeWhile is also trivially defined in terms of foldr:
takeWhile p = foldr (\x r -> if p x then x:r else []) []
Can you do dropWhile in terms of foldr? I don't see how. Mike Stefan O'Rear wrote:
On Wed, Jul 04, 2007 at 04:20:20PM -0700, Michael Vanier wrote:
I'm sure this has been done a hundred times before, but a simple generalization of foldl just occurred to me and I wonder if there's anything like it in the standard libraries (I couldn't find anything). Basically, I was trying to define the "any" function in terms of a fold, and my first try was this:
any :: (a -> Bool) -> [a] -> Bool any p = foldl (\b x -> b || p x) False This is inefficient, because if (p x) is ever True the rest of the list is scanned unnecessarily.
Rather than create a new escape fold, it's much easier, simpler, and faster just to use a right fold:
any p = foldr (\x b -> p x || b) False
That will short-ciruit well by laziness, and is made tailrecursive by same.
Stefan

On Wed, Jul 04, 2007 at 05:08:01PM -0700, Michael Vanier wrote:
That's cool -- good point. takeWhile is also trivially defined in terms of foldr:
takeWhile p = foldr (\x r -> if p x then x:r else []) []
Can you do dropWhile in terms of foldr? I don't see how.
dropWhile cannot be expressed (with full sharing semantics) in terms of foldr alone, but it can be done nicely as a so-called paramorphism using foldr and tails. dropWhile p = foldr (\l cont -> case l of { (x:xs) | p x -> cont ; _ -> l }) [] . tails Stefan

2007/7/4, Michael Vanier
That's cool -- good point. takeWhile is also trivially defined in terms of foldr:
takeWhile p = foldr (\x r -> if p x then x:r else []) []
Can you do dropWhile in terms of foldr? I don't see how.
I 'm very bad in english, sorry. Here is a solution.... dropWhile in terms of fordr Author : Graham Hutton www.cs.nott.ac.uk/~gmh/fold.ps

On 05/07/2007, at 10:08 AM, Michael Vanier wrote:
Can you do dropWhile in terms of foldr? I don't see how.
Mike
I considered that very question in an article I wrote for the Monad.Reader magazine: http://www.haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf If you are really keen, you might want to try altering the "working backwards with tuples" version into one which is properly lazy (many people who read the paper pointed out the omission). Cheers, Bernie.

Can you do dropWhile in terms of foldr? I don't see how. If you are really keen, you might want to try altering the "working backwards with tuples" version into one which is properly lazy (many people who read the paper pointed out the omission).
you might want to mention the story of the predecessor function in church numerals (where data structures are represented as their right folds, and the predecessor function goes against the grain of that recursion, but can be defined using pairing/returning functions)? for some history/anecdotes: The Impact of the Lambda Calculus in Logic and Computer Science, Barendregt, Bulletin of Symbolic Logic, 1997, section 2, paragraph 2 http://citeseer.ist.psu.edu/barendregt97impact.html for the tupling trick applied to dropWhile and primitive recursion, Graham's tutorial has already been mentioned: A tutorial on the universality and expressiveness of fold Graham Hutton. Journal of Functional Programming, 1999, section 4 http://www.cs.nott.ac.uk/~gmh/bib.html#fold claus

On Thursday 05 July 2007 11:20, Michael Vanier wrote:
Again, I'm sure this has been done before (and no doubt better); I'd appreciate any pointers to previous work along these lines.
Takusen is, if I recall correctly, based around a generalised fold supporting accumulation and early termination. Maybe have a look at that. Dan

dm.maillists:
On Thursday 05 July 2007 11:20, Michael Vanier wrote:
Again, I'm sure this has been done before (and no doubt better); I'd appreciate any pointers to previous work along these lines.
Takusen is, if I recall correctly, based around a generalised fold supporting accumulation and early termination. Maybe have a look at that.
Streams are a similar idea, a generalised unfold supporting early termination, skipping, and accumulation. Useful for coding up lots of list functions with the same underlying type, so you can fuse them with a single rule. A data type to encode this unfold: data Stream a = forall s. Stream !(s -> Step a s) -- ^ a stepper function !s -- ^ an initial state data Step a s = Yield a !s | Skip !s | Done Give a way to introduce and remove these guys: stream :: [a] -> Stream a stream xs0 = Stream next xs0 where next [] = Done next (x:xs) = Yield x xs unstream :: Stream a -> [a] unstream (Stream next s0) = unfold_unstream s0 where unfold_unstream !s = case next s of Done -> [] Skip s' -> unfold_unstream s' Yield x s' -> x : unfold_unstream s' We can roll a fair few list functions: -- folds foldl :: (b -> a -> b) -> b -> Stream a -> b foldl f z0 (Stream next s0) = loop_foldl z0 s0 where loop_foldl z !s = case next s of Done -> z Skip s' -> loop_foldl z s' Yield x s' -> loop_foldl (f z x) s' foldr :: (a -> b -> b) -> b -> Stream a -> b foldr f z (Stream next s0) = loop_foldr s0 where loop_foldr !s = case next s of Done -> z Skip s' -> expose s' $ loop_foldr s' Yield x s' -> expose s' $ f x (loop_foldr s') -- short circuiting: any :: (a -> Bool) -> Stream a -> Bool any p (Stream next s0) = loop_any s0 where loop_any !s = case next s of Done -> False Skip s' -> loop_any s' Yield x s' | p x -> True | otherwise -> loop_any s' -- maps map :: (a -> b) -> Stream a -> Stream b map f (Stream next0 s0) = Stream next s0 where next !s = case next0 s of Done -> Done Skip s' -> Skip s' Yield x s' -> Yield (f x) s' -- filters filter :: (a -> Bool) -> Stream a -> Stream a filter p (Stream next0 s0) = Stream next s0 where next !s = case next0 s of Done -> Done Skip s' -> Skip s' Yield x s' | p x -> Yield x s' | otherwise -> Skip s' -- taking takeWhile :: (a -> Bool) -> Stream a -> Stream a takeWhile p (Stream next0 s0) = Stream next s0 where next !s = case next0 s of Done -> Done Skip s' -> Skip s' Yield x s' | p x -> Yield x s' | otherwise -> Done -- dropping dropWhile :: (a -> Bool) -> Stream a -> Stream a dropWhile p (Stream next0 s0) = Stream next (S1 :!: s0) where next (S1 :!: s) = case next0 s of Done -> Done Skip s' -> Skip (S1 :!: s') Yield x s' | p x -> Skip (S1 :!: s') | otherwise -> Yield x (S2 :!: s') next (S2 :!: s) = case next0 s of Done -> Done Skip s' -> Skip (S2 :!: s') Yield x s' -> Yield x (S2 :!: s') -- zips zipWith :: (a -> b -> c) -> Stream a -> Stream b -> Stream c zipWith f (Stream next0 sa0) (Stream next1 sb0) = Stream next (sa0 :!: sb0 :!: Nothing) where next (sa :!: sb :!: Nothing) = case next0 sa of Done -> Done Skip sa' -> Skip (sa' :!: sb :!: Nothing) Yield a sa' -> Skip (sa' :!: sb :!: Just (L a)) next (sa' :!: sb :!: Just (L a)) = case next1 sb of Done -> Done Skip sb' -> Skip (sa' :!: sb' :!: Just (L a)) Yield b sb' -> Yield (f a b) (sa' :!: sb' :!: Nothing) -- concat concat :: Stream [a] -> [a] concat (Stream next s0) = loop_concat_to s0 where loop_concat_go [] !s = loop_concat_to s loop_concat_go (x:xs) !s = x : loop_concat_go xs s loop_concat_to !s = case next s of Done -> [] Skip s' -> loop_concat_to s' Yield xs s' -> loop_concat_go xs s' The nice thing is that once all your functions are in terms of these, usually non-recursive guys, and you have a rewrite rule: {-# RULES "STREAM stream/unstream fusion" forall s. stream (unstream s) = s #-} GHC will do all the loop fusion for you. Particularly nice with strict arrays, since that'll eliminate one O(n) array allocation per function. See http://www.cse.unsw.edu.au/~dons/streams.html Cheers, Don

Michael Vanier
I'm sure this has been done a hundred times before, but a simple
occurred to me and I wonder if there's anything like it in the standard
anything). Basically, I was trying to define the "any" function in terms of a fold, and my first try was this:
any :: (a -> Bool) -> [a] -> Bool any p = foldl (\b x -> b || p x) False
This is inefficient, because if (p x) is ever True the rest of the list is scanned unnecessarily. So I wrote a more general foldl with an "escape" predicate which terminates
with a function which tells what to return in that case (given an argument of
generalization of foldl just libraries (I couldn't find the evaluation, along the running total 'z'):
foldle :: (b -> Bool) -> (a -> a) -> (a -> b -> a) -> a -> [b] -> a foldle _ _ _ z [] = z foldle p h f z (x:xs) = if p x then h z else foldle p h f (f z x) xs
Using this function, "foldl" is:
foldl' = foldle (const False) id
and "any" is just:
any p = foldle p (const True) const False
There have already been better responses / solutions to this, but I just wanted to point out that there was already a form of an "escaping" left fold, namely foldM.
import Data.Maybe ( isJust ) import Control.Monad ( foldM )
any p = not . isJust . foldM (\_ x -> if p x then Nothing else Just ()) ()
Of course the logic is a little confusing to read :)
participants (8)
-
Bernie Pope
-
Claus Reinke
-
Daniel McAllansmith
-
dons@cse.unsw.edu.au
-
Guido Genzone
-
Logan Capaldo
-
Michael Vanier
-
Stefan O'Rear