Wednesday, December 27, 2006

Tying Knots Generically

A comment by a friend and a puzzle on Lambda the Ultimate made me realise that the function loeb that I defined a few weeks back does have a nice application.


> import Maybe
> import Data.Map

> loeb :: Functor a => a (a x -> x) -> a x
> loeb x = fmap (\a -> a (loeb x)) x


The problem it helps to solve is this: building circular datastructures in Haskell, otherwise known as Tying the Knot. loeb solves this problem in a very generic way that imposes the minimum of restrictions on the user.

Remember how in my previous article I showed how you could view loeb as a kind of spreadsheet evaluator. You have a container of functions and that is converted into another container by applying these functions to the final container. This is a circular definition, we're applying the functions to the final result to get the final result. If we think of the final container as a collection of answers to a bunch of problems, loeb allows each element to be constructed using references to any of the other answers in the container, even if they haven't actually been found yet. This is exactly what we need to make circular references.

Firstly, let's look at doing something similar to the Tying the Knot web page to solve Derek's puzzle. Here potential links are made by using a dictionary structure to allow names of objects to stand for direct references to objects. So define an operator to perform pointwise concatenation of string-valued functions:


> f +++ g = \x -> f x ++ g x


Now define lookup into the dictionary, substituting a default value if needed:

And now we can translate some example equations into Haskell by hand. I'm considering define a x *b and define b y *a. Note how it's trivial to write a parser to make these objects because there's nothing circular going on:


> equations = fromList
> [
> ("a",const "x"+++lookup "b"),
> ("b",const "y"+++lookup "a")
> ] where lookup = Data.Map.findWithDefault ""


We now just apply loeb to get a dictionary containing the actual values:


> values = loeb equations
> a = fromJust $ Data.Map.lookup "a" values


We can use a similar method to make a doubly linked list. Here is "A", "B" and "C" in a list with each letter pointing to its predecessor and successor if it exists:


> data DList a = Nil | Node a (DList a) (DList a) deriving Show
>
> val (Node a _ _) = a
> rt (Node _ _ r) = r
> lft (Node _ l _) = l
>
> nodes = fromList
> [
> ("a", \d -> Node "A" Nil (lookup "b" d)),
> ("b", \d -> Node "B" (lookup "a" d) (lookup "c" d)),
> ("c", \d -> Node "C" (lookup "b" d) Nil)
> ] where lookup = Data.Map.findWithDefault Nil
>
> abc = loeb nodes
> b = fromJust $ Data.Map.lookup "b" abc


b is now a doubly linked list and we can use lft and rt to walk up and down it.

And here's a nice advantage of using loeb. You don't have to restrict yourself to storing information about links in a dictionary. Any functorial container will do. For example here's a doubly linked circular list of the integers from 0 to 99 made without using any names:


> zlist = [\z -> Node i (z!!((i-1) `mod` 100)) (z!!((i+1) `mod` 100)) | i <- [0..99]]
> z = loeb zlist


Note how working your way up and down zlist is a slow process because you need to use the slow (!!) to access elements. But stepping up and down any element of z takes time O(1). Potentially very useful!

But there is a slight problem with loeb. I'd like to be able to handle errors better and the obvious way to do that is by allowing the use of monads to handle exceptions, for example if a name lookup in a dictionary fails. I attempted to do this as follows:


> class Monad m => MFunctor m f where
> fmapM :: (a -> m b) -> f a -> m (f b)

> instance Monad m => MFunctor m [] where
> fmapM = mapM

> loebM :: (Monad m,MFunctor m a) => a (a x -> m x) -> m (a x)
> loebM x = r where
> r = do
> lx <- r
> fmapM (\a -> a lx) x

> u = loebM [const (Just 1),const (Just 2)]


But attempting to evaluate u overfows the stack. It also failed when I tried modifying it to use MonadFix. So here's a puzzle. Can you write a monadic version of loeb? It seems like something that would be very useful for writing interpreters for programming languages that allow mutually recursive definitions.

So my original intuition a few weeks back was right. Taking an interesting axiom of modal logic, interpreting as a type, and them finding an implementation, did lead to something useful.



By the way, while I was thinking about loeb I was led to consider what I call tautological containers. These are containers where each element tells you how to extricate it from the container. For example, these can be thought of as tautological: (fst,snd), [head,head.tail], [(!!n) | n <- [0..]] and [("a",fromJust . lookup "a"),("b",fromJust . lookup "b")]. Can you see any use for these objects? Are they universal for some category diagram? I have partial answers to these questions but maybe you can make more sense of them than me.




Update: Ocaml version by Matias Giovannini.

Labels:

8 Comments:

Blogger Christophe Poucet said...

