[Haskell-cafe] windows network programming

Michael Litchard michael at schmong.org
Fri Jan 21 04:48:18 CET 2011


freenode figured this out. Pasting here for future reference.


import Control.Concurrent
import Network
import System.IO

main :: IO ()
main = withSocketsDo $ do
    m <- newEmptyMVar
    forkIO (waitAndPong m)
    ping m

-- The basic server
waitAndPong :: MVar () -> IO ()
waitAndPong m = do
    socket <- listenOn (PortNumber 8000)
    putMVar m ()
    (handle,_,_) <- accept socket
    hSetBuffering handle LineBuffering
    incoming <- hGetLine handle
    putStrLn ("> " ++ incoming)
    hPutStrLn handle "pong"

-- The basic client
ping :: MVar () -> IO ()
ping m = do
    _ <- takeMVar m
    handle <- connectTo "localhost" (PortNumber 8000)
    hSetBuffering handle LineBuffering
    hPutStrLn handle "ping"
    incoming <- hGetLine handle
    putStrLn ("< " ++ incoming)


On Thu, Jan 20, 2011 at 6:17 PM, Michael Litchard <michael at schmong.org>wrote:

> I tried this as an example and got the following error when running.
>
> net.exe: connect: failed (Connection refused (WSAECONNREFUSED))
>
> Firewall is off, running as administrator
>
> Windows is Windows 7 Enterprise.
>
> Advice on what to do next is appreciated
>
>
> On Tue, Nov 2, 2010 at 1:24 PM, Nils Schweinsberg <ml at n-sch.de> wrote:
>
>> Am 02.11.2010 19:57, schrieb Michael Litchard:
>>
>>  got any urls with examples?
>>>
>>
>> Sure, see this short server-client-ping-pong application.
>>
>> By the way, I noticed that you don't need withSocketsDo on windows 7, but
>> I guess it's there for a reason for older windows versions. :)
>>
>>
>>
>>    import Control.Concurrent
>>    import Network
>>    import System.IO
>>
>>    main :: IO ()
>>    main = withSocketsDo $ do
>>        forkIO waitAndPong
>>        ping
>>
>>    -- The basic server
>>    waitAndPong :: IO ()
>>    waitAndPong = do
>>        socket <- listenOn (PortNumber 1234)
>>        (handle,_,_) <- accept socket
>>        hSetBuffering handle LineBuffering
>>        incoming <- hGetLine handle
>>        putStrLn ("> " ++ incoming)
>>        hPutStrLn handle "pong"
>>
>>    -- The basic client
>>    ping :: IO ()
>>    ping = do
>>        handle <- connectTo "localhost" (PortNumber 1234)
>>        hSetBuffering handle LineBuffering
>>        hPutStrLn handle "ping"
>>        incoming <- hGetLine handle
>>        putStrLn ("< " ++ incoming)
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110120/02dd0d81/attachment.htm>


More information about the Haskell-Cafe mailing list