Haskell poker server

Folks, 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 ;). 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 get a message from Erlang once data arrives over TCP and the message is a {tcp, Socket, Bin} tuple where Bin is binary data. I can easily extract what I need using Erlang binary pattern matching: read(<<24, GID:32, Seq:16>>) -> {24, GID, Seq}. My code shoots tuples like {24, GID, Seq} back and forth and all is fine. How would I do this in Haskell, though? Some folks have kindly supplied me with references to the various binary I/O packages and some server examples. 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. Thanks, Joel -- http://wagerlabs.com/tech

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

Alistair, Thanks alot for your examples. I still have one unanswered question... How would you read a tuple of values (24, GID, Seq) like in my Erlang example, where 24 is one byte, GID is a 4-byte integer and Seq is a 2- byte word? Is there an elegant way of specifying packet format and reading/writing Haskell data according to it? Thanks, Joel On Aug 28, 2005, at 11:58 PM, Alistair Bayley wrote:
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.

Well, here's an attempt at a start on a similar mechanism for Haskell:
---------- (start Packet.hs)
module Packet where
import Data.Bits
import Data.Word
concatBits :: (Integral a, Bits a, Bits b) => [a] -> b
concatBits [] = 0
concatBits (x:xs) = shift (fromIntegral x) (sum (map bitSize xs)) +
concatBits xs
class Packet a where
readPacket :: [Word8] -> (a, [Word8])
instance Packet Word8 where
readPacket (x:xs) = (x,xs)
instance Packet Word16 where
readPacket xs = let (ys, zs) = splitAt 2 xs in (concatBits ys, zs)
instance Packet Word32 where
readPacket xs = let (ys, zs) = splitAt 4 xs in (concatBits ys, zs)
instance Packet Word64 where
readPacket xs = let (ys, zs) = splitAt 8 xs in (concatBits ys, zs)
instance (Packet a, Packet b) => Packet (a,b) where
readPacket xs = let (u, xs') = readPacket xs
(v, xs'') = readPacket xs'
in ((u,v), xs'')
instance (Packet a, Packet b, Packet c) => Packet (a,b,c) where
readPacket xs = let (u, xs') = readPacket xs
(v, xs'') = readPacket xs'
(w, xs''') = readPacket xs''
in ((u,v,w), xs''')
instance (Packet a) => Packet [a] where
readPacket [] = ([],[])
readPacket xs = let (u, xs') = readPacket xs
in (u : fst (readPacket xs'), [])
-------- (end Packet.hs)
With this you can convert lists of Word8's into particular structured
forms as you see fit. Additional instances of Packet can be added for
other types as needed. (As an easy example, if you have a GID newtype
based on Word32, you could just add Packet to the deriving clause,
assuming GHC extensions.)
For example:
readPacket [24,182,64,43,53,10,1]
:: ((Word8,Word32,Word16), [Word8])
== ((24,3057658677,2561),[])
readPacket [24,182,64,43,53,10,1,24,197,17,34,200,10,2]
:: ((Word8,Word32,Word16), [Word8])
== ((24,3057658677,2561),[24,197,17,34,200,10,2])
readPacket [24,182,64,43,53,10,1,24,197,17,34,200,10,2]
:: ([(Word8,Word32,Word16)], [Word8]) -- note the list type
== ([(24,3057658677,2561),(24,3306234568,2562)],[])
Anyway, I hope this is useful :)
- Cale
On 28/08/05, Joel Reymont
Alistair,
Thanks alot for your examples. I still have one unanswered question...
How would you read a tuple of values (24, GID, Seq) like in my Erlang example, where 24 is one byte, GID is a 4-byte integer and Seq is a 2- byte word? Is there an elegant way of specifying packet format and reading/writing Haskell data according to it?
Thanks, Joel
On Aug 28, 2005, at 11:58 PM, Alistair Bayley wrote:
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.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello Joel, Monday, August 29, 2005, 3:08:31 AM, you wrote: JR> How would you read a tuple of values (24, GID, Seq) like in my Erlang JR> example, where 24 is one byte, GID is a 4-byte integer and Seq is a 2- JR> byte word? Is there an elegant way of specifying packet format and JR> reading/writing Haskell data according to it? of course - it's a various Binary packages! :) direct way to read/write values from memory is Foreign.Storable module, which has provision for Int8,Int16,Int32,Int64,Word8,Word16,Word32,Word64 and other fixed-size data formats, and Foreign.Ptr module, which supports pointer arithmetics sorry if you need more high-level package, currently we have no such beast -- Best regards, Bulat mailto:bulatz@HotPOP.com

On Mon, Aug 29, 2005 at 01:08:31AM +0200, Joel Reymont wrote:
Alistair,
Thanks alot for your examples. I still have one unanswered question...
How would you read a tuple of values (24, GID, Seq) like in my Erlang example, where 24 is one byte, GID is a 4-byte integer and Seq is a 2- byte word? Is there an elegant way of specifying packet format and reading/writing Haskell data according to it?
If you don't actually need a binary format (or don't care about the format) you can use the 'Show' and 'Read' classes to turn values into strings and back again. so, you would do a show on one side and send the string, and then on the other side 'read' it and you will get the same value out. Instances exist for all built in types where it makes sense, and you can automatically derive instances for your own types. John -- John Meacham - ⑆repetae.net⑆john⑈
participants (5)
-
Alistair Bayley
-
Bulat Ziganshin
-
Cale Gibbard
-
Joel Reymont
-
John Meacham