Skip to content

Commit d8b0506

Browse files
fix possible overflow error when converting String to Builder
1 parent 9e7e6bd commit d8b0506

File tree

2 files changed

+9
-21
lines changed

2 files changed

+9
-21
lines changed

Data/ByteString/Builder/RealFloat.hs

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -309,11 +309,6 @@ instance ToD Double where toD = RD.d2d
309309
char7 :: Char -> Builder
310310
char7 = BP.primFixed BP.char7
311311

312-
-- | Char7 encode a 'String'.
313-
{-# INLINE string7 #-}
314-
string7 :: String -> Builder
315-
string7 = BP.primMapListFixed BP.char7
316-
317312
-- | Encodes a `-` if input is negative
318313
printSign :: RealFloat a => a -> Builder
319314
printSign f = if f < 0 then char7 '-' else mempty
@@ -332,7 +327,7 @@ showStandard m e prec =
332327
Nothing
333328
| e <= 0 -> char7 '0'
334329
`mappend` char7 '.'
335-
`mappend` string7 (replicate (-e) '0')
330+
`mappend` R.string7 (replicate (-e) '0')
336331
`mappend` mconcat (digitsToBuilder ds)
337332
| otherwise ->
338333
let f 0 s rs = mk0 (reverse s) `mappend` char7 '.' `mappend` mk0 rs

Data/ByteString/Builder/RealFloat/Internal.hs

Lines changed: 8 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@
2828

2929
module Data.ByteString.Builder.RealFloat.Internal
3030
( mask
31+
, string7
3132
, toCharsNonNumbersAndZero
3233
, SpecialStrings(..)
3334
, DecimalLength(..)
@@ -85,9 +86,7 @@ module Data.ByteString.Builder.RealFloat.Internal
8586
, module Data.ByteString.Builder.RealFloat.TableGenerator
8687
) where
8788

88-
import Control.Monad (foldM)
8989
import Data.Bits (Bits(..), FiniteBits(..))
90-
import Data.ByteString.Internal (c2w)
9190
import Data.ByteString.Builder.Internal (Builder)
9291
import Data.ByteString.Builder.Prim.Internal (BoundedPrim, boundedPrim)
9392
import Data.ByteString.Builder.RealFloat.TableGenerator
@@ -99,10 +98,9 @@ import Foreign.C.Types
9998
import GHC.Int (Int(..), Int32(..))
10099
import GHC.IO (IO(..), unIO)
101100
import GHC.Prim
102-
import GHC.Ptr (Ptr(..), plusPtr, castPtr)
101+
import GHC.Ptr (Ptr(..), castPtr)
103102
import GHC.Types (isTrue#)
104-
import GHC.Word (Word8, Word16(..), Word32(..), Word64(..))
105-
import qualified Foreign.Storable as S (poke)
103+
import GHC.Word (Word16(..), Word32(..), Word64(..))
106104

107105
#include <ghcautoconf.h>
108106
#include "MachDeps.h"
@@ -234,15 +232,10 @@ instance DecimalLength Word64 where decimalLength = decimalLength17
234232
maxEncodedLength :: Int
235233
maxEncodedLength = 32
236234

237-
-- | Storable.poke a String into a Ptr Word8, converting through c2w
238-
pokeAll :: String -> Ptr Word8 -> IO (Ptr Word8)
239-
pokeAll s ptr = foldM pokeOne ptr s
240-
where pokeOne p c = S.poke p (c2w c) >> return (p `plusPtr` 1)
241-
242-
-- | Unsafe creation of a bounded primitive of String at most length
243-
-- `maxEncodedLength`
244-
boundString :: String -> BoundedPrim ()
245-
boundString s = boundedPrim maxEncodedLength $ const (pokeAll s)
235+
-- | Char7 encode a 'String'.
236+
{-# INLINE string7 #-}
237+
string7 :: String -> Builder
238+
string7 = BP.primMapListFixed BP.char7
246239

247240
-- | Special rendering for NaN, positive\/negative 0, and positive\/negative
248241
-- infinity. These are based on the IEEE representation of non-numbers.
@@ -284,7 +277,7 @@ toCharsNonNumbersAndZero :: forall a mw ew.
284277
, ew ~ ExponentWord a
285278
, mw ~ MantissaWord a
286279
) => SpecialStrings -> a -> Maybe Builder
287-
toCharsNonNumbersAndZero SpecialStrings{..} f = flip BP.primBounded () . boundString <$>
280+
toCharsNonNumbersAndZero SpecialStrings{..} f = string7 <$>
288281
if w .&. expoMantissaBits == 0
289282
then Just if w == signBit then negativeZero else positiveZero
290283
else if w .&. expoMask == expoMask

0 commit comments

Comments
 (0)