
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

On 05/04/07, Kurt Hutchinson
Straightforward:
ssfold p f z = head . dropWhile ( not . p ) . scanl f z
I'd prefer find instead of head . dropWhile (not . p), making the result type a Maybe, as this is essentially equivalent to searching through the result of a scan for a specific value, so it should follow find's example and use Maybe for its partiality.
I want to see some real creativity here, so pull out all the stops.
You may also be interested in the Compose experiment [1]: a bit of fun seeing how many different ways compose :: [a -> a] ->(a -> a) could be defined. Most are quite silly, but the solution involving the State monad, for example, is really quite elegant. [1]: http://haskell.org/haskellwiki/Compose -- -David House, dmhouse@gmail.com

On Thu, Apr 05, 2007 at 02:09:12PM -0400, Kurt Hutchinson wrote:
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
ssfold p f z = fromJust . find p . scanl f z -- might need a few (safe) unsafeCoerce#s ssfold p f z = go . (z:) where go (x:xs) | p x = x | otherwise = case xs of (xx:xxs) -> go (f x xx:xxs) ssfold p f z = go z where go a xs | xs `seq` p a = a | otherwise = case xs of (xx:xxs) -> go (f x xx) xxs ssfold p f z = foldr go (\k -> if p k then k else undefined) where go ths cont acc | p acc = acc | otherwise = cont (f acc ths) data Exit = Exit Any deriving Typeable ssfold p f z l = unsafePerformIO $ catchDyn (evaluate (go l z)) (\ (Exit a) -> return $ unsafeCoerce# a) where go l ac | p ac = throwDyn (Exit (unsafeCoerce# ac)) go (x:xs) ac = go xs (f ac x) Stefan

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
participants (4)
-
David House
-
Kurt Hutchinson
-
Spencer Janssen
-
Stefan O'Rear