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)
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 appreciatedOn Tue, Nov 2, 2010 at 1:24 PM, Nils Schweinsberg <ml@n-sch.de> wrote:
Am 02.11.2010 19:57, schrieb Michael Litchard:Sure, see this short server-client-ping-pong application.
got any urls with examples?
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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe