Difference between revisions of "Circular programming"

From HaskellWiki
Jump to navigation Jump to search
(Moving description of Swiestra's ``Why Attribute Grammars Matter'' article to Attribute grammar)
m (Arrow category)
Line 273: Line 273:
   
 
[[Category:Idioms]]
 
[[Category:Idioms]]
  +
[[Category:Arrow]]

Revision as of 03:51, 20 December 2006

Porting from HaWiki's CircularProgramming

I port only my material from there (because I know only the copyright status of my writings on HaWiki).

Previous contributions

So, the previous materials (to which mine is connected) are on HaWiki's CircularProgramming

The notion of trace and loop

--
--
--        THE LOOP OF THE ARROW --- BEING ITSELF ALSO AN ARROW
--                   
--          ,...............................................,
--          :                                               :
--          :                                               :
--          :                  +---------+                  :
--          :   INPUT          |:::::::::|         OUTPUT   :
--  ==========================>+:::::::::+========================>
--          :                  |::ARROW::|                  :
--          :            +====>+:::::::::+=====+            :
--          :            |     |:::::::::|     |            :
--          :            |     +---------+     |            :
--          :            |                     |            :
--          :            +==========<==========+            :
--          :                    FEEDBACK                   :
--          :                                               :
--          ;...............................................;
--

Ross Paterson: Arrows and Computation introduces the loop construct of arrows (on page 11)

class Arrow arrow => ArrowLoop arrow where
        loop :: arrow (input, feedback) (output, feedback) -> arrow input output

with an ordinary function called trace:

trace :: ((input, feedback) -> (output, feedback)) -> input -> output
trace f input = let (output, feedback) = f (input, feedback)
                in output

(I renamed the type variables and their corresponding argument names, too.)

Of course trace can be seen as loop for ordinary functions as arrows:

instance ArrowLoop (->) where
        loop = trace

Let us use a modified version of trace here: our version of trace should require not a function from an ordered pair (to an ordered pair), but a curried function (to an ordered pair):

trace :: (input -> feedback -> (output, feedback)) -> input -> output
trace f input = let (output, feedback) = f input feedback
                in output

Modularity and reuse

What can trace be good for? For example, for modularizing that magic feedback step in circular programs! By the concept of modularity I mean as described in John Hughes' article Why Functional Programming Matters.

Repmin problem

Let us see the tree minimum problem (described above), and let us modularize the magic circular step by this feedback view of trace:

repmin :: Ord a => Tree a -> Tree a
repmin = trace repIImin

repIImin :: Ord a => Tree a -> a -> (Tree a, a)
repIImin (Leaf minval) rep = (Leaf rep, minval)
repIImin (Branch left right) rep = let (left', min_left) = repIImin left rep
                                         (right', min_right) = repIImin right rep
                                   in (Branch left' right', min min_left min_right)

Notations: in , my -II- infix notation means parallelity, referring to the fact that the wonderful achievement of these functions is being able to work in one traversal. Sometimes I use -X- infix notation instead of -II-, referring to cross product:

As we can see, we have things enough to confuse: two arguments, a returned tuple, how they depend from each other... A hint: let us think of the scheme of trace:

  • input -- what we work with
  • output -- what we get
  • feedback -- a state-like thing, yes, a feedback, that can be thought of through both aspects
    • feedback-as-produced: thinking of it as it leaves the box
    • feedback-as-fed-back: thinking of it as it is fed back into the box again

If we decide, what the roles of input, output, feedback plays, then these circular programming funtions will look easier. E.g. here, at the repmin problem

  • input is a tree filled with numbers, a heterogenous tree
  • output is the repmin'ed tree, a homogenized tree
  • feedback (something state-like): here that strange numeric value plays the role of feedback! Its two aspects are
    • feedback-as-produced -- in this aspect, it is a minimum value, a statistic of the tree
    • feedback-as-fed-back -- in this aspect, it is a setter value, a rather seed-like thing: it is spred homogenously in the shape of a given tree

Now it is easier to look at , we have a road-map for our eyes in the jungle of parameters and returned tuple.

--
--
--                How repmin is born: wrapping rep||min with trace
--
--                                    
--          ,.........................repmin............................,
--          :                                                           :
--          :                                                           :
--          :                     +------------+                        :
--          : Heterogenous tree   |::::::::::::|     Homogenized tree   :
--  =============================>+::::::::::::+================================>
--          :                     |::rep||min::|                        :
--          :               +====>+::::::::::::+=====+                  :
--          :               |     |::::::::::::|     |                  :
--          :    setter-val |     +------------+     |   min-val        :
--          :      a seed   |                        | a statistic      :
--          :               +===========<============+                  :
--          :                        FEEDBACK                           :
--          :                                                           :
--          ;...........................................................;
--

Normalizing vectors

Normalizing vectors by trace is not so straightforward, but a small trick can help us:

normalize :: Floating a => [a] -> [a]
normalize = trace divideIInorm

divideIInorm :: Floating a => [a] -> a -> ([a], a)
divideIInorm vector a = let (divided, norm2) = scaleIInorm2 vector (recip a)
                        in (divided, sqrt norm2)

scaleIInorm2 :: Floating a => [a] -> a -> ([a], a)
scaleIInorm2 [] _ = ([], 0)
scaleIInorm2 (x : xs) a = let (scaled, norm2) = scaleIInorm2 xs a
                          in (a * x : scaled, x * x + norm2)

(I mean my notation scaleIInorm2 be read as ). We can see what the problem was and how it was solved here:

  • trace requires a rather strict scheme: the function it takes as an argument must be exactly of the same scheme as seen in the above feedback picture
  • the recursion by which we can solve the problem eventually (here: ) usually provides another scheme. E.g. here we cannot compute norm directly by recursion.

So we have to join together the needs of trace and the possibilities of recursion together, we have to convert between these two plugs if they are incompatible, that is why we created .

This is not the only way to force the problem to the shape of trace. There are other ways, but they do not seem so natural, they look somewhat artificial, albeit in efficiency aspects, I think, they are the same:

normalize :: Floating a => [a] -> [a]
normalize = trace divideBySqrtIInorm2

divideBySqrtIInorm2 :: Floating a => [a] -> a -> ([a], a)
divideBySqrtIInorm2 vector scalar = scaleIInorm2 vector (1 / sqrt scalar)

works too, and there is another artificial solution yet:

normalize :: Floating a => [a] -> a -> ([a], a)
normalize = trace scaleIIrecipNorm

scaleIIrecipNorm :: [a] -> a -> ([a], a)
scaleIIrecipNorm vector a = let (scaled, norm2) = scaleIInorm2 vector a
                            in (scaled, recip $ sqrt norm2)

this is good, too. All these three solutions converge, they terminate.

But there are circular programming examples where such possible solutions will not be so equivalent: one of them may diverge, while the other converge. It seems to me, the diff example (described in Wouter Swiestra's Why Attribute Grammars Matter) is exactly such circular programming problem.

Decrease all elements by their average

This diff example is:

  • how to compute the average of a list
  • and (in the same traversal of the list) decrease all elements of the list by this average value.

Here, the gap between

  • the needs of trace
  • and possibilities of (single traversal) recursion

seems even wider than in the previous problem. Let us try:

diff :: Fractional a => [a] -> [a]
diff = trace decrementIIaverage

decrementIIaverage :: Fractional a => [a] -> a -> ([a], a)
decrementIIaverage list delta = let (decremented, (sum', length')) = decrementIIsumLength list delta
                                in (decremented, sum' `divideByInt` length')

decrementIIsumLength :: Fractional a => [a] -> a -> ([a], (a, Integer))
decrementIIsumLength [] _ = ([], (0, 0))
decrementIIsumLength (a : as) delta = let (decremented, (sum', length')) = decrementIIsumLength as delta
                                      in (a - delta : decremented, (a + sum', succ length'))

divideByInt :: Fractional a => a -> Integer -> a
a `divideByInt` n = a / fromRational (toRational n)

As we can see, recursion cannot deal with average (indirectly), that is why provides (besides the list with all its element decremented by the delta value) not an average value, but a length---sum pair.

There is no real reason, why the return value of should be ([a], (a, Integer)) instead of the more simple ([a], a, Integer): let us untangle the nested tuples, using the law! Let us use a instead of :

diff :: Fractional a => [a] -> [a]
diff = trace decrementIIaverage

decrementIIaverage :: Fractional a => [a] -> a -> ([a], a)
decrementIIaverage list delta = let (decremented, sum', length') = decrementIIsumIIlength list delta
                                in (decremented, sum' `divideByInt` length')

decrementIIsumIIlength :: Fractional a => [a] -> a -> ([a], a, Integer)
decrementIIsumIIlength [] _ = ([], 0, 0)
decrementIIsumIIlength (a : as) delta = let (decremented, sum', length') = decrementIIsumIIlength as delta
                                        in (a - delta : decremented, a + sum', succ length')

divideByInt :: Fractional a => a -> Integer -> a
a `divideByInt` n = a / fromRational (toRational n)

As in the previous problem (normalizing a vector), also at this probem we could imagine other possible solutions:

divdiff :: Fractional a => [a] -> [a]
divdiff = trace decquotIIsumLength

decquotIIsumLength :: Fractional a => [a] -> (a, Integer) -> ([a], (a, Integer))
decquotIIsumLength list (a, n) = let (dec, sum', length') = decrementIIsumIIlength list (a `divideByInt` n)
                                 in (dec, (sum', length'))

but this is divergent (even for the empty list): it does not terminate at all, albeit this solution seemed for me standing in a duality relation with the previous one.

Excuse me for my toys. Of course in Wouter Swiestra's Why Attribute Grammars Matter there are much deeper solutions to this and other examples. See more details on this article on the Attribute grammar HaskellWiki page.

Related concepts