[Haskell-cafe] Re: Comments on reading two ints off Bytestring
Isaac Dupree
isaacdupree at charter.net
Sun Dec 23 07:44:57 EST 2007
-- 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 <pocm at soton.ac.uk> 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
>>
>
>
>
More information about the Haskell-Cafe
mailing list