I have a good theory on the latter symptom (the "thread killed"
message). Sticking in some traces, as in my appended code, helped me
to see what's going on. It seems to be exactly what you describe --
the variable v is permanently bound to the exception it "evaluates"
to. Since the right hand True portion of the unamb evaluates more
quickly, the spawned threads are killed and the left hand (the v)
"evaluates" to "thread killed". This remains the value of its thunk
when you access it later. This problem seems sort of innate to a pure
unamb utilizing unsafePerformIO and asynchronous exceptions. A clever
use of `par` might conceivably help, given that if the par spark
fails, the thunk can still be evaluated? Might be a dead end.
Here's the code:
go = f "f" (f "" True) where f s v = (unamb (s++"f") (s++"g") v True)
`seq` v
--unamb :: String -> String -> a -> a -> a
unamb s s' a b = unsafePerformIO (race s s' (evaluate a) (evaluate b))
--race :: String -> String -> IO a -> IO a -> IO a
race s s' a b = do
v <- newEmptyMVar
let t x = x >>= putMVar v
withThread s (t a) $ withThread s' (t b) $ takeMVar v
where
withThread s u v = bracket (forkIO u) (killNote s) (const $
putStrLn ("in: " ++ s) >> v >>= \x -> putStrLn ("out: " ++ show x ++
" "++ s) >> return x)
killNote s tid = throwTo tid (ErrorCall s)
And a GHCi session:
*Un> go
in: ff
in: fg
in: f
in: g
out: True fg
out: True ff
<interactive>: ff
*** Exception: ff
Cheers,
Sterl.
On Dec 26, 2008, at 1:15 AM, Conal Elliott wrote:
I'm looking for information about black hole detection with ghc.
I'm getting "<<loop>>" where I don't think there is an actual black
hole. I get this message sometimes with the unamb package, which
is implemented with unsafePerformIO, concurrency, and killThread,
as described in http://conal.net/blog/posts/functional-concurrency-
with-unambiguous-choice/ and http://conal.net/blog/posts/smarter-
termination-for-thread-racing/ .
Suppose I have a definition 'v = unsafePerformIO ...', and v is
used more than once. Evaluation (to whnf) of v is begun and the
evaluation thread gets killed before evaluation is complete. Then
the second use begins. Will the second evaluation be (incorrectly)
flagged as a black hole?
I haven't found a simple, reproducible example of incorrect black-
hole reporting. My current examples are tied up with the Reactive
library. I do have another strange symptom, which is "thread
killed" message. I wonder if it's related to the <<loop>>
message. Code below.
Thanks, - Conal
import Prelude hiding (catch)
import System.IO.Unsafe
import Control.Concurrent
import Control.Exception
-- *** Exception: thread killed
main :: IO ()
main = print $ f (f True) where f v = (v `unamb` True) `seq` v
-- | Unambiguous choice operator. Equivalent to the ambiguous choice
-- operator, but with arguments restricted to be equal where not
bottom,
-- so that the choice doesn't matter. See also 'amb'.
unamb :: a -> a -> a
unamb a b = unsafePerformIO (evaluate a `race` evaluate b)
-- | Race two actions against each other in separate threads, and pick
-- whichever finishes first. See also 'amb'.
race :: IO a -> IO a -> IO a
race a b = do
v <- newEmptyMVar
let t x = x >>= putMVar v
withThread (t a) $ withThread (t b) $ takeMVar v
where
withThread u v = bracket (forkIO u) killThread (const v)
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users