Comments on reading two ints off Bytestring

Hello all, It is either too difficult to get two integers of a bytestring, in which case something should be done to ease the process or I should learn much more Haskell. I guess the latter is the correct guess. I have a bytestring containing two naturals. I was to get them as efficiently as possible. Here's my code: parseHeader :: BS.ByteString -> (Int, Int) parseHeader bs = let first = BS.readInt $ BS.dropWhile (not . isDigit) bs in if(isNothing first) then error "Couldn't find first natural." else let second = BS.readInt $ BS.dropWhile (not . isDigit) $ snd $ fromJust first in if(isNothing second) then error "Couldn't find second natural." else (fst $ fromJust first, fst $ fromJust second) This seems to work:
parseHeader $ BS.pack "hello 252 359" (252,359)
Is there a better way? Cheers, -- Paulo Jorge Matos - pocm at soton.ac.uk http://www.personal.soton.ac.uk/pocm PhD Student @ ECS University of Southampton, UK

On Dec 23, 2007 12:32 PM, Paulo J. Matos
Hello all,
It is either too difficult to get two integers of a bytestring, in which case something should be done to ease the process or I should learn much more Haskell. I guess the latter is the correct guess.
I have a bytestring containing two naturals. I was to get them as efficiently as possible. Here's my code:
Just tried a better one, what do you think of this: parseHeader2 :: BS.ByteString -> (Int, Int) parseHeader2 bs = case (BS.readInt $ BS.dropWhile (not . isDigit) bs) of Nothing -> error "Couldn't find first natural." Just (x, rest) -> case (BS.readInt $ BS.dropWhile (not . isDigit) rest) of Nothing -> error "Couldn't find second natural." Just (y, _) -> (x, y)
parseHeader :: BS.ByteString -> (Int, Int) parseHeader bs = let first = BS.readInt $ BS.dropWhile (not . isDigit) bs in if(isNothing first) then error "Couldn't find first natural." else let second = BS.readInt $ BS.dropWhile (not . isDigit) $ snd $ fromJust first in if(isNothing second) then error "Couldn't find second natural." else (fst $ fromJust first, fst $ fromJust second)
This seems to work:
parseHeader $ BS.pack "hello 252 359" (252,359)
Is there a better way?
Cheers,
-- Paulo Jorge Matos - pocm at soton.ac.uk http://www.personal.soton.ac.uk/pocm PhD Student @ ECS University of Southampton, UK
-- Paulo Jorge Matos - pocm at soton.ac.uk http://www.personal.soton.ac.uk/pocm PhD Student @ ECS University of Southampton, UK

-- this should work too parseHeader3 :: BS.ByteString -> Maybe (Int, Int) --note accurate type signature, which helps us use Maybe failure-monad, --although losing your separate error messages parseHeader3 bs = do (x, rest) <- BS.readInt $ BS.dropWhile (not . isDigit) bs (y, _) <- BS.readInt $ BS.dropWhile (not . isDigit) rest return (x, y) --or to be clearer without syntactic sugar, that is parseHeader3 bs = (BS.readInt $ BS.dropWhile (not . isDigit) bs) >>= \(x, rest) -> (BS.readInt $ BS.dropWhile (not . isDigit) rest) >>= \(y, _) -> return (x, y) Isaac Paulo J. Matos wrote:
On Dec 23, 2007 12:32 PM, Paulo J. Matos
wrote: Hello all,
It is either too difficult to get two integers of a bytestring, in which case something should be done to ease the process or I should learn much more Haskell. I guess the latter is the correct guess.
I have a bytestring containing two naturals. I was to get them as efficiently as possible. Here's my code:
Just tried a better one, what do you think of this: parseHeader2 :: BS.ByteString -> (Int, Int) parseHeader2 bs = case (BS.readInt $ BS.dropWhile (not . isDigit) bs) of Nothing -> error "Couldn't find first natural." Just (x, rest) -> case (BS.readInt $ BS.dropWhile (not . isDigit) rest) of Nothing -> error "Couldn't find second natural." Just (y, _) -> (x, y)
parseHeader :: BS.ByteString -> (Int, Int) parseHeader bs = let first = BS.readInt $ BS.dropWhile (not . isDigit) bs in if(isNothing first) then error "Couldn't find first natural." else let second = BS.readInt $ BS.dropWhile (not . isDigit) $ snd $ fromJust first in if(isNothing second) then error "Couldn't find second natural." else (fst $ fromJust first, fst $ fromJust second)
This seems to work:
parseHeader $ BS.pack "hello 252 359" (252,359)
Is there a better way?
Cheers,
-- Paulo Jorge Matos - pocm at soton.ac.uk http://www.personal.soton.ac.uk/pocm PhD Student @ ECS University of Southampton, UK

On Dec 23, 2007 12:44 PM, Isaac Dupree
-- this should work too parseHeader3 :: BS.ByteString -> Maybe (Int, Int) --note accurate type signature, which helps us use Maybe failure-monad, --although losing your separate error messages
Oh gee, I just noticed that my type sig is in fact not correct. How come GHC doesn't complain?
parseHeader3 bs = do (x, rest) <- BS.readInt $ BS.dropWhile (not . isDigit) bs (y, _) <- BS.readInt $ BS.dropWhile (not . isDigit) rest return (x, y)
What happens then if the first BS.readInt return Nothing???
--or to be clearer without syntactic sugar, that is parseHeader3 bs = (BS.readInt $ BS.dropWhile (not . isDigit) bs) >>= \(x, rest) -> (BS.readInt $ BS.dropWhile (not . isDigit) rest) >>= \(y, _) -> return (x, y)
Isaac
Paulo J. Matos wrote:
On Dec 23, 2007 12:32 PM, Paulo J. Matos
wrote: Hello all,
It is either too difficult to get two integers of a bytestring, in which case something should be done to ease the process or I should learn much more Haskell. I guess the latter is the correct guess.
I have a bytestring containing two naturals. I was to get them as efficiently as possible. Here's my code:
Just tried a better one, what do you think of this: parseHeader2 :: BS.ByteString -> (Int, Int) parseHeader2 bs = case (BS.readInt $ BS.dropWhile (not . isDigit) bs) of Nothing -> error "Couldn't find first natural." Just (x, rest) -> case (BS.readInt $ BS.dropWhile (not . isDigit) rest) of Nothing -> error "Couldn't find second natural." Just (y, _) -> (x, y)
parseHeader :: BS.ByteString -> (Int, Int) parseHeader bs = let first = BS.readInt $ BS.dropWhile (not . isDigit) bs in if(isNothing first) then error "Couldn't find first natural." else let second = BS.readInt $ BS.dropWhile (not . isDigit) $ snd $ fromJust first in if(isNothing second) then error "Couldn't find second natural." else (fst $ fromJust first, fst $ fromJust second)
This seems to work:
parseHeader $ BS.pack "hello 252 359" (252,359)
Is there a better way?
Cheers,
-- Paulo Jorge Matos - pocm at soton.ac.uk http://www.personal.soton.ac.uk/pocm PhD Student @ ECS University of Southampton, UK
-- Paulo Jorge Matos - pocm at soton.ac.uk http://www.personal.soton.ac.uk/pocm PhD Student @ ECS University of Southampton, UK

On Dec 24, 2007 11:55 AM, Paulo J. Matos
On Dec 23, 2007 12:44 PM, Isaac Dupree
wrote: -- this should work too parseHeader3 :: BS.ByteString -> Maybe (Int, Int) --note accurate type signature, which helps us use Maybe failure-monad, --although losing your separate error messages
Oh gee, I just noticed that my type sig is in fact not correct. How come GHC doesn't complain?
parseHeader3 bs = do (x, rest) <- BS.readInt $ BS.dropWhile (not . isDigit) bs (y, _) <- BS.readInt $ BS.dropWhile (not . isDigit) rest return (x, y)
What happens then if the first BS.readInt return Nothing???
Ok, got it, I'm not returning a maybe. That's it then. Still, the first question remains... what happens to (x, rest) if BS.readInt returns Nothing. -- Paulo Jorge Matos - pocm at soton.ac.uk http://www.personal.soton.ac.uk/pocm PhD Student @ ECS University of Southampton, UK

2007/12/24, Paulo J. Matos
On Dec 24, 2007 11:55 AM, Paulo J. Matos
wrote: On Dec 23, 2007 12:44 PM, Isaac Dupree
wrote: -- this should work too parseHeader3 :: BS.ByteString -> Maybe (Int, Int) --note accurate type signature, which helps us use Maybe failure-monad, --although losing your separate error messages
Oh gee, I just noticed that my type sig is in fact not correct. How come GHC doesn't complain?
Your type is correct.
parseHeader3 bs = do (x, rest) <- BS.readInt $ BS.dropWhile (not . isDigit) bs (y, _) <- BS.readInt $ BS.dropWhile (not . isDigit) rest return (x, y)
What happens then if the first BS.readInt return Nothing???
Ok, got it, I'm not returning a maybe. That's it then. Still, the first question remains... what happens to (x, rest) if BS.readInt returns Nothing.
Your function return a Maybe (Int,Int), (x,y) is of type (Int,Int). If readInt return a nothing, the whole funtion will return a Nothing per (>>=) instance definition. -- Jedaï

