Fix incorrect changes to C types in a foreign import for nhc98.
[haskell-directory.git] / Data / ByteString.hs
index df76e6b..8e9e919 100644 (file)
@@ -1,13 +1,12 @@
 {-# OPTIONS_GHC -cpp -fglasgow-exts -fno-warn-orphans #-}
---
--- Module      : ByteString
+-- |
+-- Module      : Data.ByteString
 -- Copyright   : (c) The University of Glasgow 2001,
 --               (c) David Roundy 2003-2005,
 --               (c) Simon Marlow 2005
 --               (c) Don Stewart 2005-2006
 --               (c) Bjorn Bringert 2006
---
--- Array fusion code:
+--               Array fusion code:
 --               (c) 2001,2002 Manuel M T Chakravarty & Gabriele Keller
 --               (c) 2006      Manuel M T Chakravarty & Roman Leshchinskiy
 --
 --
 -- Maintainer  : dons@cse.unsw.edu.au
 -- Stability   : experimental
--- Portability : portable, requires ffi and cpp
--- Tested with : GHC 6.4.1 and Hugs March 2005
+-- Portability : portable
 -- 
-
---
--- | A time and space-efficient implementation of byte vectors using
+-- A time and space-efficient implementation of byte vectors using
 -- packed Word8 arrays, suitable for high performance use, both in terms
 -- of large data quantities, or high speed requirements. Byte vectors
 -- are encoded as strict 'Word8' arrays of bytes, held in a 'ForeignPtr',
 --
 -- > import qualified Data.ByteString as B
 --
--- Original GHC implementation by Bryan O\'Sullivan. Rewritten to use
--- UArray by Simon Marlow. Rewritten to support slices and use
--- ForeignPtr by David Roundy. Polished and extended by Don Stewart.
+-- Original GHC implementation by Bryan O\'Sullivan.
+-- Rewritten to use 'Data.Array.Unboxed.UArray' by Simon Marlow.
+-- Rewritten to support slices and use 'ForeignPtr' by David Roundy.
+-- Polished and extended by Don Stewart.
 --
 
 module Data.ByteString (
@@ -291,12 +288,6 @@ instance Eq  ByteString
 instance Ord ByteString
     where compare = compareBytes
 
-instance Show ByteString where
-    showsPrec p ps r = showsPrec p (unpackWith w2c ps) r
-
-instance Read ByteString where
-    readsPrec p str = [ (packWith c2w x, y) | (x, y) <- readsPrec p str ]
-
 instance Monoid ByteString where
     mempty  = empty
     mappend = append
@@ -453,36 +444,11 @@ unpackList (PS fp off len) = withPtr fp $ \p -> do
     loop (p `plusPtr` off) (len-1) []
 
 {-# RULES
-"unpack-list"  [1]  forall p  . unpackFoldr p (:) [] = unpackList p
+    "FPS unpack-list"  [1]  forall p  . unpackFoldr p (:) [] = unpackList p
  #-}
 
 #endif
 
-------------------------------------------------------------------------
-
--- | /O(n)/ Convert a '[a]' into a 'ByteString' using some
--- conversion function
-packWith :: (a -> Word8) -> [a] -> ByteString
-packWith k str = unsafeCreate (P.length str) $ \p -> go p str
-    where
-        STRICT2(go)
-        go _ []     = return ()
-        go p (x:xs) = poke p (k x) >> go (p `plusPtr` 1) xs -- less space than pokeElemOff
-{-# INLINE packWith #-}
-{-# SPECIALIZE packWith :: (Char -> Word8) -> [Char] -> ByteString #-}
-
--- | /O(n)/ Converts a 'ByteString' to a '[a]', using a conversion function.
-unpackWith :: (Word8 -> a) -> ByteString -> [a]
-unpackWith _ (PS _  _ 0) = []
-unpackWith k (PS ps s l) = inlinePerformIO $ withForeignPtr ps $ \p ->
-        go (p `plusPtr` s) (l - 1) []
-    where
-        STRICT3(go)
-        go p 0 acc = peek p          >>= \e -> return (k e : acc)
-        go p n acc = peekByteOff p n >>= \e -> go p (n-1) (k e : acc)
-{-# INLINE unpackWith #-}
-{-# SPECIALIZE unpackWith :: (Word8 -> Char) -> ByteString -> [Char] #-}
-
 -- ---------------------------------------------------------------------
 -- Basic interface
 
@@ -513,7 +479,7 @@ lengthU = foldl' (const . (+1)) (0::Int)
 {-# RULES
 
 -- v2 fusion
-"length/loop" forall loop s .
+"FPS length/loop" forall loop s .
   length  (loopArr (loopWrapper loop s)) =
   lengthU (loopArr (loopWrapper loop s))
 
@@ -819,11 +785,11 @@ minimumU = foldl1' min
 
 {-# RULES
 
-"minimum/loop" forall loop s .
+"FPS minimum/loop" forall loop s .
   minimum  (loopArr (loopWrapper loop s)) =
   minimumU (loopArr (loopWrapper loop s))
 
-"maximum/loop" forall loop s .
+"FPS maximum/loop" forall loop s .
   maximum  (loopArr (loopWrapper loop s)) =
   maximumU (loopArr (loopWrapper loop s))
 
@@ -1133,7 +1099,7 @@ splitWith p ps = loop p ps
 -- 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
@@ -1438,8 +1404,8 @@ filterByte w ps = replicate (count w ps) w
 
 #if __GLASGOW_HASKELL__ >= 605
 {-# RULES
-"FPS specialise filter (== x)" forall x.
-    filter (== x) = filterByte x
+  "FPS specialise filter (== x)" forall x.
+     filter (== x) = filterByte x
   #-}
 #endif
 
@@ -1582,6 +1548,9 @@ zipWith :: (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a]
 zipWith f ps qs
     | null ps || null qs = []
     | otherwise = f (unsafeHead ps) (unsafeHead qs) : zipWith f (unsafeTail ps) (unsafeTail qs)
+#if defined(__GLASGOW_HASKELL__)
+{-# INLINE [1] zipWith #-}
+#endif
 
 --
 -- | A specialised version of zipWith for the common case of a
@@ -1613,6 +1582,7 @@ zipWith' f (PS fp s l) (PS fq t m) = inlinePerformIO $
 
 "FPS specialise zipWith" forall (f :: Word8 -> Word8 -> Word8) p q .
     zipWith f p q = unpack (zipWith' f p q)
+
   #-}
 
 -- | /O(n)/ 'unzip' transforms a list of pairs of bytes into a pair of
@@ -1774,9 +1744,7 @@ hGetLines h = go
 
 hGetLine :: Handle -> IO ByteString
 #if !defined(__GLASGOW_HASKELL__)
-hGetLine h = do
-  string <- System.IO.hGetLine h
-  return $ packWith c2w string
+hGetLine h = System.IO.hGetLine h >>= return . pack . P.map c2w
 #else
 hGetLine h = wantReadableHandle "Data.ByteString.hGetLine" h $ \ handle_ -> do
     case haBufferMode handle_ of