Haskell Networking Example
David Sankel
camio@yahoo.com
Wed, 2 Apr 2003 07:49:46 -0800 (PST)
Hello All,
Here is an example of using haskell networking
operations for those interested. The implementation
is a simple echo server.
echoclient.hs:
module Main( main ) where
import Network
import IO
import Control.Concurrent
main :: IO ()
main = withSocketsDo $ --For windows compatibility
do
handle <- connectTo "localhost" (PortNumber 2048)
input <- getContents
sequence_ $ map ( \a -> do
hPutStr handle $ a ++ "\n"
hFlush handle ) $ lines input
hClose handle
echoserver.hs:
module Main( main ) where
import Network
import IO
import Control.Concurrent
main :: IO ()
main = withSocketsDo $ --For windows compatibility
do
theSocket <- listenOn (PortNumber 2048)
sequence_ $ repeat $ acceptConnectionAndFork
theSocket
where
acceptConnectionAndFork :: Socket -> IO ()
acceptConnectionAndFork theSocket = do
connection <- accept theSocket
let (handle, hostname, portnumber ) = connection
putStr ("("++ hostname ++ ":" ++ (show
portnumber) ++ "): Open\n" )
forkIO (echoServer connection)
return ()
echoServer :: (Handle, String, PortNumber) -> IO ()
echoServer (handle, hostname, portnumber ) = do
a <- hGetContents handle
putStr $ foldr (++) "" $ map (\a -> "(" ++ hostname
++ ":"
++ (show portnumber) ++ "): Msg " ++ (show
a) ++ "\n" ) $ lines a
putStr ("("++ hostname ++ ":" ++ (show portnumber)
++ "): Close\n" )
Makefile:
all: echoclient echoserver
echoclient: echoclient.hs
ghc -package network echoclient.hs -o
echoclient
echoserver: echoserver.hs
ghc -package network echoserver.hs -o
echoserver
clean:
rm *.o *.hi echoclient echoserver