[Haskell-cafe] Re: Comments on reading two ints off Bytestring

Brandon S. Allbery KF8NH allbery at ece.cmu.edu
Sun Dec 23 07:51:02 EST 2007


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 at kf8nh.com
system administrator [openafs,heimdal,too many hats] allbery at ece.cmu.edu
electrical and computer engineering, carnegie mellon university    KF8NH




More information about the Haskell-Cafe mailing list