RE: [Haskell-cafe] Spurious program crashes

2005-11-23 Thread Simon Marlow
On 21 November 2005 16:43, Joel Reymont wrote:

 I'm being quite careful with resources these days. The outstanding
 issues are
 
 1) Crashes on Mac OSX that are not reproduced on Linux, Windows, etc.
 
 2) Some kind of a problem with Chan. getChanContents retrieves things
 smoothly, readChan only does it for the first few lines. Simon?
 Anyone? 

After subsequent dicsussion, do you still think something strange was
going on here?  The code does look strange:

logger :: MVar () - IO ()
logger die =
do empty - isEmptyChan parent
   unless empty $ do x - readChan parent
 putStrLn x
   alive - isEmptyMVar die
   when (alive || not empty) $ logger die

so this basically loops until there are no messages in the channel, and
then exits.  Is that what you wanted, or did you want it to keep reading
from the channel until told to die?

STM is a better solution, as already suggested.  Without STM, the best
way to do this is to multiplex everything into a single channel (i.e.
send the die message down the channel).

 3) Different performance of the logger thread on Mac OSX and Windows.
 
 I'm having thousands of threads write their trace messages to a Chan.
 The logger On Windows I only see the first few lines of output when
 using isEmptyChan/readChan to retrieve values in a loop. On Mac OSX I
 do see smooth output.

Context switch behaviour might be different between MacOS X and Windows.
With the above code, it might be that the logger thread found an empty
channel at sp,e point and exited.  Does that make sense?

 On Windows I run out of memory because all the output sent to the
 chan builds up and is never processed. I can process it by replacing
 isEmptyChan/readChan with getChanContents but then my logger thread
 hangs forever (right semantics) and hangs everything else that waits
 for the logger thread to check an MVar and exit.

yes, because the logger thread has exited.

Cheers,
SImon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-23 Thread Joel Reymont


On Nov 23, 2005, at 1:18 PM, Simon Marlow wrote:


After subsequent dicsussion, do you still think something strange was
going on here?


Yes, but in a different thread. The Postmortem one.

so this basically loops until there are no messages in the channel,  
and
then exits.  Is that what you wanted, or did you want it to keep  
reading

from the channel until told to die?


I probably made a mistake someplace as I wanted to read until told to  
die but ONLY if the channel was empty. I replaced that code with  
Tomasz's elegant solution so now I read until Nothing is read from  
the channel.


logger :: Handle - IO ()
logger h =
do ss - getChanContents parent
   logger' ss
   where logger' [] = return ()
 logger' (Nothing:_) = return ()
 logger' ((Just x):xs) =
 do putStrLn x
hPutStrLn h x
logger' xs
yield

For whatever reason this generates empty lines with some sort of an  
unprintable character at the beginning. It prints these to the screen  
but not to the file. Of course it also prints what it's supposed to  
but the garbage shows both on Windows and the Mac.



STM is a better solution, as already suggested.  Without STM, the best
way to do this is to multiplex everything into a single channel (i.e.
send the die message down the channel).


Right.

Thanks, Joel

--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Spurious program crashes

2005-11-23 Thread Simon Marlow
On 23 November 2005 13:29, Joel Reymont wrote:

 On Nov 23, 2005, at 1:18 PM, Simon Marlow wrote:
 
 After subsequent dicsussion, do you still think something strange was
 going on here?
 
 Yes, but in a different thread. The Postmortem one.
 
 so this basically loops until there are no messages in the channel,
 and then exits.  Is that what you wanted, or did you want it to keep
 reading from the channel until told to die?
 
 I probably made a mistake someplace as I wanted to read until told to
 die but ONLY if the channel was empty. I replaced that code with
 Tomasz's elegant solution so now I read until Nothing is read from
 the channel.
 
 logger :: Handle - IO ()
 logger h =
  do ss - getChanContents parent
 logger' ss
 where logger' [] = return ()
   logger' (Nothing:_) = return ()
   logger' ((Just x):xs) =
   do putStrLn x
  hPutStrLn h x
  logger' xs
  yield

The yield is unnecessary.  Also, getChanContents is considered by some
(me included) to be poor style, because it relies on lazy I/O.  This
should work just as well:

  logger h = do
 m - readChan parent
 case m of
   Nothing - return ()
   Just x  - do hPutStrLn h x; logger h

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Joel Reymont
I was under the impression that STM code needed to be in its own  
monad. I was looking at Control.Concurrent.STM.TChan, for example,  
where signatures like this exist:


