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

Reply via email to