Paulo J. Matos wrote:
On Dec 23, 2007 12:44 PM, Isaac Dupree
wrote: -- this should work too parseHeader3 :: BS.ByteString -> Maybe (Int, Int) --note accurate type signature, which helps us use Maybe failure-monad, --although losing your separate error messages
Oh gee, I just noticed that my type sig is in fact not correct. How come GHC doesn't complain?
well, it is correct for Haskell if you want program failure for parse failure... it's just not a _total_ function unless you use Maybe (which determines whether you can have the code that uses parseHeader decide what to do in the case of a failure)
parseHeader3 bs = do (x, rest) <- BS.readInt $ BS.dropWhile (not . isDigit) bs (y, _) <- BS.readInt $ BS.dropWhile (not . isDigit) rest return (x, y)
What happens then if the first BS.readInt return Nothing???
--or to be clearer without syntactic sugar, that is parseHeader3 bs = (BS.readInt $ BS.dropWhile (not . isDigit) bs) >>= \(x, rest) -> (BS.readInt $ BS.dropWhile (not . isDigit) rest) >>= \(y, _) -> return (x, y)
when the first one returns Nothing, the whole expression becomes Nothing without examining the later parts of computation (as Chaddaï said) Isaac

On Dec 24, 2007, at 13:18 , Isaac Dupree wrote:
Paulo J. Matos wrote:
On Dec 23, 2007 12:44 PM, Isaac Dupree
wrote: parseHeader3 bs = do (x, rest) <- BS.readInt $ BS.dropWhile (not . isDigit) bs (y, _) <- BS.readInt $ BS.dropWhile (not . isDigit) rest return (x, y) What happens then if the first BS.readInt return Nothing??? when the first one returns Nothing, the whole expression becomes Nothing without examining the later parts of computation (as Chaddaï said)
One thng that's not obvious here is that pattern match failure translates to a call to "fail", which in the definition of Monad for Maybe becomes Nothing. (Hm. Isaac: I thought that translation only happened for the "do" sugar, and in the direct case you must do it yourself or Haskell raises the "incomplete pattern match" exception?) -- 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

Brandon S. Allbery KF8NH wrote:
On Dec 24, 2007, at 13:18 , Isaac Dupree wrote:
Paulo J. Matos wrote:
On Dec 23, 2007 12:44 PM, Isaac Dupree
wrote: parseHeader3 bs = do (x, rest) <- BS.readInt $ BS.dropWhile (not . isDigit) bs (y, _) <- BS.readInt $ BS.dropWhile (not . isDigit) rest return (x, y) What happens then if the first BS.readInt return Nothing??? when the first one returns Nothing, the whole expression becomes Nothing without examining the later parts of computation (as Chaddaï said)
One thng that's not obvious here is that pattern match failure translates to a call to "fail", which in the definition of Monad for Maybe becomes Nothing.
(Hm. Isaac: I thought that translation only happened for the "do" sugar, and in the direct case you must do it yourself or Haskell raises the "incomplete pattern match" exception?)
Tuple-matching never fails (except for _|_) -- there's only one constructor. In this case it's only the intrinsic failure of BS.readInt. You're thinking of something like do [a,b] <- readListOfInts foo return (a+b) --readListOfInts is a function I made up :: String -> Maybe [Int] which can fail (1) if readListOfInts returns Nothing (2) because of the do-notation, also if the list doesn't have exactly two elements in it. Isaac

On Dec 23, 2007 1:44 PM, Isaac Dupree
parseHeader3 :: BS.ByteString -> Maybe (Int, Int) parseHeader3 bs = do (x, rest) <- BS.readInt $ BS.dropWhile (not . isDigit) bs (y, _) <- BS.readInt $ BS.dropWhile (not . isDigit) rest return (x, y)
But that version still itches! :-) This is what it sounds like to me: parseHeader :: BS.ByteString -> Maybe (Int,Int) parseHeader = evalStateT $ liftM2 (,) parseInt parseInt where parseInt = StateT $ BS.readInt . BS.dropWhile (not . isDigit) - Benja