newTChan :: STM (TChan a)   
readTChan :: TChan a - STM a
writeTChan :: TChan a - a - STM ()  

and then

newTChan :: STM (TChan a)   
readTChan :: TChan a - STM a
writeTChan :: TChan a - a - STM ()  


I guess I should give this another look, re-read the STM paper and  
check out your patch.


Regardless, simple is elegant and your Maybe solution is simple.

Thanks, Joel

On Nov 22, 2005, at 7:09 AM, Tomasz Zielonka wrote:


I am talking about Software Transactional Memory, which is in
Control.Concurrent.STM. I think you confused it with State
Transformer Monad.

In your case STM would allow you to wait simultaneously on (T)MVar and
(T)Chan. It would look like this:

logger :: TMVar () - IO ()
logger die =
join $ atomically $
(do x - readTChan parent
return $ do
putStrLn x
logger die)
`orElse`
(do takeTMVar die
return (return ()))


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 08:30:33AM +, Joel Reymont wrote:
 I was under the impression that STM code needed to be in its own  
 monad. I was looking at Control.Concurrent.STM.TChan, for example,  
 where signatures like this exist:
 
 newTChan :: STM (TChan a) 
 readTChan :: TChan a - STM a 
 writeTChan :: TChan a - a - STM ()  

The STM monad is where synchronisation operations are grouped
in transactions. You can use STM as a drop-in replacement for
traditional Control.Concurrent synchronisation primitives by
simply wrapping every single operation in an atomically block:

atomically :: STM a - IO a

For example, a drop-in replacement for Chan:

type Chan' a = TChan a

newChan' = atomically newTChan
readChan' c = atomically (readTChan c)
writeChan' c v = atomically (writeChan c v)

the types of these functions are:

newChan' :: IO (TChan a)
readChan' :: TChan a - IO a
writeChan' :: TChan a - a - IO ()

But it is only grouping more operations in a transaction that will let
you benefit from the wonders of STM :-)

 I guess I should give this another look, re-read the STM paper and  
 check out your patch.

You definitely should do it. It is a very rewarding read.

 Regardless, simple is elegant and your Maybe solution is simple.

But it also requires that you restructure your code, doesn't it?
I am not sure we understood each other here.

One way to restructure your code to enable smooth transition to the
(Chan (Maybe String)) idea would be to change the type of die request
from (MVar ()) to (IO ()). You could use

(dieVar, die) - do
dieVar - newEmptyMVar
return (dieVar, putMVar dieVar ())

where dieVar is used on the receiver side, and die is used on the
sender side. Then you could easily use a different notification
mechanism for logger:

let die = writeChan parent Nothing

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Joel Reymont

Tomasz,

I think it's much simpler than that. I just changed the trace  
function to send Just String down the channel. Whenever I send  
Nothing (from waitForChildren) the logger just exits. Simple change  
in two places, no need for MVars.


Did I miss anything? The program became much snappier, btw.

Joel

On Nov 22, 2005, at 8:53 AM, Tomasz Zielonka wrote:


Regardless, simple is elegant and your Maybe solution is simple.


But it also requires that you restructure your code, doesn't it?
I am not sure we understood each other here.

One way to restructure your code to enable smooth transition to the
(Chan (Maybe String)) idea would be to change the type of die  
request

from (MVar ()) to (IO ()). You could use

(dieVar, die) - do
dieVar - newEmptyMVar
return (dieVar, putMVar dieVar ())

where dieVar is used on the receiver side, and die is used on the
sender side. Then you could easily use a different notification
mechanism for logger:

let die = writeChan parent Nothing


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 09:03:55AM +, Joel Reymont wrote:
 I think it's much simpler than that. I just changed the trace  
 function to send Just String down the channel. Whenever I send  
 Nothing (from waitForChildren) the logger just exits. Simple change  
 in two places, no need for MVars.

 Did I miss anything?

Perhaps I did. I had an impression that these MVars where a pattern that
you use in other parts of your code. If this is only limited to the
logger code then it code could be probably simplified even further.

 The program became much snappier, btw.

Did it fix the problem?

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-22 Thread Joel Reymont
Yes in the sense that more than a few lines of code are now printed  
on Windows. Not in the sense of the topic of this thread but then it  
seems to be a Mac OSX-only issue.


