Re: Changed behaviour when reading from FIFOs!

2001-10-30 Thread Volker Stolz

On Mon, Oct 29, 2001 at 02:52:25PM -, Simon Marlow wrote:
  The blocking is essential since I need to be able to use MVars
  between the threadWaitRead  the hGetLine (remember the note I
  sent about fork()ing).
 
 Sorry, I can't remember that - could you remind me?  The hGetLine
 already blocks if there's no data in the FIFO, the extra threadWaitRead
 will only work if the Handle is in NoBuffering mode, because otherwise
 there might be data in the handle buffer waiting to be read which
 threadWaitRead would be unable to detect.

I'm using 'fork' (the real thing, not forkIO), in a Concurrent
Haskell programm and I need a way to lock out multiple readers
from the same file handle because of the sharing when forking.
-- 
Volker Stolz * [EMAIL PROTECTED] * PGP + S/MIME

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Changed behaviour when reading from FIFOs!

2001-10-29 Thread Volker Stolz

Something broke when reading from FIFOs in the transition from
5.00 to 5.02. The following program behaves as it should in
5.00, but with 5.02 it fails after printing the last line
(strangely for varying numbers of last!) with

Fail: end of file
Action: hGetChar
Handle: {loc=foo,type=readable,binary=False,buffering=none}
File: foo

Another issue is that it won't work at all with LineBuffering:
It will just print one line and then sit around doing nothing.

The program will create a FIFO named foo and simply echo
everything back to you, so you'd probably want to try

 ./t 
 ls -1 foo

Sometimes, if you just pipe the 'head' of something, it will
work without terminating, so you can try repeated invocations
of 'ls'. Looks like somethings wrong in the IO/buffering code.

ghc -package posix -package concurrent -o t t.lhs

\begin{code}
module Main where

import IO
import Posix
import Monad
import Maybe
import Concurrent
import System

main :: IO ()
main = do
  let fifoname = foo
  h - openFIFO fifoname
  hSetBuffering h NoBuffering
  dummy - openFile fifoname WriteMode
  fifoReadLoop h
 where
  fifoReadLoop h = do
fd - handleToFd h
threadWaitRead (fdToInt fd)
msg - hGetLine h
print msg
fifoReadLoop h

openFIFO :: String - IO Handle
openFIFO fifoname = do
  catch (openFile fifoname ReadMode)
(\e - if (isDoesNotExistError e)
  then do
putStrLn $ Creating FIFO  ++ fifoname
system $ /usr/bin/mkfifo  ++ fifoname
openFile fifoname ReadMode
  else error $ CanĀ“t create FIFO  ++ fifoname
 )
\end{code}
-- 
Volker Stolz * [EMAIL PROTECTED] * PGP + S/MIME

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Re: Changed behaviour when reading from FIFOs!

2001-10-29 Thread Volker Stolz

On Mon, Oct 29, 2001 at 02:08:23PM -, Simon Marlow wrote:
 This appears to be because the dummy Handle opened in WriteMode is being
 garbage collected and closed, which leaves the FIFO with no writers so
 you get EOF.  5.02 is behaving correctly here.  You can add an extra
 'hClose dummy' at the end of 'main' to prevent the EOF exception.

Argh, that was exactly what I feared when I read the file-handles
discussion on the list. Only I didn't realize that the feature
got indeed introduced into ghc-5.02.

 You have some extra blocking in there: just comment out the first two
 lines  of fifoReadLoop, and everything should be fine.  This also fixes
 the other problem you mentioned above (varying numbers of last).

The blocking is essential since I need to be able to use MVars
between the threadWaitRead  the hGetLine (remember the note I
sent about fork()ing).
-- 
Volker Stolz * [EMAIL PROTECTED] * PGP + S/MIME

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: Changed behaviour when reading from FIFOs!

2001-10-29 Thread Simon Marlow


 On Mon, Oct 29, 2001 at 02:08:23PM -, Simon Marlow wrote:
  This appears to be because the dummy Handle opened in 
 WriteMode is being
  garbage collected and closed, which leaves the FIFO with no 
 writers so
  you get EOF.  5.02 is behaving correctly here.  You can add an extra
  'hClose dummy' at the end of 'main' to prevent the EOF exception.
 
 Argh, that was exactly what I feared when I read the file-handles
 discussion on the list. Only I didn't realize that the feature
 got indeed introduced into ghc-5.02.

Just to clarify: this isn't really new behaviour, but there might be a
difference in the timing of GC and the scheduling of finalizers which
means the observable behaviour between 5.02 and 5.00.2 is different.  Of
course, there might also have been a bug in 5.00.2's IO implementation.

  You have some extra blocking in there: just comment out the 
 first two
  lines  of fifoReadLoop, and everything should be fine.  
 This also fixes
  the other problem you mentioned above (varying numbers of last).
 
 The blocking is essential since I need to be able to use MVars
 between the threadWaitRead  the hGetLine (remember the note I
 sent about fork()ing).

Sorry, I can't remember that - could you remind me?  The hGetLine
already blocks if there's no data in the FIFO, the extra threadWaitRead
will only work if the Handle is in NoBuffering mode, because otherwise
there might be data in the handle buffer waiting to be read which
threadWaitRead would be unable to detect.

Cheers,
Simon

___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs