John Lato wrote:
How would you implement bfnum?  (If you've already read the paper,
what was your first answer?)

My first idea was something similar to what is described in appendix A. However, after reading the paper, I wrote the following code:

  data Tree a = E | T a (Tree a) (Tree a)
    deriving Show

  bfnum :: Tree a -> Tree Int
  bfnum = num . bf

  bf :: Tree a -> [Tree a]
  bf root = output where
    children = go 1 output
    output = root : children

    go 0 _ = []
    go n (E       : rest) = go (pred n) rest
    go n (T _ a b : rest) = a : b : go (succ n) rest

  num :: [Tree a] -> Tree Int
  num input = root where
    root : children = go 1 input children

    go k (E : input) children = E : go k input children
    go k (T _ _ _ : input) ~(a : ~(b : children))
      = T k a b : go (succ k) input children

Maybe one could try to fuse bf and num.

  Tillmann
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to