Thanks, Joel

On Nov 22, 2005, at 9:14 AM, Tomasz Zielonka wrote:


The program became much snappier, btw.


Did it fix the problem?


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Keean Schupke
One thing, which I am sure you must have got right, but which burned me, 
is that you must explicitly free enitities created by FFI calls.


For example network sockets exist outside of the haskell runtime, and 
are not free'd automatically when a haskell thread is killed, you need 
an explicit exception handler to close the handle... They may eventually 
be garbage collected - but your application may run out of resources 
before this happens.


   Keean.

Joel Reymont wrote:

Maybe one of the Simons can comment on this. I distinctly remember  
trying the mdo approach to kill the other thread and getting burned  
by that. Don't know why I forgot to mention it.


On Nov 17, 2005, at 2:03 PM, Sebastian Sylvan wrote:


What I do remember is that the timeout and parIO functions in the
concurrent programming papers I found were NOT correct. killThread did
NOT behave as expected when I killed an already killed thread.
I tried multiple tricks here (including some which required recursive
do-notation) to try to get the parIO function to only kill the *other*
thread.
This could be done by having the two spawned threads take their
computations in an MVar along with the threadID of the other thread.



--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Joel Reymont
I'm being quite careful with resources these days. The outstanding  
issues are


1) Crashes on Mac OSX that are not reproduced on Linux, Windows, etc.

2) Some kind of a problem with Chan. getChanContents retrieves things  
smoothly, readChan only does it for the first few lines. Simon? Anyone?


3) Different performance of the logger thread on Mac OSX and Windows.

I'm having thousands of threads write their trace messages to a Chan.  
The logger On Windows I only see the first few lines of output when  
using isEmptyChan/readChan to retrieve values in a loop. On Mac OSX I  
do see smooth output.


On Windows I run out of memory because all the output sent to the  
chan builds up and is never processed. I can process it by replacing  
isEmptyChan/readChan with getChanContents but then my logger thread  
hangs forever (right semantics) and hangs everything else that waits  
for the logger thread to check an MVar and exit.


On Nov 21, 2005, at 4:34 PM, Keean Schupke wrote:

One thing, which I am sure you must have got right, but which  
burned me, is that you must explicitly free enitities created by  
FFI calls.


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Tomasz Zielonka
On Mon, Nov 21, 2005 at 04:42:33PM +, Joel Reymont wrote:
 2) Some kind of a problem with Chan. getChanContents retrieves things  
 smoothly, readChan only does it for the first few lines. Simon? Anyone?

This is interesting. Could you show some source code?

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Joel Reymont

Yes, of course.

darcs repo at http://test.wagerlabs.com/postmortem.

logger in Util.hs

On Nov 21, 2005, at 8:30 PM, Tomasz Zielonka wrote:


On Mon, Nov 21, 2005 at 04:42:33PM +, Joel Reymont wrote:

2) Some kind of a problem with Chan. getChanContents retrieves things
smoothly, readChan only does it for the first few lines. Simon?  
Anyone?


This is interesting. Could you show some source code?


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Tomasz Zielonka
On Mon, Nov 21, 2005 at 09:50:20PM +, Joel Reymont wrote:
 Yes, of course.
 
 darcs repo at http://test.wagerlabs.com/postmortem.
 
 logger in Util.hs

It's in Conc.hs

You seem to be busy waiting. I can see two ways of solving the problem:
1. use STM and non-deterministic choice
2. use a (Chan (Maybe String)), where (Just s) means the next log
   entry, and Nothing means break the logger loop

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Joel Reymont
STM would complicate things too much for me. At least I think so. I  
would love to use STM but I would need to fit it into type  
ScriptState = ErrorT String (StateT World IO) just to use the  
logger. I'm not THAT comfortable with monads.


Let me see if I understand you correctly... Are you saying that I  
should be using getChanContents in the code below?


logger :: Handle - MVar () - IO ()
logger h die =
do empty - isEmptyChan parent
   unless empty $ do x - readChan parent
 putStrLn x
 hPutStrLn h x
   alive - isEmptyMVar die
   when (alive || not empty) $ logger h die

I think using Maybe is a great trick but I'm curious why so few  
messages actually get taken out of the channel in the code above? Are  
you saing that with all the checking it does not get to pull messages  
out?


I see clearly how using Maybe with getChanContents will work out  
perfectly. I don't understand why the above code is inefficient to  
the point of printing just a few messages (out of hundreds) out on  
Windows. I would like to understand it to avoid such mistakes in the  
future.


Thanks, Joel

On Nov 21, 2005, at 9:56 PM, Tomasz Zielonka wrote:

You seem to be busy waiting. I can see two ways of solving the  
problem:

1. use STM and non-deterministic choice
2. use a (Chan (Maybe String)), where (Just s) means the next log
   entry, and Nothing means break the logger loop


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-21 Thread Tomasz Zielonka
On Mon, Nov 21, 2005 at 10:41:38PM +, Joel Reymont wrote:
 STM would complicate things too much for me. At least I think so. I  
 would love to use STM but I would need to fit it into type  
 ScriptState = ErrorT String (StateT World IO) just to use the  
 logger. I'm not THAT comfortable with monads.

I am talking about Software Transactional Memory, which is in
Control.Concurrent.STM. I think you confused it with State
Transformer Monad.

In your case STM would allow you to wait simultaneously on (T)MVar and
(T)Chan. It would look like this:

logger :: TMVar () - IO ()
logger die =
join $ atomically $
(do x - readTChan parent
return $ do
putStrLn x
logger die)
`orElse`
(do takeTMVar die
return (return ()))

but you have to modify the rest of code to use STM. I modified your
Conc.hs to use STM, but using the greater guarantees of STM you
could surely simplify it further (see the attached patch).

 Let me see if I understand you correctly... Are you saying that I  
 should be using getChanContents in the code below?

I am not proposing to use getChanContents. You are busy-waiting
on MVar and Chan. I just proposed a solution to stuff messages
and die-request into the same concurrency primitive, so you
can wait for both events using a single operation.

But you are right (below) that this bug doesn't explain the behaviour of
your program. It is only a performance bug.
 
 logger :: Handle - MVar () - IO ()
 logger h die =
 do empty - isEmptyChan parent
unless empty $ do x - readChan parent
  putStrLn x
  hPutStrLn h x
alive - isEmptyMVar die
when (alive || not empty) $ logger h die

 I think using Maybe is a great trick but I'm curious why so few  
 messages actually get taken out of the channel in the code above?

Actually, I am not sure. I just noticed that your code uses a bad
coding practice and could be improved. If I find some time I'll try to 
examine it more closely.

 Are  you saing that with all the checking it does not get to pull
 messages  out?

As it is, you code can impose a big performance penalty, but indeed
it shouldn't change the semantics. Perhaps I miss something.

 I see clearly how using Maybe with getChanContents will work out  
 perfectly. I don't understand why the above code is inefficient to  
 the point of printing just a few messages (out of hundreds) out on  
 Windows. I would like to understand it to avoid such mistakes in the  
 future.

Yes, this is strange. Perhaps we're both missing something obvious.

Best regards
Tomasz

New patches:

[Use STM in Conc.hs
Tomasz Zielonka [EMAIL PROTECTED]**20051122065752] {
hunk ./Conc.hs 6
+import Control.Concurrent.STM
hunk ./Conc.hs 15
-children = unsafePerformIO $ newMVar []
+children = unsafePerformIO $ atomically $ newMVar []
hunk ./Conc.hs 20
-parent = unsafePerformIO newChan
+parent = unsafePerformIO $ atomically newChan
hunk ./Conc.hs 28
-   writeChan parent $ stamp ++ :  ++ (show tid) ++ :  ++ a
+   atomically $ writeChan parent $ stamp ++ :  ++ (show tid) ++ :  ++ a
hunk ./Conc.hs 46
-do empty - isEmptyChan parent
-   unless empty $ do x - readChan parent
- putStrLn x
-   alive - isEmptyMVar die
-   when (alive || not empty) $ logger die
+join $ atomically $
+(do x - readChan parent
+return $ do
+putStrLn x
+logger die)
+`orElse`
+(do takeMVar die
+return (return ()))
hunk ./Conc.hs 58
-   logDie - newEmptyMVar
-   logDead - newEmptyMVar
-   l - forkIO (logger logDie `finally` putMVar logDead ())
+   logDie - atomically newEmptyMVar
+   logDead - atomically newEmptyMVar
+   l - forkIO (logger logDie `finally` atomically (putMVar logDead ()))
hunk ./Conc.hs 63
-  do cs - takeMVar children
+  do cs - atomically (takeMVar children)
hunk ./Conc.hs 65
- []   - do putMVar die ()
-takeMVar dead
+ []   - do atomically $ do
+putMVar die ()
+takeMVar dead
hunk ./Conc.hs 69
- m:ms - do putMVar children ms
-takeMVar m
+ m:ms - do atomically $ do
+putMVar children ms
+takeMVar m
hunk ./Conc.hs 76
-do mvar - newEmptyMVar
-   childs - takeMVar children
-   putMVar children (mvar:childs)
-   forkIO (io `finally` putMVar mvar ())
+do mvar - atomically newEmptyMVar
+   atomically $ do
+   childs - takeMVar children
+   putMVar children (mvar:childs)
+   forkIO (io `finally` atomically (putMVar mvar ()))

Re: [Haskell-cafe] Spurious program crashes

2005-11-17 Thread Joel Reymont


On Nov 17, 2005, at 1:44 PM, Sebastian Sylvan wrote:


Are you sure it's safe to kill a thread which has already been killed?


It seems so from the docs.


Why do you fork off the killing of the threads? Why not just run them
in sequence?


Someone said that they read somewhere that killThread can block. I'm  
not gonna point any fingers at musasabi ;-).



