[Haskell-cafe] Short-circuiting a fold
Stefan O'Rear
stefanor at cox.net
Thu Apr 5 14:23:54 EDT 2007
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
More information about the Haskell-Cafe
mailing list