For some reason your loeb function reminded me a lot of the List-ana(morphism) function from the webpage: http://www.cs.indiana.edu/~jsobel/Recycling/recycling.html

Your definition of loeb:
loeb f =
fmap (\a -> a (loeb f)) f

The definition of list_ana (translated to Haskell)

list_ana psi = f
where f l = map f (psi l)

If we generalize map to fmap then they seem nearly the same. Now the list_ana won't type in Haskell, but this is due to an infinite type which surely could be solved by adding proper constructors and destructors.

Could we perhaps say that loeb is a generalized ana-morphism, or is this reading too much into the seeming similarity.

Thursday, 28 December, 2006  
Blogger Josef said...

I don't have a solution to your loebM puzzle but an explanation as to why it fails. Your definition of loebM requires that bind is lazy. What I mean is that bottom >>= f /= bottom. If bind is strict then loebM will inevitably diverge.

Now, this leads to a bit of a problem because all monads that I know of that supply some kind of failure have strict binds. I conjecture that this must necessarily be the case, all monads will failure are strict. And this spells doom for you loebM.

I guess you already was aware of this but I'd thought I'd spell it out. And the puzzle remains unsolved.

Thursday, 28 December, 2006  
Blogger sigfpe said...

joesf,

I had more or less convinced myself that loebM was impossible but I think you've put the final nail in the coffin. In fact, I think that something like loebM isn't necessarily the best way to handle errors in this situation anyway and that with a bit of extra work, you can still use loeb.

Thursday, 28 December, 2006  
Blogger Unknown said...

How about the following ?

import Control.Monad.Fix

class Monad m => MFunctor m f
where
fmapM :: (a -> m b) -> (f a -> m (f b))

instance Monad m => MFunctor m []
where
fmapM = mapM

pamfM :: MFunctor m f => f a -> (a -> m b) -> m (f b)
pamfM = flip fmapM

loebM :: (MonadFix m,MFunctor m f) => f (f a -> m a) -> m (f a)
-- both works
loebM f = mdo let mfa = f `pamfM` ($ fa)
fa <- mfa
return fa
loebM f = mfix $ \fa -> do
f `pamfM` ($ fa)

u = loebM [const (Just 1),const (Just 2)]
-- > u
-- Just [1,2]

-- Stefan Ljungstrand

Friday, 29 December, 2006  
Blogger sigfpe said...

ski,

u = loebM [const (Just 1),Nothing]

Works lovely.

But then I try:

import Prelude hiding ((!!))
...
(!!) :: [a] -> Int -> Maybe a
[] !! _ = Nothing
a !! 0 = Just $ head a
a !! n = do
x <- (tail a) !! (n-1)
return x

u = loebM [const (Just 1),!!0]

and that fails to terminate. The intention is that if !!n returns Nothing then the whole thing should fail with Nothing.

Friday, 29 December, 2006  
Blogger Jeremy Gibbons said...

Your tautological containers remind me of Peter Hancock's Naperian functors. These are containers of fixed shape (such as the pairs, streams, and ("a","b")-dictionaries you use as examples). The names comes from the fact that they have a notion of "position", which has many of the properties of a logarithm.

Tuesday, 02 January, 2007  
Blogger sigfpe said...

Ah...'Naperian' is just the concept I need to help thinking about these things.

Tuesday, 02 January, 2007  
Blogger Unknown said...

Unfortunately, the function loeb given in the text does not produce a circular data structure with pointers into itself; rather, it produces an infinite stream of identical data structures (indexed by successive calls to loeb) each with pointers into the next. To see this, one needs to add an observable side-effect:

> import Debug.Trace

> zlist' = [\z -> Node i (z!!!((i-1) `mod` 100)) (z!!!((i+1) `mod` 100)) | i <- [0..99]]
> where lst !!! ind = trace ("indexing " ++ show ind) $ lst !! ind

> z' = loeb zlist'

Note how the first time one asks for, say, the lft of some node, it runs down the list looking for it

> val $ lft $ head z'
indexing 99
99

but the second time, that reference is cached

> val $ lft $ head z'
99

Now we can tell that rt . lft does not get us the same node, because the lft of that node has to run down the list again.

> val $ lft $ rt $ lft $ head z'
indexing 0
indexing 99
99

The "indexing 99" is repeated, and shouldn't be.

Fortunately, this bug can be fixed:

> loeb' x = result where result = fmap (\a -> a result) x

> z'' = loeb' zlist'

> val $ lft $ head z''
indexing 99
99

> val $ lft $ rt $ lft $ head z''
indexing 0
99

Now rt . lft really does get us back to the same node, as intended.

Sunday, 29 November, 2009  

Post a Comment

<< Home