
import Control.Monad import Control.Monad.Instances
foldr is The One True Fold:
ssfold :: (a -> Bool) -> (a -> b -> a) -> a -> [b] -> a ssfold p f a0 xs = foldr (\x xs a -> if p a then a else xs (f a x)) id xs a0
pointfree obfuscated:
if' True x _ = x if' _ _ y = y ssfold' = (flip .) . flip flip id . (foldr .) . (. ((flip (.) .) . flip)) . (.) . (.) . ap . (if' =<<)
Spencer Janssen
On Thu, 5 Apr 2007 14:09:12 -0400
"Kurt Hutchinson"
Here's a bit of Thursday afternoon fun.
Mission: Define "ssfold," a short-circuiting fold. It evaluates to the "folded value" that first satisfies the given predicate.
ssfold :: ( a -> Bool ) -> ( a -> b -> a ) -> a -> [b] -> a
Here are two of mine.
Straightforward:
ssfold p f z = head . dropWhile ( not . p ) . scanl f z
Monadic:
data Done a b = Done { undone :: a } | NotDone b instance Monad ( Done a ) where ( NotDone i ) >>= f = f i ( Done r ) >>= _ = Done r return = NotDone
ssfold p f z = undone . foldM (\ v e -> if p v then Done v else NotDone ( f v e ) ) z
I want to see some real creativity here, so pull out all the stops.
Kurt _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe