[Haskell-beginners] De-serialising with minimal code noise and fluff... possible?

Sean Charles sean at objitsu.com
Wed Apr 4 00:26:55 CEST 2012


Hi list,

to further my haskell skills I decided to produce my own raw MySQL 
connection. So far I can connect to the server and extract the handshake 
initialisation packet (HIP) and create the client authentication packet. 
Once I've figured out how to implement the salting and hashing I have a 
chance of starting a session. Not a problem, just got to do it. I want a 
module that I can use for simple DBMS I/O that doesn't use libmysql or 
odbc as sometimes these things just refuse to install on certain 
platform / architecture combinations!

So, here's my problem: I kind of understand monads, I can use them and 
appreciate what/why they are useful etc. but my current implementation 
of reading the HIP into the type I created (shown next) appears to me at 
least to be plain clunky, ugly and inelegant compared to ninja haskell 
code I've read and one day hope to match, here's my code... apologies 
for the length of the post but I hope it's interesting to some!

data PktHIP = PktHIP
               { hipProtoVer :: Int
               , hipSvrVer   :: String
               , hipThreadId :: Int
               , hipScramble :: BS.ByteString
               , hipSvrCaps  :: Integer
               , hipSvrLang  :: Int
               , hipSvrStat  :: Int
               , hipScramLen :: Int
               , hipPlugin   :: String
               } deriving(Show)

and reading it...

getHIP :: Handle -> IO PktHIP
getHIP h = do
   ver <- streamInt h 1
   str <- getNTS h
   tid <- streamInt h 4
   buf <- BS.hGet h 8
   BS.hGet h 1 -- filler
   scap1 <- streamInt h 2
   slang <- streamInt h 1
   sstat <- streamInt h 2
   scap2 <- streamInt h 2
   scrln <- streamInt h 1
   BS.hGet h 10 -- filler
   scram <- getNTS h
   -- todo: there *has* to be a more concise way of doing this?
   return $
     PktHIP { hipProtoVer = ver
            , hipSvrVer   = str
            , hipThreadId = tid
            , hipScramble = buf
            , hipSvrCaps  = fromIntegral scap1 -- scap2 << 2 ? TODO!
            , hipSvrLang  = slang
            , hipSvrStat  = sstat
            , hipScramLen = scrln
            , hipPlugin   = scram
            }

-- Extract an N byte Int value from the input stream
streamInt :: Handle -> Int -> IO Int
streamInt h len = liftM bsVal $ BS.hGet h len

bsVal :: BS.ByteString -> Int
bsVal = BS.foldr' (\byte total ->  fromEnum byte + (shiftL total 8)) 0

-- Get a Null-Terminated String
getNTS :: Handle -> IO String
getNTS h = streamInt h 1 >>= \b -> getString h "" b
            where
              getString :: Handle -> String -> Int -> IO String
              getString h acc c
                | c == 0  = return $ reverse acc
                | otherwise = streamInt h 1 >>= getString h ((chr c):acc)


Then I read about the Data.Binary package and the Get monad and got this 
far...

readHIP :: Get (Maybe PktHIP)
readHIP = do
   return (Nothing)

I looked at the example on this page: 
http://www.haskell.org/haskellwiki/DealingWithBinaryData , I stopped 
because I realised that the Get monad was only going to mean I ended up 
with very similarly structured code and probably  a lot of it. I know 
the PktHIP has lots of fields but even so I am convinced it can be 
reduced and re-factored into much more beautiful code that I know how to 
write so far.

I've tried to reason about it and I can "see" that there is a function 
out there that takes a Handle and "a record modifier function" and I can 
see also that it might be time for me to create my first Monad type ever
IIUC, by implementing >>=, >> and return and I make use of the many 
monad centric modules that exist but I also am under the impression that 
I can add as many other functions to my Monad class as I need to do what 
I need to do, is that correct?

I would therefore like some way to create an initial "thing" that 
contains the handle passed in to the function so that the >>= 
invocations can be as clean as possible because somewhere in my mind I 
can feel code resembling something like this:

getHIP :: Handle -> MyMonad PktHIP
getHIP h = do    -- science fiction code starts now!

     let rs = ... --- record state monad thing with "h" and "PktHIP"

     getInt 1 rs hipProtoVer >>
     getNTS   rs hipSvrVer >>
     getInt 4 rs hipThreadId >>
     getBS  8 rs hipScramble >>
     skip 1 >>
        :
        : ...etc
     return $ theHIP

getInt :: Int -> ST ? -> (PktHIP -> PktHIP) -> MyMonad PktHIP
getInt len state fmod = do
     val <- readStream ("h from state") len
let state' = modify state by setting field "fmod" to "val"
        return state'

Problems / things I am clueless about how to do here

   |1| how to create "something" that each >>= can modify (state monad 
instance?)
   |2| how to put the Handle "h" somewhere it can be read on each read 
action
   |3| everything else!!!

So, any ideas, examples etc. would be most enlightening and gratefully 
absorbed!
Sean Charles.
:)




More information about the Beginners mailing list