awaitEval in Concurrent Haskell

Claus Reinke claus.reinke@talk21.com
Tue, 11 Feb 2003 17:04:06 -0000


> Yes, we considered using something like the Hood technique.   The problem
> is that a path-annotated observation sequence is a rather unwieldy 
> representation of a data structure. 

Instead of generating path-annotated observation sequences, you could use
the same trick to trigger other demand-driven actions, but I think I can see the 
problem: you'd have a sequence of actions in demand-for-x-driven order
on one side and an expression  (predicate applied to x) on the other. 

Intriguing problem..

It may be possible to get the two representations together by applying the
predicate to a "reader" for x, generated from x, which would complement 
something like Hood's "writer" for x, generated from x. Just as the context
demanding parts of x isn't aware of triggering observations, the predicate
depending on parts of x need not be aware of having to wait for those
observations, and MVars could provide the plumbing between the implicit
readers and writers. See below for an outline.

> What we are after is a little different.  We need a way of attaching
> an arbitrary boolean predicate to a data structure, with its own pattern 
> of demand for the components, but only proceeding as and when the needed 
> components become evaluated by the normal computation.  Perhaps 
> "data-driven" is misleading; ...

No, seems quite apt to me: demand for some x makes parts of x available,
and you would like the availability of that data to drive the evaluation of
some (predicate x), provided that there is demand for the result. Btw, there
is no guarantee that there'll ever be sufficient data for the evaluation of
those predicate applications, so they won't be on the main evaluation 
thread - what do you do with their results?

Anyway, here's an outline of the reader/writer idea:

First, we can modify the Hood trick slightly to generate "writers" for the 
xs in question (again taking pairs as examples for the generic functions):

    observeW mv (a,b) = unsafePerformIO $ do
        mva <- newEmptyMVar
        mvb <- newEmptyMVar
        putMVar mv (mva,mvb)      -- "(,) has been observed here"
        return (observeW mva a,observeW mvb b)

Then, we can generate a complement of "readers" to guard copies of 
those xs from premature evaluation by the predicates (note that all data
come via the hidden plumbing here - the parameter is for typing only):

    observeR mv (a,b) = unsafePerformIO $ do
        (mva,mvb) <- takeMVar mv     -- "(,) has been observed elsewhere"
        return (observeR mva a,observeR mvb b)

We could now hack up some assertion scheme, employing observeR
to guard x from some predicate, and observeW to drive that predicate
by demand for x from the evaluation context:

    assert :: String -> (a->Bool) -> a -> a
    assert l p x = unsafePerformIO $ do
        mv <- newEmptyMVar
        forkIO $ putStrLn $ l++show (p (observeR mv x)
        return $ observeW mv x

The side-thread for the predicate should print only to the extent that
(p x) depends only on parts of x observed in the main thread, hopefully?-)

It seems that the reader/writer scheme relies on all constructors being 
polymorphic, as x::((,) a b) and mv::MVar ((,) (MVar a') (MVar b')) are
used with the same (,). A workaround would be to package constructors 
separately from their components, using

        putMVar mv ((,),mva,mvb)

in the writer and

        (c,mva,mvb) <- takeMVar mv
        return $ c (observeR mva a) (observeR mvb b)

in the reader.

Hope this makes some sense. Naturally, it is completely untested,
and whether or not it is as unsafe as it looks is left as an exercise;-)

Cheers,
Claus