On 12/07/10 12:36, Henning Thielemann wrote: > > 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. > > I also needed a bidirectional fold in the past. See foldl'r in > http://code.haskell.org/~thielema/utility/src/Data/List/HT/Private.hs > > You can express it using foldr alone, since 'foldl' can be written as > 'foldr': > http://www.haskell.org/haskellwiki/Foldl_as_foldr > > You may add your example to the Wiki. I found: http://www.haskell.org/haskellwiki/Foldl_as_foldr#Folding_by_concatenating_updates hard to understand. However, scanning http://www.haskell.org/haskellwiki/Foldl_as_foldr#See_also shows, on page 13(with fold renamed to foldr): (1.t): foldl :: ( b -> a -> b) -> b -> ([a] -> b) (1.0): foldl f v [] = v (1.1): foldl f v xs = foldr (\x g -> (\a -> g (f a x))) id xs v which is much simpler than with wiki page; however, it still looks like foldr on the rhs takes 4 args instead of 3, until one realizes that foldr is calculating a function instead of a value and the last arg on the rhs, v, is being passed to that calculated function. foldr from p. 2 of the reference( again, with renaming) is: (2.t): foldr :: ( a' -> b' -> b') -> b' -> ([a'] -> b') (2.0): foldr f v [] = v (2.1): foldr f v x:xs = f x (foldr f v xs) So, the (1.1) rhs( except for v) with xs=[1,2,3] gives: (1.1.rhs.0): foldr (\x g -> (\a -> g (f a x))) id [1,2,3] applying(i.e. replacing lhs with rhs) (2.1) to (1.1.rhs.0) with (2.1) substitutiions being: [ f <- (\x g -> (\a -> g (f a x))) , v <- id , x <- 1 , xs <- [2,3] ] gives(after renaming x and g to avoid variable capture): (1.1.rhs.1): (\x0 g0 -> (\a0 -> g0 (f a0 x0))) 1 (foldr (\x1 g1 -> (\a1 -> g1 (f a1 x1))) id [2,3] ) applying substitutions: [x0 <- 1] in (1.1.rhs.1) gives: (1.1.rhs.2): (\g0 -> (\a0 -> g0 (f a0 1))) (foldr (\x1 g1 -> (\a1 -> g1 (f a1 x1))) id [2,3] ) applying subsitutions: [ g0 <- (foldr (\x1 g1 -> (\a1 -> g1 (f a1 x1))) id [2,3] ) ] in (1.1.rhs.2) gives: (1.1.rhs.3): (\a0 -> (foldr (\x1 g1 -> (\a1 -> g1 (f a1 x1))) id [2,3] ) (f a0 1) ) applying (2.1) to (1.1.rhs.3) with (2.1) substitutions being: [ f <- (\x1 g1 -> (\a1 -> g1 (f a1 x1))) , v <- id , x <- 2 , xs <- [3] ] gives: (1.1.rhs.4): (\a0 -> (\x1 g1 -> (\a1 -> g1 (f a1 x1))) 2 (foldr (\x2 g2 -> (\a2 -> g2(f a2 x2))) id [3] ) ) (f a0 1) ) applying substitutions: [x1 <- 2] in (1.1.rhs.4) gives: (1.1.rhs.4): (\a0 -> (\g1 -> (\a1 -> g1 (f a1 2))) (foldr (\x2 g2 -> (\a2 -> g2(f a2 x2))) id [3] ) ) (f a0 1) ) applying substitutions: [ g1 <- (foldr (\x2 g2 -> (\a2 -> g2 (f a2 x2))) id [3] ) ] in (1.1.rhs.4) gives: (1.1.rhs.5): (\a0 -> (\a1 -> (foldr (\x2 g2 -> (\a2 -> g2 (f a2 x2))) id [3] ) (f a1 2) ) (f a0 1) ) applying (2.1) to (1.1.rhs.5) with (2.1) substitutions being: [ f <- (\x2 g2 -> (\a2 -> g2 (f a2 x2))) , v <- id , x <- 3 , xs <- [] ] gives: (1.1.rhs.6): (\a0 -> (\a1 -> (\x2 g2 -> (\a2 -> g2 (f a2 x2))) 3 ( foldr (\x3 g3 ->(\a3 -> g3 (f a3 x3))) id [] ) ) (f a1 2) ) (f a0 1) ) applying (2.0) to (1.1.rhs.6) gives: (1.1.rhs.6): (\a0 -> (\a1 -> (\x2 g2 -> (\a2 -> g2 (f a2 x2))) 3 id ) (f a1 2) ) (f a0 1) ) applying substitutions: [ x2 <- 3 , g2 <- id ] in (1.1.rhs.6) gives: (1.1.rhs.7): (\a0 -> (\a1 -> (\a2 -> f a2 3 ) (f a1 2) ) (f a0 1) ) Then, addding back the tail argument, v, that was left off of (1.1.rhs.0) gives: (1.1.rhs.8): (\a0 -> (\a1 -> (\a2 -> f a2 3 ) (f a1 2) ) (f a0 1) ) v Then, the substition: [ a0 <- v ] into (1.1.rhs.8) gives: (1.1.rhs.9): (\a1 -> (\a2 -> f a2 3 ) (f a1 2) ) (f v 1) Then, the substition: [ a1 <- (f v 1) ] into (1.1.rhs.9) gives: (1.1.rhs.10): (\a2 -> f a2 3 ) (f (f v 1 ) 2 ) Then, the substition: [ a2 <- (f (f v 1 ) 2 ) ] into (1.1.rhs.10) gives: (1.1.rhs.11): f (f (f v 1 ) 2 ) 3 which agrees with: foldl f z [x1, x2, ..., xn] == (...((z ‘f‘ x1) ‘f‘ x2) ‘f‘...) ‘f‘ xn from: http://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1720009.1 except for the use of infix f instead of prefix f and the the use of z instead of v, and the use of i instead of xi for i=1,2,3.