{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE BangPatterns #-}

-- Copyright     : Erik de Castro Lopo <erikd@mega-nerd.com>
-- License       : BSD3

module Network.Wai.Handler.Warp.ReadInt (
    readInt
  , readInt64
  ) where

import qualified Data.ByteString as S

import Network.Wai.Handler.Warp.Imports hiding (readInt)

{-# INLINE readInt #-}
readInt :: Integral a => ByteString -> a
readInt :: forall a. Integral a => ByteString -> a
readInt ByteString
bs = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ ByteString -> Int64
readInt64 ByteString
bs

-- This function is used to parse the Content-Length field of HTTP headers and
-- is a performance hot spot. It should only be replaced with something
-- significantly and provably faster.
--
-- It needs to be able work correctly on 32 bit CPUs for file sizes > 2G so we
-- use Int64 here and then make a generic 'readInt' that allows conversion to
-- Int and Integer.

{-# NOINLINE readInt64 #-}
readInt64 :: ByteString -> Int64
readInt64 :: ByteString -> Int64
readInt64 ByteString
bs = forall a. (a -> Word8 -> a) -> a -> ByteString -> a
S.foldl' (\ !Int64
i !Word8
c -> Int64
i forall a. Num a => a -> a -> a
* Int64
10 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
c forall a. Num a => a -> a -> a
- Word8
48)) Int64
0
             forall a b. (a -> b) -> a -> b
$ (Word8 -> Bool) -> ByteString -> ByteString
S.takeWhile Word8 -> Bool
isDigit ByteString
bs

isDigit :: Word8 -> Bool
isDigit :: Word8 -> Bool
isDigit Word8
w = Word8
w forall a. Ord a => a -> a -> Bool
>= Word8
48 Bool -> Bool -> Bool
&& Word8
w forall a. Ord a => a -> a -> Bool
<= Word8
57