Network on Win98: failed - socket - no error ??
Claus Reinke
claus.reinke@talk21.com
Mon, 3 Mar 2003 14:28:29 -0000
> Did you remember to use 'withSocketsDo'? If you
> did, it would help to see the code that's failing
> for you (trivial or not.)
Did. But you're right, of course, so here's the current code.
Claus
-- Server.hs
module Main where
import Network
import IO
import System
main = withSocketsDo $ do
(pnum:_) <- getArgs
let p = fromIntegral $ read pnum
s <- listenOn $ PortNumber p
(h, host, portnr) <- accept s
hSetBuffering h LineBuffering
loop h
where
loop h = do
l <- hGetLine h
putStrLn $ "SERVER: "++l
loop h
-- Client.hs
module Main where
import Network
import IO
import System
main = withSocketsDo $ do
(pnum:_) <- getArgs
let p = fromIntegral $ read pnum
h <- connectTo "localhost" $ PortNumber p
hSetBuffering h LineBuffering
loop h
where
loop h = do
l <- getLine
putStrLn $ "CLIENT: "++l
hPutStrLn h l
loop h
> ----- Original Message -----
> From: "Claus Reinke" <claus.reinke@talk21.com>
> To: <glasgow-haskell-users@haskell.org>
> Sent: Monday, March 03, 2003 04:14
> Subject: Network on Win98: failed - socket - no error ??
>
>
> > I'm playing with the Network library (the recommended portable way?) and
> > have a surprising problem with a simple client/server example. As the same
> > program works fine on Solaris and Win2k, I suspect its a standard
> "feature"
> > and someone here with more network programming experience might be
> > able to enlighten me?
> >
> > - Server: listenOn port, then accept handle and enter loop, echoing from
> > handle to stdout
> > - Client: connectTo "localhost" port, then enter loop echoing from
> > stdin to handle
> >
> > Both programs work on Solaris and Win2k, but fail on Win98, with:
> >
> > Fail: failed
> > Action: socket
> > Reason: No error
> >
> > which would be merely amusing, I guess, if I knew what it meant, and
> > what to do about it?
> >
> > Cheers,
> > Claus
> >
> > _______________________________________________
> > Glasgow-haskell-users mailing list
> > Glasgow-haskell-users@haskell.org
> > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>