On Dec 26, 2007 12:42 PM, Benja Fallenstein
parseHeader :: BS.ByteString -> Maybe (Int,Int) parseHeader = evalStateT $ liftM2 (,) parseInt parseInt where parseInt = StateT $ BS.readInt . BS.dropWhile (not . isDigit)
(oh, I missed Conal's mail which says the same thing) - Benja

Just curious -- how can this be done in Arrows instead of Manad/T? Or can it?
On Dec 26, 2007 6:42 AM, Benja Fallenstein
On Dec 23, 2007 1:44 PM, Isaac Dupree
wrote: parseHeader3 :: BS.ByteString -> Maybe (Int, Int) parseHeader3 bs = do (x, rest) <- BS.readInt $ BS.dropWhile (not . isDigit) bs (y, _) <- BS.readInt $ BS.dropWhile (not . isDigit) rest return (x, y)
But that version still itches! :-)
This is what it sounds like to me:
parseHeader :: BS.ByteString -> Maybe (Int,Int) parseHeader = evalStateT $ liftM2 (,) parseInt parseInt where parseInt = StateT $ BS.readInt . BS.dropWhile (not . isDigit)
- Benja
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Dec 23, 2007, at 7:35 , Paulo J. Matos wrote:
parseHeader2 :: BS.ByteString -> (Int, Int) parseHeader2 bs = case (BS.readInt $ BS.dropWhile (not . isDigit) bs) of Nothing -> error "Couldn't find first natural." Just (x, rest) -> case (BS.readInt $ BS.dropWhile (not . isDigit) rest) of Nothing -> error "Couldn't find second natural." Just (y, _) -> (x, y)
-- simple version, factor out common code parseHeader3 bs = let (x1,bs') = parse' bs "first" (x2,_ ) = parse' bs' "second" in (x1,x2) where parse' s es = case BS.readInt $ BS.dropWhile (not . isDigit) s of Nothing -> error $ "Couldn't find " ++ es ++ " natural." Just r -> r -- this one uses MonadError; result is Either String (Int,Int) parseHeader4 bs = do (x1,bs') <- parse'' bs "first" (x2,_ ) <- parse'' bs' "second" return (x1,x2) where parse'' s es = case BS.readInt $ BS.dropWhile (not . isDigit) s of Nothing -> fail $ "Couldn't find " ++ es ++ " natural." Just r -> return r -- 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

Hi
parseHeader $ BS.pack "hello 252 359" (252,359)
If this were strings, I'd start with: map read . words If you want to have error correction, I'd move to: mapM readMay . words (readMay comes from the safe package, http://www-users.cs.york.ac.uk/~ndm/safe/) I don't know about the bytestring bit, but I guess the functions all map over.
I have a bytestring containing two naturals. I was to get them as efficiently as possible. Here's my code:
Have you profiled your code and found that the parsing of two Int's from a bytestring is the performance critial bit? If not, I'd just keep it simple, and then optimise once you know where you should be optimising. Thanks Neil

Paulo J. Matos wrote:
I guess the latter is the correct guess.
Good guess! You can take advantage of the fact that the Maybe type is an instance of the Monad typeclass to chain those computations together, getting rid of all of the explicit case analysis. import qualified Data.ByteString.Char8 as B import Data.Char (isDigit) readTwoInts :: B.ByteString -> Maybe ((Int, Int), B.ByteString) readTwoInts r = do (a, s) <- B.readInt . B.dropWhile (not . isDigit) $ r (b, t) <- B.readInt . B.dropWhile (not . isDigit) $ s return ((a, b), t) Let's try that in ghci: *Main> readTwoInts (B.pack "hello 256 299 remainder") Just ((256,299)," remainder") The case analysis is still happening, it's just being done behind your back by the (>>=) combinator, leaving your code much tidier. (And why is there no explicit use of (>>=) above? Read about desugaring of "do" notation in the Haskell 98 report.) The learning you'll want to do, to be able to reproduce code such as the above, is about monads. Cheers,

To clean up even more, use StateT B.ByteString Maybe. Then the ByteString
threading will be invisible, leading to just "liftM2 (,) readI readI", for
suitably defined readI.
On Dec 23, 2007 6:45 AM, Bryan O'Sullivan
Paulo J. Matos wrote:
I guess the latter is the correct guess.
Good guess!
You can take advantage of the fact that the Maybe type is an instance of the Monad typeclass to chain those computations together, getting rid of all of the explicit case analysis.
import qualified Data.ByteString.Char8 as B import Data.Char (isDigit)
readTwoInts :: B.ByteString -> Maybe ((Int, Int), B.ByteString) readTwoInts r = do (a, s) <- B.readInt . B.dropWhile (not . isDigit) $ r (b, t) <- B.readInt . B.dropWhile (not . isDigit) $ s return ((a, b), t)
Let's try that in ghci:
*Main> readTwoInts (B.pack "hello 256 299 remainder") Just ((256,299)," remainder")
The case analysis is still happening, it's just being done behind your back by the (>>=) combinator, leaving your code much tidier. (And why is there no explicit use of (>>=) above? Read about desugaring of "do" notation in the Haskell 98 report.)
The learning you'll want to do, to be able to reproduce code such as the above, is about monads.
Cheers,
http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (9)
-
Benja Fallenstein
-
Brandon S. Allbery KF8NH
-
Bryan O'Sullivan
-
Chaddaï Fouché
-
Conal Elliott
-
Isaac Dupree
-
Neil Mitchell
-
Paulo J. Matos
-
Steve Lihn