Also, I'd recommend refactoring the code a bit, write a function
parIO which runs IO computations in parallell and then define
timeout in terms of that.


I did this by stealing the timeout/either combinators from the  
Asynchronous Exceptions paper. It did not help a single bit.


Joel

--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-17 Thread Sebastian Sylvan
On 11/17/05, Joel Reymont [EMAIL PROTECTED] wrote:

 On Nov 17, 2005, at 1:44 PM, Sebastian Sylvan wrote:

  Are you sure it's safe to kill a thread which has already been killed?

 It seems so from the docs.

  Why do you fork off the killing of the threads? Why not just run them
  in sequence?

 Someone said that they read somewhere that killThread can block. I'm
 not gonna point any fingers at musasabi ;-).

  Also, I'd recommend refactoring the code a bit, write a function
  parIO which runs IO computations in parallell and then define
  timeout in terms of that.

 I did this by stealing the timeout/either combinators from the
 Asynchronous Exceptions paper. It did not help a single bit.



This is somewhat frustrating for me because I had a very similar (if
not the exact same) issue when writing some test applications for an
FMOD binding. However, all that source code (and so much more) was
lost due to a hard disk failure. I am now struggling to remember what
was the cause, and how I solved.

What I do remember is that the timeout and parIO functions in the
concurrent programming papers I found were NOT correct. killThread did
NOT behave as expected when I killed an already killed thread.
I tried multiple tricks here (including some which required recursive
do-notation) to try to get the parIO function to only kill the *other*
thread.
This could be done by having the two spawned threads take their
computations in an MVar along with the threadID of the other thread.

something like:

parIO f1 f2 = do m - newEmptyMVar -- result Mvar
   mf1 - newEmptyMVar  -- MVar for f1
   mf2 - newEmptyMVar  -- MVar for f2
   -- fork worker threads
   t1 - forkIO (child m mf1)
   t2 - forkIO (child m mf2)

   -- pass computations and threadID to worker threads
   putMVar mf1 (t2, f1)
   putMVar mf2 (t1, f2)

   -- return result
   takeMVar m
   where child m mf = do (tid, f) - takeMVar mf
x - f
putMVar m x
killThread tid


timeout t f = threadDelay (round (t * 1e6)) `parIO` f


As I remember another solution I came up with was to wrap the child
function body in a catch statement. The child function was just a
helper function that ran a computation and put its result in an MVar.

I *think* the problem *may* have been that when an FFI function got
ThreadKilled exception asynchrounously that got bubbled up to the
parIO thread for some reason.

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-17 Thread Joel Reymont
Maybe one of the Simons can comment on this. I distinctly remember  
trying the mdo approach to kill the other thread and getting burned  
by that. Don't know why I forgot to mention it.


On Nov 17, 2005, at 2:03 PM, Sebastian Sylvan wrote:


What I do remember is that the timeout and parIO functions in the
concurrent programming papers I found were NOT correct. killThread did
NOT behave as expected when I killed an already killed thread.
I tried multiple tricks here (including some which required recursive
do-notation) to try to get the parIO function to only kill the *other*
thread.
This could be done by having the two spawned threads take their
computations in an MVar along with the threadID of the other thread.


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Spurious program crashes

