I think the docs are wrong, or perhaps we're misunderstanding them.
Magnus is correct.

Attached is a test program which listens on two ports, 42000 (blocking
IO) and 42001 (non-blocking). You can use netcat, telnet, etc, to send
it data. The behavior is as Magnus describes: bytes from
hGetNonBlocking are available immediately, while hGet waits for a full
buffer (or EOF) before returning.

This behavior obviously makes hGet unsuitable for enumHandle; my
apologies for not understanding the problem sooner.
import Control.Concurrent (forkIO, threadDelay)
import Control.Monad (forever, unless)
import Control.Monad.Fix (fix)
import qualified Data.ByteString as B
import Network
import System.IO

main :: IO ()
main = do
	blockingSock <- listenOn (PortNumber 42000)
	nonblockingSock <- listenOn (PortNumber 42001)
	
	forkIO $ acceptLoop B.hGet blockingSock "Blocking"
	forkIO $ acceptLoop nonblockingGet nonblockingSock "Non-blocking"
	forever $ threadDelay 1000000

nonblockingGet :: Handle -> Int -> IO B.ByteString
nonblockingGet h n = do
	hasInput <- catch (hWaitForInput h (-1)) (\_ -> return False)
	if hasInput
		then B.hGetNonBlocking h n
		else return B.empty

acceptLoop :: (Handle -> Int -> IO B.ByteString) -> Socket -> String -> IO ()
acceptLoop get sock label = fix $ \loop -> do
	(h, _, _) <- accept sock
	putStrLn $ label ++ " client connected"
	bytesLoop (get h)
	putStrLn $ label ++ " EOF"
	loop

bytesLoop :: (Int -> IO B.ByteString) -> IO ()
bytesLoop get = fix $ \loop -> do
	bytes <- get 20
	unless (B.null bytes) $ do
		putStrLn $ "bytes = " ++ show bytes
		loop
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to