Title: RE: fatal error

Keith,

I think you are right about the black hole, but I don't see how my code causes it. I have put the offending function below for you to see. If I remove the recursive calls to polyR, I do not get the deadlock.

Mike

-- Return a Lagrange polynomial as a function.
-- The index is one based, and the first index is the lower number.
--              x list     y list     index  index  polynomial
lagrangePoly :: [Float] -> [Float] -> Int -> Int -> (Float -> Float)
lagrangePoly xs ys i m = polyR xs ys (i-1) (m-1)
        where
        -- This is a zero based index
        polyR :: [Float] -> [Float] -> Int -> Int -> (Float -> Float)
        polyR xs ys i m
                | m > i = \x ->
                        (
                                ((x - xs!!(i+m)) * ((polyR xs ys i (m - 1)) x)) +
                                ((xs!!i - x) * ((polyR xs ys (i+1) (m)) x))
                        ) /
                        (xs!!i - xs!!(i+m))
                | otherwise = \x -> (ys!!i)

> -----Original Message-----
> From: Keith Wansbrough [mailto:[EMAIL PROTECTED]]
> Sent: Monday, June 05, 2000 8:02 PM
> To: Michael A. Jones
> Cc: [EMAIL PROTECTED]
> Subject: Re: fatal error
>
>
> > main: fatal error: No threads to run! Deadlock?
> [..]
> > It was mentioned to me that trace can cause this problem.
> However, I am not
> > using trace. Does anyone know any other causes?
> > 
> > One last thing, I am not doing any kind of multithreading
> on my own, but I
> > am using a lot of infinite lists. Could there be some kind
> of evaluation
> > that does not evaluate lazily.
>
> Trace, or attempting to write to both stdout and stderr, is the most
> common cause this error message.
>
> However, what the error message *means* is that you have fallen into a
> `black hole': you have a thunk whose value depends on itself.  For
> example,
>
>   let x = 1 + x
>   in  x * 2
>
> has a black hole: when the computer tries to evaluate x, it first
> looks up the value of x... but that value isn't ready yet (it's being
> computed), so the thread is put to sleep, hoping some other thread
> will complete the computation.  But this never happens, and so you
> find yourself in deadlock.
>
> In Haskell one part of a data structure is allowed to depend on other
> parts, like this:
>
>   fibs = 1 : 1 : f fibs
>        where f (x:y:xs) = x + y : f (y:xs)
>
> But a single value is not allowed to depend on itself; nor are you
> allowed a situation like this:
>
>   let x = y + 1
>       y = x - 1
>   in x
>
> It seems likely that this is what you've hit.
>
> Some versions of GHC have a blackhole detector, which detects
> (sometimes) when you've done this, and gives a more useful error
> message.
>
> HTH.
>
> --KW 8-)
>

Reply via email to