Re: awaitEval in Concurrent Haskell

Colin [ccing GHC users in case there are other enthusiasts out there]
| we briefly discussed the lack in | Concurrent Haskell of any way to set up a data-driven | thread -- one that works on a data structure D without | ever forcing its evaluation, only proceeding with the | computation over D as and when the needed parts get | evaluated by some other thread.
I'm not sure whether I understand what you have in mind later on, but this first part sounds so remarkably like something I've seen before, that I'll take my chances. Do you remember Andy Gill's Hood from long ago? Inside its implementation, it had a very similar problem: writing information about an observed structure to some observation trace, but without forcing premature evaluation of the structure under observation. The trick used in Observe.lhs is roughly this (here for (,)): observe label (a,b) = unsafePerformIO $ do sendObservation label "(,)" return (observe label a,observe label b) with some position information and strictness mangling added, and the whole nicely wrapped into a monad (see Observe.lhs for details). Nothing happens as long as the thing under observation is not inspected by its context. Then, and precisely then, the unsafePerformIO kicks in to record a piece of information and to return the outer part of the thing, wrapping its components into fresh observers. Andy used this to store observations in a list, to be processed at the end of the program run, but you can just as well send the observations during evaluation, e.g., to a concurrent thread (with the usual caveats). In particular, the sequencing of information becoming available was detailed enough to inspire my own GHood;-) With no implementation slot free, something like this might get your student's project unstuck (e.g., replace sendObservation by assert)? After all, my favourite justification for unsafePerformIO is as an extension hook in the runtime system.. Sorry if your intention was something else and I'm just trying to fit a solution to the problem. Even then, you might be able to adapt the trick to your application. Cheers, Claus

C.Reinke wrote:
I'm not sure whether I understand what you have in mind later on, but this first part sounds so remarkably like something I've seen before, that I'll take my chances.
Do you remember Andy Gill's Hood from long ago?
Inside its implementation, it had a very similar problem: writing information about an observed structure to some observation trace, but without forcing premature evaluation of the structure under observation ... Nothing happens as long as the thing under observation is not inspected by its context. Then, and precisely then, the unsafePerformIO kicks in to record a piece of information and to return the outer part of the thing, wrapping its components into fresh observers.
Andy used this to store observations in a list, to be processed at the end of the program run, but you can just as well send the observations during evaluation, e.g., to a concurrent thread (with the usual caveats). In particular, the sequencing of information becoming available was detailed enough to inspire my own GHood;-)
With no implementation slot free, something like this might get your student's project unstuck (e.g., replace sendObservation by assert)? After all, my favourite justification for unsafePerformIO is as an extension hook in the runtime system..
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. As you say, Hood stores the observations to file, where they can be post-processed beyond the confines of the observed Haskell computation. The scheme works because the whole purpose of the application is just to observe the data in the order that it becomes evaluated. 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; we want the sequence of evaluation for an asserted predicate to remain demand driven as usual, but for progress in that sequence to be constrained by the rule that no evaluation of the data structure argument may be forced. Colin R

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

Claus,
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.
Thanks for this further suggestion. A solution along these lines might be possible, but it would still be restricted in comparison with something based on a more "global" awaitEval: the availability of data would only be detected if the demand that prompted its evaluation was in the context of the assertion-tagged expression. Yes? Regards Colin R

A couple of hours ago, I wrote (in reponse to Claus Reinke's suggestion):
Thanks for this further suggestion. A solution along these lines might be possible, but it would still be restricted ...
Actually a mild variant of Claus's proposal seems to work out quite well. Another way to avoid the problems with types is to use a multi-parameter type class. Little example attached. So, thanks again Claus! Regards Colin R -- A mini-experiment in concurrent data-driven assertions. -- Colin Runciman after Claus Reinke after Andy Gill after ... -- February 2003 import Control.Concurrent import Char(isLower) import System.IO.Unsafe(unsafePerformIO) -- Each type a over which assertions are to be made is -- encoded using a metatype b. class Assert a b | a -> b, b -> a where assertW :: MVar b -> a -> a assertR :: MVar b -> a assert :: Assert a b => String -> (a->Bool) -> a -> a assert s p x = unsafePerformIO $ do mv <- newEmptyMVar forkIO $ check s p (assertR mv) return $ assertW mv x check :: String -> (a -> Bool) -> a -> IO () check s p x | p x = return () | otherwise = putStrLn $ "assertion failure: " ++ s -- We can use assertions over characters, encoded as themselves. instance Assert Char Char where assertW mv c = unsafePerformIO $ do putMVar mv c return c assertR mv = unsafePerformIO $ do c <- takeMVar mv return c -- Here's the metatype encoding for lists; similar definitions -- would be needed for other structured types. data MetaList a = Nil | Cons (MVar a) (MVar (MetaList a)) instance Assert a b => Assert [a] (MetaList b) where assertW mv [] = unsafePerformIO $ do putMVar mv Nil return [] assertW mv (x:xs) = unsafePerformIO $ do mvx <- newEmptyMVar mvxs <- newEmptyMVar putMVar mv (Cons mvx mvxs) return (assertW mvx x : assertW mvxs xs) assertR mv = unsafePerformIO $ do ml <- takeMVar mv return $ case ml of Nil -> [] (Cons mvx mvxs) -> (assertR mvx : assertR mvxs) -- Finally, a simple example application. singleCaseWords :: String -> Bool singleCaseWords xs = all unmixed (words xs) unmixed :: String -> Bool unmixed "" = True unmixed (c:cs) | isLower c = all isLower cs | otherwise = not (any isLower cs) main = do input <- getContents putStr (assert "single-case words" singleCaseWords input)
participants (3)
-
C.Reinke
-
Claus Reinke
-
Colin Runciman