Somebody suggested I post this here if I wanted feedback.

So I was thinking about the ReverseState monad I saw mentioned on r/haskell
a couple days ago, and playing around with the concept of information
flowing two directions when I came up with this function:

bifold :: (l -> a -> r -> (r,l)) -> (l,r) -> [a] -> (r,l)
bifold _ (l,r) [] = (r,l)
bifold f (l,r) (a:as) = (ra,las)
 where (ras,las) = bifold f (la,r) as
         (ra,la) = f l a ras

(I'm sure someone else has come up with this before, so I'll just say I
discovered it, not invented it).

Basically, it's a simultaneous left and right fold, passing one value from
the start of the list toward the end, and one from the end toward the start.

It lets you do some interesting stuff, like filter based on positionor other
left-dependent information:

evenIndexed :: [a] -> [a]
evenIndexed = fst . bifold alternate (0,[])
 where alternate 0 x xs = (x:xs, 1)
       alternate 1 _ xs = (xs, 0)

maximums :: (Ord a) => [a] -> [a]
maximums [] = []
maximums (a:as) = a : (fst $ bifold (\m a l -> if a > m then (a:l,a) else
(l,m)) (a,[]) as)

As long as you don't examine the left-to-right value, it can still work on
infinite lists:

ghci> take 20 $ evenIndexed [0..]
[0,2,4,6,8,10,12,14,16,18,20,22,24,26,28,30,32,34,36,38]

Also, it can be used for corecursive data (or, at least, doubly-linked
lists):

data DList a =  Start { first :: DList a } |
               Entry { value :: a, next :: DList a, prev  :: DList a } |
               End   { last :: DList a }  deriving (Eq)

ofList :: [a] -> (DList a, DList a)
ofList as = (start,end)
 where start = Start first
       end = End last
       (first,last) = bifold mkEntry (start,end) as
       mkEntry p v n = let e = Entry v n p in (e,e)

It's just been running around my head all night, so I thought I'd share.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to