[commit: packages/bytestring] 0.10.4.x, master: Rename sumP to checkedSum, and export it (2530b1c)

git at git.haskell.org git at git.haskell.org
Fri Jan 23 22:42:32 UTC 2015


Repository : ssh://git@git.haskell.org/bytestring

On branches: 0.10.4.x,master
Link       : http://git.haskell.org/packages/bytestring.git/commitdiff/2530b1c28f15d0f320a84701bf507d5650de6098

>---------------------------------------------------------------

commit 2530b1c28f15d0f320a84701bf507d5650de6098
Author: Bryan O'Sullivan <bos at serpentine.com>
Date:   Fri Jun 6 14:42:47 2014 -0700

    Rename sumP to checkedSum, and export it


>---------------------------------------------------------------

2530b1c28f15d0f320a84701bf507d5650de6098
 Data/ByteString/Internal.hs | 17 ++++++++++++++---
 1 file changed, 14 insertions(+), 3 deletions(-)

diff --git a/Data/ByteString/Internal.hs b/Data/ByteString/Internal.hs
index efdb7a6..15192c1 100644
--- a/Data/ByteString/Internal.hs
+++ b/Data/ByteString/Internal.hs
@@ -38,6 +38,7 @@ module Data.ByteString.Internal (
 #if defined(__GLASGOW_HASKELL__)
         unsafePackAddress,
 #endif
+        checkedSum,
 
         -- * Low level imperative construction
         create,                 -- :: Int -> (Ptr Word8 -> IO ()) -> IO ByteString
@@ -532,12 +533,21 @@ concat []     = mempty
 concat [bs]   = bs
 concat bss0   = unsafeCreate totalLen $ \ptr -> go bss0 ptr
   where
-    totalLen = List.sum [ len | (PS _ _ len) <- bss0 ]
+    totalLen = checkedSum "concat" [ len | (PS _ _ len) <- bss0 ]
     go []                  !_   = return ()
     go (PS fp off len:bss) !ptr = do
       withForeignPtr fp $ \p -> memcpy ptr (p `plusPtr` off) len
       go bss (ptr `plusPtr` len)
 
+-- | Add a list of non-negative numbers.  Errors out on overflow.
+checkedSum :: String -> [Int] -> Int
+checkedSum fun = go 0
+  where go !a (x:xs)
+            | ax >= 0   = go ax xs
+            | otherwise = overflowError fun
+          where ax = a + x
+        go a  _         = a
+
 ------------------------------------------------------------------------
 
 -- | Conversion between 'Word8' and 'Char'. Should compile to a no-op.
@@ -581,6 +591,9 @@ isSpaceChar8 c =
     c == '\xa0'
 {-# INLINE isSpaceChar8 #-}
 
+overflowError :: String -> a
+overflowError fun = error $ "Data.ByteString." ++ fun ++ ": size overflow"
+
 ------------------------------------------------------------------------
 
 -- | This \"function\" has a superficial similarity to 'unsafePerformIO' but
@@ -620,7 +633,6 @@ inlinePerformIO = accursedUnutterablePerformIO
 {-# INLINE inlinePerformIO #-}
 {-# DEPRECATED inlinePerformIO "If you think you know what you are doing, use 'unsafePerformIO'. If you are sure you know what you are doing, use 'unsafeDupablePerformIO'. If you enjoy sharing an address space with a malevolent agent of chaos, try 'accursedUnutterablePerformIO'." #-}
 
-
 -- ---------------------------------------------------------------------
 --
 -- Standard C functions
@@ -684,4 +696,3 @@ foreign import ccall unsafe "static fpstring.h fps_minimum" c_minimum
 
 foreign import ccall unsafe "static fpstring.h fps_count" c_count
     :: Ptr Word8 -> CULong -> Word8 -> IO CULong
-



More information about the ghc-commits mailing list