Skip to main content

Overflow While Parsing IPv4 Addresses (Part 4)

Kazu Yamamoto asked about the IPv4 octet parsing subject to Int overflow bug in iproute, so I went ahead and implemented a fix. In doing so, I realized that I could improve the ip fix even further!

ip

In Overflow While Parsing IPv4 Addresses (Part 3), I first wrote the maybeDigitToInt function and then inlined it into the readOctet function. I failed to spot that the character range does not need to be checked in the go helper function because Char.isDigit guarantees that all of the characters are digits. The updated function is as follows:

readOctet :: TextRead.Reader Word
readOctet t = do
  let (digits, rest) = Text.span Char.isDigit t
  when (Text.null digits) $ Left "octet does not start with a digit"
  case Text.foldr go Just digits 0 of
    Just n  -> Right (fromIntegral n, rest)
    Nothing -> Left ipOctetSizeErrorMsg
  where
  go :: Char -> (Int -> Maybe Int) -> Int -> Maybe Int
  go !d !f !n =
    let n' = n * 10 + Char.ord d - 48
    in  if n' <= 255 then f n' else Nothing

(Note: This code is written to match the style of the ip source.)

iproute

The iproute library parses strings using the appar library. The overflow occurred in the dig parser:

dig :: Parser Int
dig = 0 <$ char '0'
  <|> toInt <$> oneOf ['1'..'9'] <*> many digit
  where
    toInt n ns = foldl' (\x y -> x * 10 + y) 0 . map digitToInt $ n : ns

The value is calculated using a fold over characters, so I implemented my fix using a fold like the above fix:

octet :: Parser Int
octet = 0 <$ char '0'
  <|> (toInt =<< (:) <$> oneOf ['1'..'9'] <*> many digit)
  where
    toInt ds = maybe (fail "IPv4 address") pure $ foldr go Just ds 0
    go !d !f !n =
      let n' = n * 10 + ord d - 48
      in  if n' <= 255 then f n' else Nothing

(Note: This code is written to match the style of the iproute source.)

Note that the toInt helper function can now fail on overflow, so it is changed to use the Parser monad instead of being a pure function that is mapped onto the result.

Upon changing the dig function, I discovered that it is also used to parse max lengths in IPv4 and IPv6 address ranges:

ip4range :: Parser (AddrRange IPv4)
ip4range = do
    ip <- ip4
    len <- option 32 $ char '/' >> dig
    check len
    let msk = maskIPv4 len
        adr = ip `maskedIPv4` msk
    return $ AddrRange adr msk len
  where
    check len = when (len < 0 || 32 < len) (fail "IPv4 mask length")
ip6range :: Parser (AddrRange IPv6)
ip6range = do
    ip <- ip6
    len <- option 128 $ char '/' >> dig
    check len
    let msk = maskIPv6 len
        adr = ip `maskedIPv6` msk
    return $ AddrRange adr msk len
  where
    check len = when (len < 0 || 128 < len) (fail ("IPv6 mask length: " ++ show len))

The use of the option function here is problematic. If the dig function fails, the failure is ignored and the default value is returned. I considered various options and decided to implement a maskLen function as follows:

maskLen :: Int -> Parser Int
maskLen maxLen = do
  hasSlash <- option False $ True <$ char '/'
  if hasSlash
    then 0 <$ char '0'
      <|> (toInt =<< (:) <$> oneOf ['1'..'9'] <*> many digit)
    else return maxLen
  where
    toInt ds = maybe (fail "mask length") pure $ foldr go Just ds 0
    go !d !f !n =
      let n' = n * 10 + ord d - 48
      in  if n' <= maxLen then f n' else Nothing

(Note: This code is written to match the style of the iproute source.)

In this implementation, the option function is only used to check if a slash character is present. If a slash is present, the mask length is parsed and can fail when invalid. Otherwise, the default value is returned.

Kazu merged the fix and created a new release this morning.