
Hi all, Can anyone help me with some Haskell de/serialisation woes I'm encountering? What I'm trying to do it implement a proprietary network protocol which will enable me to talk to a network Java/Tuple Space. Specifically, I'm trying to serialise a "TypeStructurePreamble" and send that down the Handle (my network stream), I'm then expecting the Space to send me a TypeStructurePreamble back again, but with different data. So I need to de/serialise this type. I've not got all the code together yet, because I'm trying to figure out the concepts rather than any particular coding problem. Here's some code I have so far; import System.IO (hGetLine,hClose,hPutStrLn,hSetBuffering,BufferMode(..),Handle,stdout) import Data.Binary.Get import qualified Data.ByteString.Lazy as L type TypeStructurePreamble = (String,Int,[String]) -- This function I know works because it was spoon-fed to me by someone on this list! :-) readStrings :: Int -> Get [String] readStrings n = replicateM n $ do len <- getWord32be name <- getByteString $ fromIntegral len return $ UTF.toString name deserialisePreamble :: Get(String, Int, [String]) deserialisePreamble = do len <- getWord32be typename <- getByteString $ fromIntegral len c <- getWord32be numFields <- getWord32be fields <- readStrings (fromIntegral numfields) return (typename,c,numFields) -- not sure what this type should be serialisePreamble :: Handle -> TypeStructurePreamble -> ?? serialisePreamble h (n,c,fs) = do L.hPut h (encode (0xFAB1000A :: Word32)) L.hPut h (encode (length n)) L.hPut h (encode n) L.hPut h (encode (c :: Word32)) L.hPut h (encode (length fs)) -- not sure how I would L.hPut out every String in fs It is my (maybe wrong) understanding that these de/serialise functions don't actually do the work, they basically just form a description of what must be done in order to get the work done, so I'm slightly confused on how I should use it. For example; main = do -- set up Handle called h here, I know how to do this serialisePreamble h ("MyType",0,["field1","field2"]) --now I'm expecting to be able to read a modified TypeStructurePreamble from h (n,c,fs) <- deserialisePreamble -- but according to the type of deserialisePreamble, how does the h get into it? print "c was "+c -- can I just slot sout style statements into here? evaluate (n,c,fs) hClose h return (n,c,fs) Does this make sense? Can someone help me fill in the blanks of serialisePreamble and main? I've read the tutorials on the Get monad which google turns up, am I missing some really good ones? Is there some other resource which I'm missing? I'm been thrown a lot of the Hackage documentation on these things but (assuming I'm looking in the right place) they seem to work more like JavaDocs and give the "what it does", rather than the "how it should be used". Many thanks, Tom

Hi Tom For the serializePreamble question... serialisePreamble would need to map over the list of strings. As you want to apply a monadic function to each value you would need monadic-map rather than regular map (:: (a->b) -> [a] -> [b]). Monad map comes in two flavours a) mapM :: (a -> m b) -> [a] -> m [b] b) mapM_ :: (a -> m b) -> [a] -> m () mapM_ is in some respects a "forgetful" version of mapM - it performs the actions but "forgets" the results. mapM_ is the one you want here as writing to handle in the IO monad is approximately :: a -> IO () Because Strings are length prefixed you will a helper function along the lines of serializeString :: Handle -> String -> IO () serializeString h s = do { L.hPut h (encode (length s)) ; mapM_ (\ch -> L.hPutChar h ch) s } Unfortunately using L.hPutChar isn't appropriate - it illustrates what you would have to do, but isn't the right way of doing it. If you are using String data from the Java world - its likely you will actually have to deal with some encoding - probably converting each char to a Word16 and writing a Word16 with the appropriate endian-ness. The Data.Binary.Put module has a function putByteString for writing (byte) strings. Unfortunately this is won't be appropriate either, as the data layout from putByteString is unlikely to match the layout that the Java tuple space expects. For your use case, you will have to make some "primitive" output functions yourself.
participants (2)
-
Stephen Tetley
-
Tom Hobbs