Skip to content

Commit aca65b3

Browse files
authored
Use only fixed-width uints in the C itoa functions (#702)
* Use only fixed-width uints in the C itoa functions The existing logic for decimal encoding of signed ints was a bit more complicated than necessary in its handling for negative numbers, mostly because of negation overflowing for INT_MIN. But the absolute value of the smallest signed Int16 does fit into an unsigned Word16 without overflowing, allowing some simplification. Additionally, on hardware with slow integer division instructions, fast division-by-known-divisor is typically faster for unsigned types, so this change may lead to a slight speed-up on such platforms. (We could almost certainly produce slightly better code still for these platforms by hand, for example by exploiting the fact that after the first division the numbers are small enough that a quotient by ten can be extracted with a single mulhi and no shift.) * Remove a dead branch in `integerDec` If the absolute value of the input is small enough to enter this branch, then it fits in an Int and takes the very first branch instead.
1 parent 4e80579 commit aca65b3

File tree

5 files changed

+90
-173
lines changed

5 files changed

+90
-173
lines changed

Data/ByteString/Builder/ASCII.hs

Lines changed: 5 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -79,7 +79,7 @@ import Data.ByteString.Builder.Internal (Builder)
7979
import qualified Data.ByteString.Builder.Prim as P
8080
import qualified Data.ByteString.Builder.Prim.Internal as P
8181
import Data.ByteString.Builder.RealFloat (floatDec, doubleDec)
82-
import Data.ByteString.Internal.Type (c_int_dec_padded9, c_long_long_int_dec_padded18)
82+
import Data.ByteString.Internal.Type (c_uint32_dec_padded9, c_uint64_dec_padded18)
8383

8484
import Foreign
8585
import Data.List.NonEmpty (NonEmpty(..))
@@ -275,10 +275,8 @@ integerDec i
275275
| otherwise = go i
276276
where
277277
go :: Integer -> Builder
278-
go n | n < maxPow10 = intDec (fromInteger n)
279-
| otherwise =
280-
case putH (splitf (maxPow10 * maxPow10) n) of
281-
x:|xs -> intDec x `mappend` P.primMapListBounded intDecPadded xs
278+
go n = case putH (splitf (maxPow10 * maxPow10) n) of
279+
x:|xs -> intDec x `mappend` P.primMapListBounded intDecPadded xs
282280

283281
splitf :: Integer -> Integer -> NonEmpty Integer
284282
splitf pow10 n0
@@ -311,5 +309,5 @@ integerDec i
311309
{-# INLINE intDecPadded #-}
312310
intDecPadded :: P.BoundedPrim Int
313311
intDecPadded = P.liftFixedToBounded $ P.caseWordSize_32_64
314-
(P.fixedPrim 9 $ c_int_dec_padded9 . fromIntegral)
315-
(P.fixedPrim 18 $ c_long_long_int_dec_padded18 . fromIntegral)
312+
(P.fixedPrim 9 $ c_uint32_dec_padded9 . fromIntegral)
313+
(P.fixedPrim 18 $ c_uint64_dec_padded18 . fromIntegral)

Data/ByteString/Builder/Prim/ASCII.hs

Lines changed: 44 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE TypeFamilies #-}
2+
13
-- | Copyright : (c) 2010 Jasper Van der Jeugt
24
-- (c) 2010 - 2011 Simon Meier
35
-- License : BSD3-style (see LICENSE)
@@ -99,30 +101,50 @@ char7 = (\c -> fromIntegral $ ord c .&. 0x7f) >$< word8
99101
-- Signed integers
100102
------------------
101103

102-
{-# INLINE encodeIntDecimal #-}
103-
encodeIntDecimal :: Integral a => Int -> BoundedPrim a
104-
encodeIntDecimal bound = boundedPrim bound $ c_int_dec . fromIntegral
104+
type family CorrespondingUnsigned s where
105+
CorrespondingUnsigned Int8 = Word8
106+
CorrespondingUnsigned Int16 = Word16
107+
CorrespondingUnsigned Int32 = Word32
108+
CorrespondingUnsigned Int = Word
109+
CorrespondingUnsigned Int64 = Word64
110+
111+
{-# INLINE encodeSignedViaUnsigned #-}
112+
encodeSignedViaUnsigned ::
113+
forall s.
114+
(Integral s, Num (CorrespondingUnsigned s)) =>
115+
Int -> (BoundedPrim (CorrespondingUnsigned s)) -> BoundedPrim s
116+
encodeSignedViaUnsigned bound writeUnsigned = boundedPrim bound $ \sval ptr ->
117+
if sval < 0 then do
118+
poke ptr (c2w '-')
119+
runB writeUnsigned (makeUnsigned (negate sval)) (ptr `plusPtr` 1)
120+
-- This call to 'negate' may overflow if `sval == minBound`.
121+
-- But since we insist that the unsigned type has the same width,
122+
-- this causes no trouble.
123+
else do
124+
runB writeUnsigned (makeUnsigned sval) ptr
125+
where
126+
makeUnsigned = fromIntegral @s @(CorrespondingUnsigned s)
105127

106128
-- | Decimal encoding of an 'Int8'.
107129
{-# INLINE int8Dec #-}
108130
int8Dec :: BoundedPrim Int8
109-
int8Dec = encodeIntDecimal 4
131+
int8Dec = encodeSignedViaUnsigned 4 word8Dec
110132

111133
-- | Decimal encoding of an 'Int16'.
112134
{-# INLINE int16Dec #-}
113135
int16Dec :: BoundedPrim Int16
114-
int16Dec = encodeIntDecimal 6
136+
int16Dec = encodeSignedViaUnsigned 6 word16Dec
115137

116138

117139
-- | Decimal encoding of an 'Int32'.
118140
{-# INLINE int32Dec #-}
119141
int32Dec :: BoundedPrim Int32
120-
int32Dec = encodeIntDecimal 11
142+
int32Dec = encodeSignedViaUnsigned 11 word32Dec
121143

122144
-- | Decimal encoding of an 'Int64'.
123145
{-# INLINE int64Dec #-}
124146
int64Dec :: BoundedPrim Int64
125-
int64Dec = boundedPrim 20 $ c_long_long_int_dec . fromIntegral
147+
int64Dec = encodeSignedViaUnsigned 20 word64Dec
126148

127149
-- | Decimal encoding of an 'Int'.
128150
{-# INLINE intDec #-}
@@ -135,29 +157,29 @@ intDec = caseWordSize_32_64
135157
-- Unsigned integers
136158
--------------------
137159

138-
{-# INLINE encodeWordDecimal #-}
139-
encodeWordDecimal :: Integral a => Int -> BoundedPrim a
140-
encodeWordDecimal bound = boundedPrim bound $ c_uint_dec . fromIntegral
160+
{-# INLINE encodeWord32Decimal #-}
161+
encodeWord32Decimal :: Integral a => Int -> BoundedPrim a
162+
encodeWord32Decimal bound = boundedPrim bound $ c_uint32_dec . fromIntegral
141163

142164
-- | Decimal encoding of a 'Word8'.
143165
{-# INLINE word8Dec #-}
144166
word8Dec :: BoundedPrim Word8
145-
word8Dec = encodeWordDecimal 3
167+
word8Dec = encodeWord32Decimal 3
146168

147169
-- | Decimal encoding of a 'Word16'.
148170
{-# INLINE word16Dec #-}
149171
word16Dec :: BoundedPrim Word16
150-
word16Dec = encodeWordDecimal 5
172+
word16Dec = encodeWord32Decimal 5
151173

152174
-- | Decimal encoding of a 'Word32'.
153175
{-# INLINE word32Dec #-}
154176
word32Dec :: BoundedPrim Word32
155-
word32Dec = encodeWordDecimal 10
177+
word32Dec = encodeWord32Decimal 10
156178

157179
-- | Decimal encoding of a 'Word64'.
158180
{-# INLINE word64Dec #-}
159181
word64Dec :: BoundedPrim Word64
160-
word64Dec = boundedPrim 20 $ c_long_long_uint_dec . fromIntegral
182+
word64Dec = boundedPrim 20 c_uint64_dec
161183

162184
-- | Decimal encoding of a 'Word'.
163185
{-# INLINE wordDec #-}
@@ -173,30 +195,30 @@ wordDec = caseWordSize_32_64
173195
-- without lead
174196
---------------
175197

176-
{-# INLINE encodeWordHex #-}
177-
encodeWordHex :: forall a. (Storable a, Integral a) => BoundedPrim a
178-
encodeWordHex =
179-
boundedPrim (2 * sizeOf (undefined :: a)) $ c_uint_hex . fromIntegral
198+
{-# INLINE encodeWord32Hex #-}
199+
encodeWord32Hex :: forall a. (Storable a, Integral a) => BoundedPrim a
200+
encodeWord32Hex =
201+
boundedPrim (2 * sizeOf @a undefined) $ c_uint32_hex . fromIntegral
180202

181203
-- | Hexadecimal encoding of a 'Word8'.
182204
{-# INLINE word8Hex #-}
183205
word8Hex :: BoundedPrim Word8
184-
word8Hex = encodeWordHex
206+
word8Hex = encodeWord32Hex
185207

186208
-- | Hexadecimal encoding of a 'Word16'.
187209
{-# INLINE word16Hex #-}
188210
word16Hex :: BoundedPrim Word16
189-
word16Hex = encodeWordHex
211+
word16Hex = encodeWord32Hex
190212

191213
-- | Hexadecimal encoding of a 'Word32'.
192214
{-# INLINE word32Hex #-}
193215
word32Hex :: BoundedPrim Word32
194-
word32Hex = encodeWordHex
216+
word32Hex = encodeWord32Hex
195217

196218
-- | Hexadecimal encoding of a 'Word64'.
197219
{-# INLINE word64Hex #-}
198220
word64Hex :: BoundedPrim Word64
199-
word64Hex = boundedPrim 16 $ c_long_long_uint_hex . fromIntegral
221+
word64Hex = boundedPrim 16 c_uint64_hex
200222

201223
-- | Hexadecimal encoding of a 'Word'.
202224
{-# INLINE wordHex #-}

Data/ByteString/Internal/Pure.hs

Lines changed: 0 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,6 @@ module Data.ByteString.Internal.Pure
1919
, isValidUtf8
2020
, isValidUtf8BA
2121
-- * itoa.c
22-
, encodeSignedDec
2322
, encodeUnsignedDec
2423
, encodeUnsignedDecPadded
2524
, encodeUnsignedHex
@@ -307,22 +306,6 @@ reverseBytesInplace !p1 !p2
307306
reverseBytesInplace (plusPtr p1 1) (plusPtr p2 (-1))
308307
| otherwise = pure ()
309308

310-
-- | Encode signed number as decimal
311-
encodeSignedDec :: (Eq a, Num a, Integral a) => a -> Ptr Word8 -> IO (Ptr Word8)
312-
{-# INLINABLE encodeSignedDec #-} -- for specialization
313-
encodeSignedDec !x !buf
314-
| x >= 0 = encodeUnsignedDec x buf
315-
| otherwise = do
316-
-- we cannot negate directly as 0 - (minBound :: Int) = minBound
317-
-- So we write the sign and the first digit.
318-
pokeByteOff buf 0 '-'
319-
let !(q,r) = quotRem x (-10)
320-
putDigit buf 1 (fromIntegral (abs r))
321-
case q of
322-
0 -> pure (plusPtr buf 2)
323-
_ -> encodeUnsignedDec' q (plusPtr buf 1) (plusPtr buf 2)
324-
325-
326309
-- | Encode positive number as decimal
327310
encodeUnsignedDec :: (Eq a, Num a, Integral a) => a -> Ptr Word8 -> IO (Ptr Word8)
328311
{-# INLINABLE encodeUnsignedDec #-} -- for specialization
@@ -331,7 +314,6 @@ encodeUnsignedDec !v !next_ptr = encodeUnsignedDec' v next_ptr next_ptr
331314
-- | Encode positive number as little-endian decimal, then reverse it.
332315
--
333316
-- Take two pointers (orig_ptr, next_ptr) to support already encoded digits
334-
-- (e.g. used by encodeSignedDec to avoid overflows)
335317
--
336318
encodeUnsignedDec' :: (Eq a, Num a, Integral a) => a -> Ptr Word8 -> Ptr Word8 -> IO (Ptr Word8)
337319
{-# INLINABLE encodeUnsignedDec' #-} -- for specialization

Data/ByteString/Internal/Type.hs

Lines changed: 30 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -103,14 +103,12 @@ module Data.ByteString.Internal.Type (
103103
c_count_ba,
104104
c_elem_index,
105105
c_sort,
106-
c_int_dec,
107-
c_int_dec_padded9,
108-
c_uint_dec,
109-
c_uint_hex,
110-
c_long_long_int_dec,
111-
c_long_long_int_dec_padded18,
112-
c_long_long_uint_dec,
113-
c_long_long_uint_hex,
106+
c_uint32_dec,
107+
c_uint64_dec,
108+
c_uint32_dec_padded9,
109+
c_uint64_dec_padded18,
110+
c_uint32_hex,
111+
c_uint64_hex,
114112
cIsValidUtf8BA,
115113
cIsValidUtf8BASafe,
116114
cIsValidUtf8,
@@ -1164,29 +1162,23 @@ foreign import ccall unsafe "static sbs_elem_index"
11641162

11651163

11661164

1167-
foreign import ccall unsafe "static _hs_bytestring_uint_dec" c_uint_dec
1168-
:: CUInt -> Ptr Word8 -> IO (Ptr Word8)
1165+
foreign import ccall unsafe "static _hs_bytestring_uint32_dec" c_uint32_dec
1166+
:: Word32 -> Ptr Word8 -> IO (Ptr Word8)
11691167

1170-
foreign import ccall unsafe "static _hs_bytestring_long_long_uint_dec" c_long_long_uint_dec
1171-
:: CULLong -> Ptr Word8 -> IO (Ptr Word8)
1168+
foreign import ccall unsafe "static _hs_bytestring_uint64_dec" c_uint64_dec
1169+
:: Word64 -> Ptr Word8 -> IO (Ptr Word8)
11721170

1173-
foreign import ccall unsafe "static _hs_bytestring_int_dec" c_int_dec
1174-
:: CInt -> Ptr Word8 -> IO (Ptr Word8)
1171+
foreign import ccall unsafe "static _hs_bytestring_uint32_hex" c_uint32_hex
1172+
:: Word32 -> Ptr Word8 -> IO (Ptr Word8)
11751173

1176-
foreign import ccall unsafe "static _hs_bytestring_long_long_int_dec" c_long_long_int_dec
1177-
:: CLLong -> Ptr Word8 -> IO (Ptr Word8)
1174+
foreign import ccall unsafe "static _hs_bytestring_uint64_hex" c_uint64_hex
1175+
:: Word64 -> Ptr Word8 -> IO (Ptr Word8)
11781176

1179-
foreign import ccall unsafe "static _hs_bytestring_uint_hex" c_uint_hex
1180-
:: CUInt -> Ptr Word8 -> IO (Ptr Word8)
1177+
foreign import ccall unsafe "static _hs_bytestring_uint32_dec_padded9"
1178+
c_uint32_dec_padded9 :: Word32 -> Ptr Word8 -> IO ()
11811179

1182-
foreign import ccall unsafe "static _hs_bytestring_long_long_uint_hex" c_long_long_uint_hex
1183-
:: CULLong -> Ptr Word8 -> IO (Ptr Word8)
1184-
1185-
foreign import ccall unsafe "static _hs_bytestring_int_dec_padded9"
1186-
c_int_dec_padded9 :: CInt -> Ptr Word8 -> IO ()
1187-
1188-
foreign import ccall unsafe "static _hs_bytestring_long_long_int_dec_padded18"
1189-
c_long_long_int_dec_padded18 :: CLLong -> Ptr Word8 -> IO ()
1180+
foreign import ccall unsafe "static _hs_bytestring_uint64_dec_padded18"
1181+
c_uint64_dec_padded18 :: Word64 -> Ptr Word8 -> IO ()
11901182

11911183
-- We import bytestring_is_valid_utf8 both unsafe and safe. For small inputs
11921184
-- we can use the unsafe version to get a bit more performance, but for large
@@ -1272,28 +1264,22 @@ checkedCast x =
12721264
-- Haskell version of functions in itoa.c
12731265
----------------------------------------------------------------
12741266

1275-
c_int_dec :: CInt -> Ptr Word8 -> IO (Ptr Word8)
1276-
c_int_dec = Pure.encodeSignedDec
1277-
1278-
c_long_long_int_dec :: CLLong -> Ptr Word8 -> IO (Ptr Word8)
1279-
c_long_long_int_dec = Pure.encodeSignedDec
1280-
1281-
c_uint_dec :: CUInt -> Ptr Word8 -> IO (Ptr Word8)
1282-
c_uint_dec = Pure.encodeUnsignedDec
1267+
c_uint32_dec :: Word32 -> Ptr Word8 -> IO (Ptr Word8)
1268+
c_uint32_dec = Pure.encodeUnsignedDec
12831269

1284-
c_long_long_uint_dec :: CULLong -> Ptr Word8 -> IO (Ptr Word8)
1285-
c_long_long_uint_dec = Pure.encodeUnsignedDec
1270+
c_uint64_dec :: Word64 -> Ptr Word8 -> IO (Ptr Word8)
1271+
c_uint64_dec = Pure.encodeUnsignedDec
12861272

1287-
c_uint_hex :: CUInt -> Ptr Word8 -> IO (Ptr Word8)
1288-
c_uint_hex = Pure.encodeUnsignedHex
1273+
c_uint32_hex :: Word32 -> Ptr Word8 -> IO (Ptr Word8)
1274+
c_uint32_hex = Pure.encodeUnsignedHex
12891275

1290-
c_long_long_uint_hex :: CULLong -> Ptr Word8 -> IO (Ptr Word8)
1291-
c_long_long_uint_hex = Pure.encodeUnsignedHex
1276+
c_uint64_hex :: Word64 -> Ptr Word8 -> IO (Ptr Word8)
1277+
c_uint64_hex = Pure.encodeUnsignedHex
12921278

1293-
c_int_dec_padded9 :: CInt -> Ptr Word8 -> IO ()
1294-
c_int_dec_padded9 = Pure.encodeUnsignedDecPadded 9
1279+
c_uint32_dec_padded9 :: Word32 -> Ptr Word8 -> IO ()
1280+
c_uint32_dec_padded9 = Pure.encodeUnsignedDecPadded 9
12951281

1296-
c_long_long_int_dec_padded18 :: CLLong -> Ptr Word8 -> IO ()
1297-
c_long_long_int_dec_padded18 = Pure.encodeUnsignedDecPadded 18
1282+
c_uint64_dec_padded18 :: Word64 -> Ptr Word8 -> IO ()
1283+
c_uint64_dec_padded18 = Pure.encodeUnsignedDecPadded 18
12981284

12991285
#endif

0 commit comments

Comments
 (0)