On 11/30/10 13:43, Noah Easterly wrote: > On Tue, Nov 30, 2010 at 9:37 AM, Larry Evans <cppljev...@suddenlink.net > <mailto:cppljev...@suddenlink.net>> wrote: > > 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 > [snip] > > [snip] > > Thanks, Larry, this is some interesting stuff. > > I'm not sure yet whether Q is equivalent - it may be, but I haven't been > able to thoroughly grok it yet. > > For uniformity, I shifted the notation you gave to Haskell: > > (.^) :: (a -> a) -> Int -> a -> a > f .^ 0 = id > f .^ n = f . (f .^ (n - 1)) > > (./) :: (b -> c -> c) -> [a -> b] -> (a->c) -> a -> c > (./) = flip . foldr . \h f g -> h <$> f <*> g > > _Q_ :: (b -> c -> c) -> (a -> b) -> (a -> a) -> (a -> c) -> a -> c > _Q_ h i j k = h <$> i <*> (k . j) > > So the shorthand just states the equivalence of (_Q_ h i j) .^ n and > (./) h [ i . (j .^ m) | m <- [0 .. n-1] ] . ( . (j .^ n)) > > Looking at it that way, we can see that (_Q_ h i j) .^ n takes some > initial value, unpacks it into a list of size n+1 (using i as the > iterate function), > derives a base case value from the final value (and some function k) > maps the initial values into a new list, then foldrs over them. > > The _f_ function seems to exist to repeat _Q_ until we reach some > stopping condition (rather than n times) > > _f_ :: (b -> c -> c) -> (a -> b) -> (a -> a) -> (a -> Bool) -> (a -> > c) -> a -> c > _f_ h i j p q a = if p a then q a else _Q_ h i j (_f_ h i j p q) a > > No simple way to pass values from left to right pops out at me, but I > don't doubt that bifold could be implemented in foldr, and therefore > there should be *some* way. >
Hi Noah, The attached is my attempt at reproducing your code and also contains an alternative attempt at emulating the code in section 12.5 of: http://www.thocp.net/biographies/papers/backus_turingaward_lecture.pdf However, ghci compilation of bifold produces an error message: BifoldIfRecur.hs:20:19: parse error on input `=' OTOH, when this code is commented out and the test variable is printed, the output is: [1,2,3,999,3,2,1] [3,2,1,999] [1,2,3,999] [(),(),()] The first line is for a call to if_recur. The other two are for foldl and foldr where the binary operator is (flip (:)) and (:), respectively. The suffix after 999 of the 1st line suggests to me that if_recur does something like foldr with the else_ function is called, after which something like foldr is done, as indicated by the [1,2,3] prefix before 999 of the 1st line. So it seems that both foldr and foldl are being done during if_recur, IOW, it's a kinda bifold also. Hopefully this sheds some light on how section 12.5 is related to bifold; however, I'm still not completely sure what that relation is :( -regards, Larry
{- Purpose: Further develop idea that Bifold in posts: http://article.gmane.org/gmane.comp.lang.haskell.cafe/83874 http://article.gmane.org/gmane.comp.lang.haskell.cafe/83883 if somehow like the f in section 12.5 of: http://www.thocp.net/biographies/papers/backus_turingaward_lecture.pdf -} module BifoldIfRecur where import Monad; import Control.Applicative; -- {*83874 article {- 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 -} -- }*83874 article -- {*83883 article {--} (.^) :: (a -> a) -> Int -> a -> a f .^ 0 = id f .^ n = f . (f .^ (n - 1)) (./) :: (b -> c -> c) -> [a -> b] -> (a->c) -> a -> c (./) = flip . foldr . \h f g -> h <$> f <*> g _Q_ :: (b -> c -> c) -> (a -> b) -> (a -> a) -> (a -> c) -> a -> c _Q_ h i j k = h <$> i <*> (k . j) {--} -- }*83883 article -- {*if_recur.hpp from http://svn.boost.org/svn/boost/sandbox/variadic_templates/boost/mpl/ if_recur :: state_down -> (state_down -> Bool) -> (state_down -> state_down) -> ((state_down,state_up) -> state_up) -> (state_down -> state_up) -> state_up if_recur state_now -- current state recur_ -- continue recursion? then_down -- ::state_down -> state_down now_up -- ::((state_down,state_up)->state_up else_ -- ::state_down -> state_up = if recur_ state_now then now_up ( state_now , if_recur (then_down state_now) recur_ then_down now_up else_ ) else else_ state_now -- }*if_recur.hpp from http://svn.boost.org/svn/boost/sandbox/variadic_templates/boost/mpl/ {--} palindrome_btm :: [a] -> a -> [a] palindrome_btm x b = if_recur (x,[]) --state_now (not.null.fst) --recur_ (\(sn,cd) -> (tail sn,(head sn):cd)) --then_down (\(sn,cu) -> (head $ fst sn):cu) --now_up (\(sn,cd) -> b:cd) test = sequence [ print (palindrome_btm [1,2,3] 999) , print (foldl (flip(:)) [999] [1,2,3]) , print (foldr (:) [999] [1,2,3]) ] {--}
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe