[Haskell-cafe] Simple network client

Peter Verswyvelen bf3 at telenet.be
Wed Jan 30 09:01:10 EST 2008


Yes, and if I'm correct this hGetContents is used by many other functions, such as readFile...

As a newbie I made a nice little program that called readFile and writeFile on the same filename, but of course the file handle of the readFile was not closed yet => access denied. A nice case of getting bitten by my imperative background.

Then I tried the "seq" hack to force the handle opened by readFile to be closed, but that did not seem to work either. For example, the following still gave access denied:

main = do
  cs <- readFile "L:/Foo.txt"
  writeFile "L:/Foo.txt" $ seq (length cs) cs

This is (I guess) because the writeFile *still* happens before the seq, so the readFile handle is still not closed.

The following does work:

main = do
  cs <- readFile "L:/Foo.txt"
  (seq (length cs) writeFile) "L:/Foo.txt" cs

This all looks a lot like hacking a side effect :)

So I guess hGet/hGetNonBlocking/ByteString is also the correct way to solve this?

Thanks,
Peter

PS: I would love to see an immutable filesystem that does not allow writing to files, it only creates new files and garbage collects files that have no incoming reference anymore... Just like a garbage collected heap, and a bit like an OLAP databases (as far as I remember my DB theory...) Besides the performance bottleneck, does something like that exists?

> -----Original Message-----
> From: haskell-cafe-bounces at haskell.org [mailto:haskell-cafe-
> bounces at haskell.org] On Behalf Of Jules Bean
> Sent: Wednesday, January 30, 2008 1:03 PM
> To: "Timo B. Hübel"
> Cc: haskell-cafe at haskell.org
> Subject: Re: [Haskell-cafe] Simple network client
> 
> Your bug here is hGetContents.
> 
> Don't use it.
> 
> Lazy IO gremlins bite once again.
> 
> Your client is waiting for the server to close the socket before it
> prints anything. But your server is waiting for the client to close the
> socket before *it* prints anything.
> 
> Just don't use hGetContents in any serious code, or any program longer
> than 4 lines.
> 
> Jules
> 
> Timo B. Hübel wrote:
> > Hello,
> >
> > I am using the very simple interactTCP example from [1] to play
> around with
> > Haskell network programming but I just can't get a simple client for
> that
> > example to work (it works like a charm with my telnet client, as
> described in
> > the article).
> >
> > This is what I am trying to do with the client:
> >
> >   main = withSocketsDo $ do
> >          hdl <- connectTo "localhost" (PortNumber 1234)
> >          hSetBuffering hdl NoBuffering
> >          hPutStr hdl "test message"
> >          res <- hGetContents hdl
> >          putStrLn (show res)
> >
> > The server looks like this:
> >
> >   interactTCP :: Int -> (String -> IO String) -> IO ()
> >   interactTCP port f = withSocketsDo $ do
> >           servSock <- listenOn $ PortNumber (fromIntegral port)
> >           waitLoop f servSock
> >
> >   waitLoop f servSock = do
> >           bracket (fmap (\(h,_,_)->h) $ accept servSock)
> >                   hClose
> >                   (\h -> do
> >                           hSetBuffering h NoBuffering
> >                           hGetContents h >>= f >>= hPutStr h)
> >           waitLoop f servSock
> >
> >   main = interactTCP 1234 (return . map toUpper)
> >
> > But is seems as some deadlocking occurs. Both programs just hang
> around doing
> > nothing. By inserting some debug output I was able to make sure that
> the
> > client successfully connects, but the data interchange just does not
> start.
> > Because the whole thing works using telnet, I suspect that I am doing
> > something fundamentally wrong in the client ...
> >
> > Any hints are greatly appreciated.
> >
> > Thanks,
> > Timo
> >
> > [1]
> >
> http://stephan.walter.name/blog/computers/programming/haskell/interactt
> cp.html
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 
> 
> --
> Internal Virus Database is out-of-date.
> Checked by AVG Free Edition.
> Version: 7.5.516 / Virus Database: 269.19.9/1239 - Release Date:
> 1/23/2008 10:24 AM




More information about the Haskell-Cafe mailing list