[Haskell-cafe] Re: Bifold: a simultaneous foldr and foldl

Larry Evans cppljevans at suddenlink.net
Tue Nov 30 15:37:32 CET 2010


On 11/29/10 21:41, Noah Easterly wrote:
> 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.
[snip]

Hi Noah,

I've not examined bifold real close, but the description:

  passing one value
  from the start of the list toward the end, and one from the end toward
  the start.

suggested to me that bifold might be similar to the function, Q, of
section 12.5 equation 1) on p. 15 of:

  http://www.thocp.net/biographies/papers/backus_turingaward_lecture.pdf

Now Q takes just 1 argument, a function.  Also, the f function defined
with Q can be short-circuited, IOW, it may not process all the
elements is a list.  Also, it may not even act on a list; however,
that just means it's more general and could be easily specialized to
just act on lists.

Anyway, I'll reproduce some of the reference's section 12.5 here:

    f == p -> q; Q(f)

  where:

    Q(k) == h <*> [i, k<*>j]

  and where(by p. 4 of reference):
    <*> is the function composition operator:
       (f <*> g) x == f(g(x))
  and where(by p. 9 of reference):
    [f,g] x = <f x, g x>
  and where(by p. 8 of reference)
    <x1,x2,...,xn> is a sequence of objects, x1,x2,...xn (like
      haskell's tuple: (x1,x2,...,xn)
  and where(by p. 8 of reference):
      (p -> g; h)(x) means "if p(x) then do g(x) else do h(x)"

  for any functions, k, p, g, h, i, j.

p. 16 provides a nice shorthand for the result of that function:

  Q^n(g) = /h<*>[i,i<*>j,...,i<*>j^(n-1),g<*>J^n

where:

  f^n = f<*>f<*>....<*> f  for n applications of f
  /h<*>[f1,f2,...,fn] is defined on p. 13 of reference.


Again, I'm not sure it's the same a bifold, but it seems pretty close.


-Larry






More information about the Haskell-Cafe mailing list