
Hi all, Can anyone help me with this problem I'm been banging my head against for a while? I have a stream of bytes that I want to read, the stream is formatted thus; null, null, null, 4, 'd', 'a', 't', 'a'<end of stream> Where the first four bytes tell me the number of bytes I should read next in order to get some string value. What I have is code similar to the following; readFromStream address port = do h <- connectTo address (PortNumber port) hSetBuffering h NoBuffering L.hPut h (encode (0xFAB10000 :: Word32)) p <- L.hGet h 4 readData h (extractInt((L.unpack p))) extractInt = foldl addDigit 0 where addDigit num d = 10*num + d readData h c = do print c s <- L.hGet h c print s (Note: extractInt is largely copied from a Stack Overflow answer to something else.) The problem with this code in GHCI is; Couldn't match expected type `Int' against inferred type `Word8' In the second argument of `readData', namely `(extractInt ((L.unpack p)))' In a stmt of a 'do' expression: readData h (extractInt ((L.unpack p))) In the expression: do { h <- connectTo a (PortNumber p); hSetBuffering h NoBuffering; L.hPut h (encode (4205903872 :: Word32)); p <- L.hGet h 8; .... } I read this as saying that readData was expecting an Int, but instead extractInt returned it a Word8. How do I fix extractInt to return an Int rather than a Word8? Or is my problem something else? Some other things that bother me is my repeating use of 'do'. How can I go about breaking these functions out of being monadic and instead being pure? Is that something I should be striving for, because otherwise I can see every function I write here being in a 'do' block. Also, the final line of readFromStream bothers me. I feel like I'm starting to violate some similar form of the Lay of Demeter. (spelling?) I don't like writing code that looks like "f1 (f2 (f3 (f4 (f5 e))))" even if that is what is officially going on, as a programmer I'd rather see named variables. How can I fix that inside of a 'do' block? Sorry, this is a bit of a brain dump, but I would really appreciate someone else's opinion. Many thanks, Tom -- Using Opera's revolutionary e-mail client: http://www.opera.com/mail/

Hi Tom Try ... extractInt :: [Word8] -> Int extractInt = foldl addDigit 0 where addDigit num d = 10*num + (fromIntegral d) You might find you want to keep your functions monadic, and mostly use the Get monad from the module Data.Binary.Get for working with binary data.For instance there is a function getWord32be to do the work that extractInt is doing Best wishes Stephen

Further, Data.Binary is distributed with GHC but it isn't always an accessible module: you can see the module references in Haddock docs distributed with GHC, but you can't load the modules in your own projects (certainly on GHC 6.12.2 it is hidden). If this is the case for the GHC you are using, you have to get and install "binary" from Hackage. http://hackage.haskell.org/package/binary Best wishes Stephen

Hi Stephen,
Thanks for the answer, I shall give it a go later tonight (UK time).
Why would I want to keep my functions monadic? It's not that I'm against
the idea, rather it's that I don't understand the choice. I was under the
(possibly wrong) impression that (IO) monadic functions were just to "get
around" the issue of side-effects and that where possible functions should
be coded outside of monads. Is that just plain wrong, or does it boil down
to "It depends on what you're doing, and in this case..."?
Also I think I've already encountered the hidden Data.Binary problem in GHC.
I have got around it already by (if memory serves) starting GHC and telling
it to ignore it's own Data.Binary so I can then include it in my own
projects. But I created an alias which starts this Data.Binary-capable GHC
and I can't remember what's behind it now!
What's the reason for GHC hiding packages and preventing them from being
imported/used in loaded projects?
Thanks again for the help.
Tom
On Tue, Jun 15, 2010 at 9:15 PM, Stephen Tetley
Hi Tom
Try ...
extractInt :: [Word8] -> Int extractInt = foldl addDigit 0 where addDigit num d = 10*num + (fromIntegral d)
You might find you want to keep your functions monadic, and mostly use the Get monad from the module Data.Binary.Get for working with binary data.For instance there is a function getWord32be to do the work that extractInt is doing
Best wishes
Stephen

On 16 June 2010 08:40, Tom Hobbs
Hi Stephen,
Thanks for the answer, I shall give it a go later tonight (UK time). Why would I want to keep my functions monadic? It's not that I'm against the idea, rather it's that I don't understand the choice. I was under the (possibly wrong) impression that (IO) monadic functions were just to "get around" the issue of side-effects and that where possible functions should be coded outside of monads. Is that just plain wrong, or does it boil down to "It depends on what you're doing, and in this case..."?
Hi Tom Yes - its a "depend on what your doing" thing... For reading binary data, having a set of functions to read different types of data provides a nice interface. Data.Binary.Get provides some - e.g. getWord8, getWord32,... - and they are all in the Get monad. For a particular domain you would want to construct the parsers for that domain - but still keep them in the Get monad so you would keep the uniform interface. E.g., say if you had a structure for IP address, stored without the dots: data IPAddr = IPAddr Word8 Word8 Word8 Word8 getIPAddr :: Get IPAddr getIPAdde = do { a <- getWord8 ; b <- getWord8 ; c <- getWord8 ; d <- getWord8 ; return (IPAddr a b c d) } In you original code, the extractInt function is a good candidate to be a "Get" function rather than a a function that turns [Word8] data into an Int - i.e. I would make it do some parsing work rather than just the data conversion. As you are always reading 4 bytes and its big endian (I think?), I would adapt the existing getWord32be parser: extractInt :: Get Int extractInt = do { a <- getWord32be ; return (fromIntegral a) } Or more succinctly: extractInt :: Get Int extractInt = liftM fromIntegral getWord32be liftM, liftM2 are a family of functions that post-process the value (or values) returned from monadic operation(s) with a pure function (here fromIntegral). Of course, this will mean that the other code will have to be changed to use Data.Binary.Get but the end result should be cleaner code.
Also I think I've already encountered the hidden Data.Binary problem in GHC. I have got around it already by (if memory serves) starting GHC and telling it to ignore it's own Data.Binary so I can then include it in my own projects. But I created an alias which starts this Data.Binary-capable GHC and I can't remember what's behind it now! What's the reason for GHC hiding packages and preventing them from being imported/used in loaded projects?
GHC used to ship with a lot of libraries, but that was a large maintenance effort and now the Haskell Platform does this job. However, GHC is self-contained, so it still ships versions of the third-party libraries it uses internally (base, containers, the cabal-libraries but not the "cabal install" the tool...). I think Data.Binary is a more recent dependency, and its perhaps just an accident that it is half in / half out. Best wishes Stephen

On Jun 16, 2010, at 03:40 , Tom Hobbs wrote:
Why would I want to keep my functions monadic? It's not that I'm against the idea, rather it's that I don't understand the choice. I was under the (possibly wrong) impression that (IO) monadic functions were just to "get around" the issue of side-effects and that where possible functions should be coded outside of monads. Is that just plain wrong, or does it boil down to "It depends on what you're doing, and in this case..."?
Not all monads are IO. In this particular case, you'd be using the Get monad, which is essentially a custom State monad that carries deserialization state around for you. Avoiding IO is usually a good idea. But monads are your friends; state monads in particular get you out of a lot of boilerplate code, and Reader does the same with some useful localization capabilities. Writer is good for trace/log information; Maybe / Error / Cont are good for short-circuiting evaluation without building unwieldy case/if ladders, and Error is in particular good for pure "exceptions". Etc. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Tom Hobbs wrote:
I have a stream of bytes... Where the first four bytes tell me the number of bytes I should read next in order to get some string value...
What I have is code similar to the following;
readFromStream address port = do h <- connectTo address (PortNumber port) hSetBuffering h NoBuffering L.hPut h (encode (0xFAB10000 :: Word32)) p <- L.hGet h 4 readData h (extractInt((L.unpack p)))
extractInt = foldl addDigit 0 where addDigit num d = 10*num + d
readData h c = do print c s <- L.hGet h c print s
You're looking for the binary package. That is a general library for encoding and decoding of binary data streams via lazy bytestrings. http://hackage.haskell.org/package/binary Then you can write: import Data.Binary.Get ... n <- fmap (runGet word32be) $ L.hGet h 4 theString <- L.hGet h n This gives you theString as a lazy bytestring, of course. You take it from there. Regards, Yitz
participants (5)
-
Brandon S. Allbery KF8NH
-
Stephen Tetley
-
Tom Hobbs
-
Tom Hobbs
-
Yitzchak Gale