[Haskell-cafe] Correct parsers for bounded integral values

Viktor Dukhovni ietf-dane at dukhovni.org
Sun Jul 13 13:18:30 UTC 2025


On Sun, Jul 13, 2025 at 01:34:15PM +0200, Stefan Klinger wrote:

> I've been bugged by the silent overflowing of integer parsers as
> provided by `base`, `attoparsec`, and others.  I'd go so far as to
> call it a bug when the user types `298` and the parser says `Right
> 42`.

Fortunately, silent overflow when parsing bounded integers is not a
behaviour of either the ByteString or streaming-bytestring libraries.

    $ ghci -v0
    λ> import Data.ByteString.Char8
    λ> :t readInt8
    readInt8 :: ByteString -> Maybe (GHC.Internal.Int.Int8, ByteString)
    λ> readInt8 $ pack "42 foo"
    Just (42," foo")
    λ> readInt8 $ pack "342 foo"
    Nothing
    λ> readInt16 $ pack "342 foo"
    Just (342," foo")
    λ> readInt16 $ pack "76342 foo"
    Nothing
    λ> readInt32 $ pack "76342 foo"
    Just (76342," foo")
    λ> readInt32 $ pack "9876531042 foo"
    Nothing
    λ> readInt64 $ pack "9876531042 foo"
    Just (9876531042," foo")

The bytestring library also supports the various Word sizes, Integer and
Natural!

Similarly, (be it for just the Int type):

    [viktor at chardros m]$ cabal repl -z -v0 --build-depend streaming-bytestring
    λ> import Streaming.ByteString.Char8
    λ> import Data.Functor.Of
    λ> import Data.Functor.Compose
    λ> import Data.Bifoldable
    λ> (x :> _) <-  getCompose <$> readInt (string "42 foo")
    λ> print x
    Just 42
    λ> (x :> _) <-  getCompose <$> readInt (string "9876543210987654210 foo")
    λ> print x
    Nothing

> Unfortunately, all parsing libraries I've looked at get this wrong.  A
> [solution][4] is proposed below.

There were more libraries to look at.

-- 
    Viktor.


More information about the Haskell-Cafe mailing list