
I wrote a poker server in Erlang (link in signature) and I'm learning Haskell with an eye towards using it with Erlang. Erlang would take care of the overall control, etc. whereas Haskell would take care of the rest. I'm stuck with the basics I'm afraid and Haskell hackers don't seem to be active this weekend ;).
There's a public holiday on Monday in the UK; I don't know about other European states... I should have mentioned darcs: http://darcs.net/ A distributed revision control system is bound to contain some good networking examples.
I'm trying to write the poker server in Haskell to compare against my other implementations, specifically the Erlang one. The server talks a binary protocol. A packet notifying the player that a game has started looks like this:
0 1 5 7 +----+-----+-----+ | 24 | GID | Seq | +----+-----+-----+
I'm wondering, though, if someone would be kind enough to show how a packet like above could be sent and retrieved using Haskell sockets. I think this would serve as an excellent example to be posted at the Haskell Wiki. I also think that Haskell has a lot of interesting features that could well simplify my poker coding. I just need a little help to get started.
Below is a contrived, non-optimal first attempt. The server just reads seven bytes from the socket, prints them, and quits. And the client just sends seven bytes and quits. This is not good example code from just about any POV (for example: the client sending a byte-at-a-time, no interrupt masks, no exception handling), but it does show that you can send and receive bytes. The possibly dismaying thing is that you need code from networking, IO, and FFI libraries, so there are quite a few API's to digest. ----------------------- module Server where import Network import System.IO import Foreign.Marshal.Alloc import Foreign.Storable import Foreign.Ptr import Data.Word import Control.Monad (when) main = withSocketsDo run run = do sock <- listenOn (PortNumber 8080) (handle, _, _) <- accept sock getSevenBytes handle hClose handle sClose sock getSevenBytes handle = do allocaBytes 7 $ \buffer -> do readCount <- hGetBuf handle buffer 7 printBytes buffer (readCount-1) printBytes buffer count = printByte buffer count 0 printByte buffer count n = do b <- peekByteOff buffer n -- tell compiler what type of data is in buffer: Word8 let byte :: Word8; byte = b putStrLn $ "Byte " ++ (show n) ++ ": " ++ (show byte) when (count > n) (printByte buffer count (n+1)) ---------------------- module Client where import Network import System.IO import Foreign.Storable import Foreign.Marshal.Alloc import Data.Word main = withSocketsDo $ do handle <- connectTo "localhost" (PortNumber 8080) putByte handle 24 putByte handle 1 putByte handle 2 putByte handle 3 putByte handle 4 putByte handle 5 putByte handle 6 hClose handle putByte :: Handle -> Word8 -> IO () putByte handle byte = do allocaBytes 1 $ \buffer -> do poke buffer byte hPutBuf handle buffer 1