Remove Control.Parallel*, now in package parallel
[haskell-directory.git] / Data / ByteString / Char8.hs
index bd4b31a..a62ae57 100644 (file)
@@ -1,16 +1,14 @@
 {-# OPTIONS_GHC -cpp -fglasgow-exts #-}
---
+-- |
 -- Module      : Data.ByteString.Char8
 -- Copyright   : (c) Don Stewart 2006
 -- License     : BSD-style
 --
 -- Maintainer  : dons@cse.unsw.edu.au
 -- Stability   : experimental
--- Portability : portable (tested with GHC>=6.4.1 and Hugs 2005)
--- 
-
+-- Portability : portable
 --
--- | Manipulate 'ByteString's using 'Char' operations. All Chars will be
+-- Manipulate 'ByteString's using 'Char' operations. All Chars will be
 -- truncated to 8 bits. It can be expected that these functions will run
 -- at identical speeds to their 'Word8' equivalents in "Data.ByteString".
 --
@@ -162,7 +160,8 @@ module Data.ByteString.Char8 (
         sort,                   -- :: ByteString -> ByteString
 
         -- * Reading from ByteStrings
-        readInt,                -- :: ByteString -> Maybe Int
+        readInt,                -- :: ByteString -> Maybe (Int, ByteString)
+        readInteger,            -- :: ByteString -> Maybe (Integer, ByteString)
 
         -- * Low level CString conversions
 
@@ -266,7 +265,7 @@ import Control.Exception        (bracket)
 import Foreign
 
 #if defined(__GLASGOW_HASKELL__)
-import GHC.Base                 (Char(..),unpackCString#,unsafeCoerce#)
+import GHC.Base                 (Char(..),unpackCString#,ord#,int2Word#)
 import GHC.IOBase               (IO(..),stToIO)
 import GHC.Prim                 (Addr#,writeWord8OffAddr#,plusAddr#)
 import GHC.Ptr                  (Ptr(..))
@@ -302,7 +301,7 @@ pack str = B.unsafeCreate (P.length str) $ \(Ptr p) -> stToIO (go p str)
   where
     go :: Addr# -> [Char] -> ST a ()
     go _ []        = return ()
-    go p (C# c:cs) = writeByte p (unsafeCoerce# c) >> go (p `plusAddr#` 1#) cs
+    go p (C# c:cs) = writeByte p (int2Word# (ord# c)) >> go (p `plusAddr#` 1#) cs
 
     writeByte p c = ST $ \s# ->
         case writeWord8OffAddr# p 0# c s# of s2# -> (# s2#, () #)
@@ -584,7 +583,7 @@ spanChar = B.spanByte . c2w
 -- argument, consuming the delimiter. I.e.
 --
 -- > split '\n' "a\nb\nd\ne" == ["a","b","d","e"]
--- > split 'a'  "aXaXaXa"    == ["","X","X","X"]
+-- > split 'a'  "aXaXaXa"    == ["","X","X","X",""]
 -- > split 'x'  "x"          == ["",""]
 -- 
 -- and
@@ -931,6 +930,51 @@ readInt as
           end True _ n ps = Just (negate n, ps)
           end _    _ n ps = Just (n, ps)
 
+-- | readInteger reads an Integer from the beginning of the ByteString.  If
+-- there is no integer at the beginning of the string, it returns Nothing,
+-- otherwise it just returns the int read, and the rest of the string.
+readInteger :: ByteString -> Maybe (Integer, ByteString)
+readInteger as
+    | null as   = Nothing
+    | otherwise =
+        case unsafeHead as of
+            '-' -> first (unsafeTail as) >>= \(n, bs) -> return (-n, bs)
+            '+' -> first (unsafeTail as)
+            _   -> first as
+
+    where first ps | null ps   = Nothing
+                   | otherwise =
+                       case B.unsafeHead ps of
+                        w | w >= 0x30 && w <= 0x39 -> Just $
+                            loop 1 (fromIntegral w - 0x30) [] (unsafeTail ps)
+                          | otherwise              -> Nothing
+
+          loop :: Int -> Int -> [Integer]
+               -> ByteString -> (Integer, ByteString)
+          STRICT4(loop)
+          loop d acc ns ps
+              | null ps   = combine d acc ns empty
+              | otherwise =
+                  case B.unsafeHead ps of
+                   w | w >= 0x30 && w <= 0x39 ->
+                       if d == 9 then loop 1 (fromIntegral w - 0x30)
+                                           (toInteger acc : ns)
+                                           (unsafeTail ps)
+                                 else loop (d+1)
+                                           (10*acc + (fromIntegral w - 0x30))
+                                           ns (unsafeTail ps)
+                     | otherwise -> combine d acc ns ps
+
+          combine _ acc [] ps = (toInteger acc, ps)
+          combine d acc ns ps =
+              ((10^d * combine1 1000000000 ns + toInteger acc), ps)
+
+          combine1 _ [n] = n
+          combine1 b ns  = combine1 (b*b) $ combine2 b ns
+
+          combine2 b (n:m:ns) = let t = m*b + n in t `seq` (t : combine2 b ns)
+          combine2 _ ns       = ns
+
 -- | Read an entire file strictly into a 'ByteString'.  This is far more
 -- efficient than reading the characters into a 'String' and then using
 -- 'pack'.  It also may be more efficient than opening the file and