2005-11-17 Thread Simon Marlow
On 16 November 2005 17:38, Joel Reymont wrote:

 I'm getting crashes like this and I cannot figure out what the
 problem is. I'm launching a bunch of threads that connect to a server
 via TCP and exchange packets.
 
 I am running operations like connect and receive in a timeout
 function that launches two threads and uses an MVar to figure out
 who's done first. The timeout function then kills the two threads.
 
 Any ideas what could be causing this? I feel like a Haskell guinea
 pig these days :-).

I don't see any reason why you should be getting crashes here, but this
is a delicate area (async exceptions + FFI).  It's possible there's a
bug, but as usual we need to reproduce the symptoms here.  Can you help
with a repro case?

Regarding the behaviour of killThread, I believe the version in GHC is
slightly different from the version described in the Asynchronous
Exceptions paper, in particular the GHC version blocks until the
exception has been delivered to the target thread (use another forkIO to
get the fully async version).

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-17 Thread Joel Reymont
I will work on the repro case over the weekend. Getting this to work  
correctly is crucial to the future of Haskell, I think. Without this  
working correctly there's a slim chance of Haskell being used  
successfully used for high-performance networking apps.


On Nov 17, 2005, at 3:00 PM, Simon Marlow wrote:

I don't see any reason why you should be getting crashes here, but  
this

is a delicate area (async exceptions + FFI).  It's possible there's a
bug, but as usual we need to reproduce the symptoms here.  Can you  
help

with a repro case?


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-17 Thread Joel Reymont
Actually, this has just become crucial for me. In my using of  
hWaitForInput I missed that it blocks all other threads if no input  
is available :-(. Arghh! I still need timeouts.


On Nov 17, 2005, at 3:00 PM, Simon Marlow wrote:


Regarding the behaviour of killThread, I believe the version in GHC is
slightly different from the version described in the Asynchronous
Exceptions paper, in particular the GHC version blocks until the
exception has been delivered to the target thread (use another  
forkIO to

get the fully async version).


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-16 Thread Tomasz Zielonka
On Wed, Nov 16, 2005 at 05:37:34PM +, Joel Reymont wrote:
 I'm getting crashes like this and I cannot figure out what the  
 problem is. I'm launching a bunch of threads that connect to a server  
 via TCP and exchange packets.
 
 I am running operations like connect and receive in a timeout  
 function that launches two threads and uses an MVar to figure out  
 who's done first. The timeout function then kills the two threads.
 
 Any ideas what could be causing this?

Let me guess - excessive use of unsafe operations (like unsafe*, FFI)?
I've got an impression that you use them too often for a fresh Haskell
programmer. Too often for a Haskell programmer in general.

Excuse me if I wrong.

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-16 Thread Joel Reymont
I really don't use more FFI than needed to send and receive binary  
packets over the network. I don't even use FPS these days and all the  
allocaBytes code checks for nullPtr.


My hunch is that this is to do with killing threads that perform FFI  
in my timeout code. It would kill blocking connect and hGet  
operations for example.


timeout :: forall a.Show a = Int - IO a - IO a
timeout secs fun =
do mvar - newEmptyMVar
   tid1 - forkIO $ do result - try fun
   putMVar mvar $
   either (Left . show) (Right . id)
   result
   tid2 - forkIO $ do threadDelay (secs * 100)
   putMVar mvar (Left timeout)
   maybeResult - takeMVar mvar
   forkIO $ do killThread tid1
   killThread tid2
   case maybeResult of
 Right a - return a
 Left b - fail b

On Nov 16, 2005, at 5:52 PM, Tomasz Zielonka wrote:


Let me guess - excessive use of unsafe operations (like unsafe*, FFI)?
I've got an impression that you use them too often for a fresh Haskell
programmer. Too often for a Haskell programmer in general.


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Spurious program crashes

2005-11-16 Thread Tomasz Zielonka
On Wed, Nov 16, 2005 at 06:16:48PM +, Joel Reymont wrote:
 I really don't use more FFI than needed to send and receive binary  
 packets over the network. I don't even use FPS these days and all the  
 allocaBytes code checks for nullPtr.

Then please accept my apologies. I may have confused you with
someone else.

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe