Sync Data.ByteString with current stable branch, 0.7
[ghc-base.git] / Data / ByteString / Char8.hs
1 {-# OPTIONS_GHC -cpp -fglasgow-exts #-}
2 --
3 -- Module      : Data.ByteString.Char8
4 -- Copyright   : (c) Don Stewart 2006
5 -- License     : BSD-style
6 --
7 -- Maintainer  : dons@cse.unsw.edu.au
8 -- Stability   : experimental
9 -- Portability : portable (tested with GHC>=6.4.1 and Hugs 2005)
10 -- 
11
12 --
13 -- | Manipulate 'ByteString's using 'Char' operations. All Chars will be
14 -- truncated to 8 bits. It can be expected that these functions will run
15 -- at identical speeds to their 'Word8' equivalents in "Data.ByteString".
16 --
17 -- More specifically these byte strings are taken to be in the
18 -- subset of Unicode covered by code points 0-255. This covers
19 -- Unicode Basic Latin, Latin-1 Supplement and C0+C1 Controls.
20 -- 
21 -- See: 
22 --
23 --  * <http://www.unicode.org/charts/>
24 --
25 --  * <http://www.unicode.org/charts/PDF/U0000.pdf>
26 --
27 --  * <http://www.unicode.org/charts/PDF/U0080.pdf>
28 --
29 -- This module is intended to be imported @qualified@, to avoid name
30 -- clashes with "Prelude" functions.  eg.
31 --
32 -- > import qualified Data.ByteString.Char8 as B
33 --
34
35 module Data.ByteString.Char8 (
36
37         -- * The @ByteString@ type
38         ByteString,             -- abstract, instances: Eq, Ord, Show, Read, Data, Typeable, Monoid
39
40         -- * Introducing and eliminating 'ByteString's
41         empty,                  -- :: ByteString
42         singleton,              -- :: Char   -> ByteString
43         pack,                   -- :: String -> ByteString
44         unpack,                 -- :: ByteString -> String
45
46         -- * Basic interface
47         cons,                   -- :: Char -> ByteString -> ByteString
48         snoc,                   -- :: ByteString -> Char -> ByteString
49         append,                 -- :: ByteString -> ByteString -> ByteString
50         head,                   -- :: ByteString -> Char
51         last,                   -- :: ByteString -> Char
52         tail,                   -- :: ByteString -> ByteString
53         init,                   -- :: ByteString -> ByteString
54         null,                   -- :: ByteString -> Bool
55         length,                 -- :: ByteString -> Int
56
57         -- * Transformating ByteStrings
58         map,                    -- :: (Char -> Char) -> ByteString -> ByteString
59         reverse,                -- :: ByteString -> ByteString
60         intersperse,            -- :: Char -> ByteString -> ByteString
61         transpose,              -- :: [ByteString] -> [ByteString]
62
63         -- * Reducing 'ByteString's (folds)
64         foldl,                  -- :: (a -> Char -> a) -> a -> ByteString -> a
65         foldl',                 -- :: (a -> Char -> a) -> a -> ByteString -> a
66         foldl1,                 -- :: (Char -> Char -> Char) -> ByteString -> Char
67         foldl1',                -- :: (Char -> Char -> Char) -> ByteString -> Char
68
69         foldr,                  -- :: (Char -> a -> a) -> a -> ByteString -> a
70         foldr',                 -- :: (Char -> a -> a) -> a -> ByteString -> a
71         foldr1,                 -- :: (Char -> Char -> Char) -> ByteString -> Char
72         foldr1',                -- :: (Char -> Char -> Char) -> ByteString -> Char
73
74         -- ** Special folds
75         concat,                 -- :: [ByteString] -> ByteString
76         concatMap,              -- :: (Char -> ByteString) -> ByteString -> ByteString
77         any,                    -- :: (Char -> Bool) -> ByteString -> Bool
78         all,                    -- :: (Char -> Bool) -> ByteString -> Bool
79         maximum,                -- :: ByteString -> Char
80         minimum,                -- :: ByteString -> Char
81
82         -- * Building ByteStrings
83         -- ** Scans
84         scanl,                  -- :: (Char -> Char -> Char) -> Char -> ByteString -> ByteString
85         scanl1,                 -- :: (Char -> Char -> Char) -> ByteString -> ByteString
86         scanr,                  -- :: (Char -> Char -> Char) -> Char -> ByteString -> ByteString
87         scanr1,                 -- :: (Char -> Char -> Char) -> ByteString -> ByteString
88
89         -- ** Accumulating maps
90         mapAccumL,              -- :: (acc -> Char -> (acc, Char)) -> acc -> ByteString -> (acc, ByteString)
91         mapAccumR,              -- :: (acc -> Char -> (acc, Char)) -> acc -> ByteString -> (acc, ByteString)
92         mapIndexed,             -- :: (Int -> Char -> Char) -> ByteString -> ByteString
93
94         -- * Generating and unfolding ByteStrings
95         replicate,              -- :: Int -> Char -> ByteString
96         unfoldr,                -- :: (a -> Maybe (Char, a)) -> a -> ByteString
97         unfoldrN,               -- :: Int -> (a -> Maybe (Char, a)) -> a -> (ByteString, Maybe a)
98
99         -- * Substrings
100
101         -- ** Breaking strings
102         take,                   -- :: Int -> ByteString -> ByteString
103         drop,                   -- :: Int -> ByteString -> ByteString
104         splitAt,                -- :: Int -> ByteString -> (ByteString, ByteString)
105         takeWhile,              -- :: (Char -> Bool) -> ByteString -> ByteString
106         dropWhile,              -- :: (Char -> Bool) -> ByteString -> ByteString
107         span,                   -- :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
108         spanEnd,                -- :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
109         break,                  -- :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
110         breakEnd,               -- :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
111         group,                  -- :: ByteString -> [ByteString]
112         groupBy,                -- :: (Char -> Char -> Bool) -> ByteString -> [ByteString]
113         inits,                  -- :: ByteString -> [ByteString]
114         tails,                  -- :: ByteString -> [ByteString]
115
116         -- ** Breaking into many substrings
117         split,                  -- :: Char -> ByteString -> [ByteString]
118         splitWith,              -- :: (Char -> Bool) -> ByteString -> [ByteString]
119
120         -- ** Breaking into lines and words
121         lines,                  -- :: ByteString -> [ByteString]
122         words,                  -- :: ByteString -> [ByteString]
123         unlines,                -- :: [ByteString] -> ByteString
124         unwords,                -- :: ByteString -> [ByteString]
125
126         -- ** Joining strings
127         join,                   -- :: ByteString -> [ByteString] -> ByteString
128
129         -- ** Searching for substrings
130         isPrefixOf,             -- :: ByteString -> ByteString -> Bool
131         isSuffixOf,             -- :: ByteString -> ByteString -> Bool
132         isSubstringOf,          -- :: ByteString -> ByteString -> Bool
133         findSubstring,          -- :: ByteString -> ByteString -> Maybe Int
134         findSubstrings,         -- :: ByteString -> ByteString -> [Int]
135
136         -- * Searching ByteStrings
137
138         -- ** Searching by equality
139         elem,                   -- :: Char -> ByteString -> Bool
140         notElem,                -- :: Char -> ByteString -> Bool
141
142         -- ** Searching with a predicate
143         find,                   -- :: (Char -> Bool) -> ByteString -> Maybe Char
144         filter,                 -- :: (Char -> Bool) -> ByteString -> ByteString
145 --      partition               -- :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
146
147         -- * Indexing ByteStrings
148         index,                  -- :: ByteString -> Int -> Char
149         elemIndex,              -- :: Char -> ByteString -> Maybe Int
150         elemIndices,            -- :: Char -> ByteString -> [Int]
151         elemIndexEnd,           -- :: Char -> ByteString -> Maybe Int
152         findIndex,              -- :: (Char -> Bool) -> ByteString -> Maybe Int
153         findIndices,            -- :: (Char -> Bool) -> ByteString -> [Int]
154         count,                  -- :: Char -> ByteString -> Int
155
156         -- * Zipping and unzipping ByteStrings
157         zip,                    -- :: ByteString -> ByteString -> [(Char,Char)]
158         zipWith,                -- :: (Char -> Char -> c) -> ByteString -> ByteString -> [c]
159         unzip,                  -- :: [(Char,Char)] -> (ByteString,ByteString)
160
161         -- * Ordered ByteStrings
162         sort,                   -- :: ByteString -> ByteString
163
164         -- * Reading from ByteStrings
165         readInt,                -- :: ByteString -> Maybe Int
166
167         -- * Low level CString conversions
168
169         -- ** Packing CStrings and pointers
170         packCString,            -- :: CString -> ByteString
171         packCStringLen,         -- :: CString -> ByteString
172         packMallocCString,      -- :: CString -> ByteString
173
174         -- ** Using ByteStrings as CStrings
175         useAsCString,           -- :: ByteString -> (CString -> IO a) -> IO a
176         useAsCStringLen,        -- :: ByteString -> (CStringLen -> IO a) -> IO a
177
178         -- * Copying ByteStrings
179         copy,                   -- :: ByteString -> ByteString
180         copyCString,            -- :: CString -> IO ByteString
181         copyCStringLen,         -- :: CStringLen -> IO ByteString
182
183         -- * I\/O with @ByteString@s
184
185         -- ** Standard input and output
186         getLine,                -- :: IO ByteString
187         getContents,            -- :: IO ByteString
188         putStr,                 -- :: ByteString -> IO ()
189         putStrLn,               -- :: ByteString -> IO ()
190         interact,               -- :: (ByteString -> ByteString) -> IO ()
191
192         -- ** Files
193         readFile,               -- :: FilePath -> IO ByteString
194         writeFile,              -- :: FilePath -> ByteString -> IO ()
195         appendFile,             -- :: FilePath -> ByteString -> IO ()
196 --      mmapFile,               -- :: FilePath -> IO ByteString
197
198         -- ** I\/O with Handles
199         hGetLine,               -- :: Handle -> IO ByteString
200         hGetNonBlocking,        -- :: Handle -> Int -> IO ByteString
201         hGetContents,           -- :: Handle -> IO ByteString
202         hGet,                   -- :: Handle -> Int -> IO ByteString
203         hPut,                   -- :: Handle -> ByteString -> IO ()
204         hPutStr,                -- :: Handle -> ByteString -> IO ()
205         hPutStrLn,              -- :: Handle -> ByteString -> IO ()
206
207 #if defined(__GLASGOW_HASKELL__)
208         -- * Low level construction
209         -- | For constructors from foreign language types see "Data.ByteString"
210         packAddress,            -- :: Addr# -> ByteString
211         unsafePackAddress,      -- :: Int -> Addr# -> ByteString
212 #endif
213
214         -- * Utilities (needed for array fusion)
215 #if defined(__GLASGOW_HASKELL__)
216         unpackList,
217 #endif
218
219     ) where
220
221 import qualified Prelude as P
222 import Prelude hiding           (reverse,head,tail,last,init,null
223                                 ,length,map,lines,foldl,foldr,unlines
224                                 ,concat,any,take,drop,splitAt,takeWhile
225                                 ,dropWhile,span,break,elem,filter,unwords
226                                 ,words,maximum,minimum,all,concatMap
227                                 ,scanl,scanl1,scanr,scanr1
228                                 ,appendFile,readFile,writeFile
229                                 ,foldl1,foldr1,replicate
230                                 ,getContents,getLine,putStr,putStrLn,interact
231                                 ,zip,zipWith,unzip,notElem)
232
233 import qualified Data.ByteString as B
234 import qualified Data.ByteString.Base as B
235
236 -- Listy functions transparently exported
237 import Data.ByteString (empty,null,length,tail,init,append
238                        ,inits,tails,reverse,transpose
239                        ,concat,take,drop,splitAt,join
240                        ,sort,isPrefixOf,isSuffixOf,isSubstringOf,findSubstring
241                        ,findSubstrings,copy,group
242
243                        ,getLine, getContents, putStr, putStrLn, interact
244                        ,hGetContents, hGet, hPut, hPutStr, hPutStrLn
245                        ,hGetLine, hGetNonBlocking
246                        ,packCString,packCStringLen, packMallocCString
247                        ,useAsCString,useAsCStringLen, copyCString,copyCStringLen
248 #if defined(__GLASGOW_HASKELL__)
249                        ,unpackList
250 #endif
251                        )
252
253 import Data.ByteString.Base (
254                         ByteString(..)
255 #if defined(__GLASGOW_HASKELL__)
256                        ,packAddress, unsafePackAddress
257 #endif
258                        ,c2w, w2c, unsafeTail, isSpaceWord8, inlinePerformIO
259                        )
260
261 import Data.Char    ( isSpace )
262 import qualified Data.List as List (intersperse)
263
264 import System.IO                (openFile,hClose,hFileSize,IOMode(..))
265 import Control.Exception        (bracket)
266 import Foreign
267
268 #if defined(__GLASGOW_HASKELL__)
269 import GHC.Base                 (Char(..),unpackCString#,unsafeCoerce#)
270 import GHC.IOBase               (IO(..),stToIO)
271 import GHC.Prim                 (Addr#,writeWord8OffAddr#,plusAddr#)
272 import GHC.Ptr                  (Ptr(..))
273 import GHC.ST                   (ST(..))
274 #endif
275
276 #define STRICT1(f) f a | a `seq` False = undefined
277 #define STRICT2(f) f a b | a `seq` b `seq` False = undefined
278 #define STRICT3(f) f a b c | a `seq` b `seq` c `seq` False = undefined
279 #define STRICT4(f) f a b c d | a `seq` b `seq` c `seq` d `seq` False = undefined
280
281 ------------------------------------------------------------------------
282
283 -- | /O(1)/ Convert a 'Char' into a 'ByteString'
284 singleton :: Char -> ByteString
285 singleton = B.singleton . c2w
286 {-# INLINE singleton #-}
287
288 -- | /O(n)/ Convert a 'String' into a 'ByteString'
289 --
290 -- For applications with large numbers of string literals, pack can be a
291 -- bottleneck. In such cases, consider using packAddress (GHC only).
292 pack :: String -> ByteString
293 #if !defined(__GLASGOW_HASKELL__)
294
295 pack str = B.unsafeCreate (P.length str) $ \p -> go p str
296     where go _ []     = return ()
297           go p (x:xs) = poke p (c2w x) >> go (p `plusPtr` 1) xs
298
299 #else /* hack away */
300
301 pack str = B.unsafeCreate (P.length str) $ \(Ptr p) -> stToIO (go p str)
302   where
303     go :: Addr# -> [Char] -> ST a ()
304     go _ []        = return ()
305     go p (C# c:cs) = writeByte p (unsafeCoerce# c) >> go (p `plusAddr#` 1#) cs
306
307     writeByte p c = ST $ \s# ->
308         case writeWord8OffAddr# p 0# c s# of s2# -> (# s2#, () #)
309     {-# INLINE writeByte #-}
310
311 {-# RULES
312 "pack/packAddress" forall s# .
313                    pack (unpackCString# s#) = B.packAddress s#
314  #-}
315
316 #endif
317
318 {-# INLINE pack #-}
319
320 -- | /O(n)/ Converts a 'ByteString' to a 'String'.
321 unpack :: ByteString -> [Char]
322 unpack = P.map w2c . B.unpack
323 {-# INLINE unpack #-}
324
325 -- | /O(n)/ 'cons' is analogous to (:) for lists, but of different
326 -- complexity, as it requires a memcpy.
327 cons :: Char -> ByteString -> ByteString
328 cons = B.cons . c2w
329 {-# INLINE cons #-}
330
331 -- | /O(n)/ Append a Char to the end of a 'ByteString'. Similar to
332 -- 'cons', this function performs a memcpy.
333 snoc :: ByteString -> Char -> ByteString
334 snoc p = B.snoc p . c2w
335 {-# INLINE snoc #-}
336
337 -- | /O(1)/ Extract the first element of a ByteString, which must be non-empty.
338 head :: ByteString -> Char
339 head = w2c . B.head
340 {-# INLINE head #-}
341
342 -- | /O(1)/ Extract the last element of a packed string, which must be non-empty.
343 last :: ByteString -> Char
344 last = w2c . B.last
345 {-# INLINE last #-}
346
347 -- | /O(n)/ 'map' @f xs@ is the ByteString obtained by applying @f@ to each element of @xs@
348 map :: (Char -> Char) -> ByteString -> ByteString
349 map f = B.map (c2w . f . w2c)
350 {-# INLINE map #-}
351
352 -- | /O(n)/ The 'intersperse' function takes a Char and a 'ByteString'
353 -- and \`intersperses\' that Char between the elements of the
354 -- 'ByteString'.  It is analogous to the intersperse function on Lists.
355 intersperse :: Char -> ByteString -> ByteString
356 intersperse = B.intersperse . c2w
357 {-# INLINE intersperse #-}
358
359 -- | 'foldl', applied to a binary operator, a starting value (typically
360 -- the left-identity of the operator), and a ByteString, reduces the
361 -- ByteString using the binary operator, from left to right.
362 foldl :: (a -> Char -> a) -> a -> ByteString -> a
363 foldl f = B.foldl (\a c -> f a (w2c c))
364 {-# INLINE foldl #-}
365
366 -- | 'foldl\'' is like foldl, but strict in the accumulator.
367 foldl' :: (a -> Char -> a) -> a -> ByteString -> a
368 foldl' f = B.foldl' (\a c -> f a (w2c c))
369 {-# INLINE foldl' #-}
370
371 -- | 'foldr', applied to a binary operator, a starting value
372 -- (typically the right-identity of the operator), and a packed string,
373 -- reduces the packed string using the binary operator, from right to left.
374 foldr :: (Char -> a -> a) -> a -> ByteString -> a
375 foldr f = B.foldr (\c a -> f (w2c c) a)
376 {-# INLINE foldr #-}
377
378 -- | 'foldr\'' is a strict variant of foldr
379 foldr' :: (Char -> a -> a) -> a -> ByteString -> a
380 foldr' f = B.foldr' (\c a -> f (w2c c) a)
381 {-# INLINE foldr' #-}
382
383 -- | 'foldl1' is a variant of 'foldl' that has no starting value
384 -- argument, and thus must be applied to non-empty 'ByteStrings'.
385 foldl1 :: (Char -> Char -> Char) -> ByteString -> Char
386 foldl1 f ps = w2c (B.foldl1 (\x y -> c2w (f (w2c x) (w2c y))) ps)
387 {-# INLINE foldl1 #-}
388
389 -- | A strict version of 'foldl1'
390 foldl1' :: (Char -> Char -> Char) -> ByteString -> Char
391 foldl1' f ps = w2c (B.foldl1' (\x y -> c2w (f (w2c x) (w2c y))) ps)
392 {-# INLINE foldl1' #-}
393
394 -- | 'foldr1' is a variant of 'foldr' that has no starting value argument,
395 -- and thus must be applied to non-empty 'ByteString's
396 foldr1 :: (Char -> Char -> Char) -> ByteString -> Char
397 foldr1 f ps = w2c (B.foldr1 (\x y -> c2w (f (w2c x) (w2c y))) ps)
398 {-# INLINE foldr1 #-}
399
400 -- | A strict variant of foldr1
401 foldr1' :: (Char -> Char -> Char) -> ByteString -> Char
402 foldr1' f ps = w2c (B.foldr1' (\x y -> c2w (f (w2c x) (w2c y))) ps)
403 {-# INLINE foldr1' #-}
404
405 -- | Map a function over a 'ByteString' and concatenate the results
406 concatMap :: (Char -> ByteString) -> ByteString -> ByteString
407 concatMap f = B.concatMap (f . w2c)
408 {-# INLINE concatMap #-}
409
410 -- | Applied to a predicate and a ByteString, 'any' determines if
411 -- any element of the 'ByteString' satisfies the predicate.
412 any :: (Char -> Bool) -> ByteString -> Bool
413 any f = B.any (f . w2c)
414 {-# INLINE any #-}
415
416 -- | Applied to a predicate and a 'ByteString', 'all' determines if
417 -- all elements of the 'ByteString' satisfy the predicate.
418 all :: (Char -> Bool) -> ByteString -> Bool
419 all f = B.all (f . w2c)
420 {-# INLINE all #-}
421
422 -- | 'maximum' returns the maximum value from a 'ByteString'
423 maximum :: ByteString -> Char
424 maximum = w2c . B.maximum
425 {-# INLINE maximum #-}
426
427 -- | 'minimum' returns the minimum value from a 'ByteString'
428 minimum :: ByteString -> Char
429 minimum = w2c . B.minimum
430 {-# INLINE minimum #-}
431
432 -- | /O(n)/ map Char functions, provided with the index at each position
433 mapIndexed :: (Int -> Char -> Char) -> ByteString -> ByteString
434 mapIndexed f = B.mapIndexed (\i c -> c2w (f i (w2c c)))
435 {-# INLINE mapIndexed #-}
436
437 -- | The 'mapAccumL' function behaves like a combination of 'map' and
438 -- 'foldl'; it applies a function to each element of a ByteString,
439 -- passing an accumulating parameter from left to right, and returning a
440 -- final value of this accumulator together with the new list.
441 mapAccumL :: (acc -> Char -> (acc, Char)) -> acc -> ByteString -> (acc, ByteString)
442 mapAccumL f = B.mapAccumL (\acc w -> case f acc (w2c w) of (acc', c) -> (acc', c2w c))
443
444 -- | The 'mapAccumR' function behaves like a combination of 'map' and
445 -- 'foldr'; it applies a function to each element of a ByteString,
446 -- passing an accumulating parameter from right to left, and returning a
447 -- final value of this accumulator together with the new ByteString.
448 mapAccumR :: (acc -> Char -> (acc, Char)) -> acc -> ByteString -> (acc, ByteString)
449 mapAccumR f = B.mapAccumR (\acc w -> case f acc (w2c w) of (acc', c) -> (acc', c2w c))
450
451 -- | 'scanl' is similar to 'foldl', but returns a list of successive
452 -- reduced values from the left:
453 --
454 -- > scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
455 --
456 -- Note that
457 --
458 -- > last (scanl f z xs) == foldl f z xs.
459 scanl :: (Char -> Char -> Char) -> Char -> ByteString -> ByteString
460 scanl f z = B.scanl (\a b -> c2w (f (w2c a) (w2c b))) (c2w z)
461
462 -- | 'scanl1' is a variant of 'scanl' that has no starting value argument:
463 --
464 -- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
465 scanl1 :: (Char -> Char -> Char) -> ByteString -> ByteString
466 scanl1 f = B.scanl1 (\a b -> c2w (f (w2c a) (w2c b)))
467
468 -- | scanr is the right-to-left dual of scanl.
469 scanr :: (Char -> Char -> Char) -> Char -> ByteString -> ByteString
470 scanr f z = B.scanr (\a b -> c2w (f (w2c a) (w2c b))) (c2w z)
471
472 -- | 'scanr1' is a variant of 'scanr' that has no starting value argument.
473 scanr1 :: (Char -> Char -> Char) -> ByteString -> ByteString
474 scanr1 f = B.scanr1 (\a b -> c2w (f (w2c a) (w2c b)))
475
476 -- | /O(n)/ 'replicate' @n x@ is a ByteString of length @n@ with @x@
477 -- the value of every element. The following holds:
478 --
479 -- > replicate w c = unfoldr w (\u -> Just (u,u)) c
480 --
481 -- This implemenation uses @memset(3)@
482 replicate :: Int -> Char -> ByteString
483 replicate w = B.replicate w . c2w
484 {-# INLINE replicate #-}
485
486 -- | /O(n)/, where /n/ is the length of the result.  The 'unfoldr' 
487 -- function is analogous to the List \'unfoldr\'.  'unfoldr' builds a 
488 -- ByteString from a seed value.  The function takes the element and 
489 -- returns 'Nothing' if it is done producing the ByteString or returns 
490 -- 'Just' @(a,b)@, in which case, @a@ is the next character in the string, 
491 -- and @b@ is the seed value for further production.
492 --
493 -- Examples:
494 --
495 -- > unfoldr (\x -> if x <= '9' then Just (x, succ x) else Nothing) '0' == "0123456789"
496 unfoldr :: (a -> Maybe (Char, a)) -> a -> ByteString
497 unfoldr f x0 = B.unfoldr (fmap k . f) x0
498     where k (i, j) = (c2w i, j)
499
500 -- | /O(n)/ Like 'unfoldr', 'unfoldrN' builds a ByteString from a seed
501 -- value.  However, the length of the result is limited by the first
502 -- argument to 'unfoldrN'.  This function is more efficient than 'unfoldr'
503 -- when the maximum length of the result is known.
504 --
505 -- The following equation relates 'unfoldrN' and 'unfoldr':
506 --
507 -- > unfoldrN n f s == take n (unfoldr f s)
508 unfoldrN :: Int -> (a -> Maybe (Char, a)) -> a -> (ByteString, Maybe a)
509 unfoldrN n f w = B.unfoldrN n ((k `fmap`) . f) w
510     where k (i,j) = (c2w i, j)
511 {-# INLINE unfoldrN #-}
512
513 -- | 'takeWhile', applied to a predicate @p@ and a ByteString @xs@,
514 -- returns the longest prefix (possibly empty) of @xs@ of elements that
515 -- satisfy @p@.
516 takeWhile :: (Char -> Bool) -> ByteString -> ByteString
517 takeWhile f = B.takeWhile (f . w2c)
518 {-# INLINE takeWhile #-}
519
520 -- | 'dropWhile' @p xs@ returns the suffix remaining after 'takeWhile' @p xs@.
521 dropWhile :: (Char -> Bool) -> ByteString -> ByteString
522 dropWhile f = B.dropWhile (f . w2c)
523 {-# INLINE dropWhile #-}
524
525 -- | 'break' @p@ is equivalent to @'span' ('not' . p)@.
526 break :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
527 break f = B.break (f . w2c)
528 {-# INLINE break #-}
529
530 -- | 'span' @p xs@ breaks the ByteString into two segments. It is
531 -- equivalent to @('takeWhile' p xs, 'dropWhile' p xs)@
532 span :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
533 span f = B.span (f . w2c)
534 {-# INLINE span #-}
535
536 -- | 'spanEnd' behaves like 'span' but from the end of the 'ByteString'.
537 -- We have
538 --
539 -- > spanEnd (not.isSpace) "x y z" == ("x y ","z")
540 --
541 -- and
542 --
543 -- > spanEnd (not . isSpace) ps
544 -- >    == 
545 -- > let (x,y) = span (not.isSpace) (reverse ps) in (reverse y, reverse x) 
546 --
547 spanEnd :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
548 spanEnd f = B.spanEnd (f . w2c)
549 {-# INLINE spanEnd #-}
550
551 -- | 'breakEnd' behaves like 'break' but from the end of the 'ByteString'
552 -- 
553 -- breakEnd p == spanEnd (not.p)
554 breakEnd :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
555 breakEnd f = B.breakEnd (f . w2c)
556 {-# INLINE breakEnd #-}
557
558 {-
559 -- | 'breakChar' breaks its ByteString argument at the first occurence
560 -- of the specified Char. It is more efficient than 'break' as it is
561 -- implemented with @memchr(3)@. I.e.
562 -- 
563 -- > break (=='c') "abcd" == breakChar 'c' "abcd"
564 --
565 breakChar :: Char -> ByteString -> (ByteString, ByteString)
566 breakChar = B.breakByte . c2w
567 {-# INLINE breakChar #-}
568
569 -- | 'spanChar' breaks its ByteString argument at the first
570 -- occurence of a Char other than its argument. It is more efficient
571 -- than 'span (==)'
572 --
573 -- > span  (=='c') "abcd" == spanByte 'c' "abcd"
574 --
575 spanChar :: Char -> ByteString -> (ByteString, ByteString)
576 spanChar = B.spanByte . c2w
577 {-# INLINE spanChar #-}
578 -}
579
580 -- | /O(n)/ Break a 'ByteString' into pieces separated by the byte
581 -- argument, consuming the delimiter. I.e.
582 --
583 -- > split '\n' "a\nb\nd\ne" == ["a","b","d","e"]
584 -- > split 'a'  "aXaXaXa"    == ["","X","X","X"]
585 -- > split 'x'  "x"          == ["",""]
586 -- 
587 -- and
588 --
589 -- > join [c] . split c == id
590 -- > split == splitWith . (==)
591 -- 
592 -- As for all splitting functions in this library, this function does
593 -- not copy the substrings, it just constructs new 'ByteStrings' that
594 -- are slices of the original.
595 --
596 split :: Char -> ByteString -> [ByteString]
597 split = B.split . c2w
598 {-# INLINE split #-}
599
600 -- | /O(n)/ Splits a 'ByteString' into components delimited by
601 -- separators, where the predicate returns True for a separator element.
602 -- The resulting components do not contain the separators.  Two adjacent
603 -- separators result in an empty component in the output.  eg.
604 --
605 -- > splitWith (=='a') "aabbaca" == ["","","bb","c",""]
606 --
607 splitWith :: (Char -> Bool) -> ByteString -> [ByteString]
608 splitWith f = B.splitWith (f . w2c)
609 {-# INLINE splitWith #-}
610 -- the inline makes a big difference here.
611
612 {-
613 -- | Like 'splitWith', except that sequences of adjacent separators are
614 -- treated as a single separator. eg.
615 -- 
616 -- > tokens (=='a') "aabbaca" == ["bb","c"]
617 --
618 tokens :: (Char -> Bool) -> ByteString -> [ByteString]
619 tokens f = B.tokens (f . w2c)
620 {-# INLINE tokens #-}
621 -}
622
623 -- | The 'groupBy' function is the non-overloaded version of 'group'.
624 groupBy :: (Char -> Char -> Bool) -> ByteString -> [ByteString]
625 groupBy k = B.groupBy (\a b -> k (w2c a) (w2c b))
626
627 {-
628 -- | /O(n)/ joinWithChar. An efficient way to join to two ByteStrings with a
629 -- char. Around 4 times faster than the generalised join.
630 --
631 joinWithChar :: Char -> ByteString -> ByteString -> ByteString
632 joinWithChar = B.joinWithByte . c2w
633 {-# INLINE joinWithChar #-}
634 -}
635
636 -- | /O(1)/ 'ByteString' index (subscript) operator, starting from 0.
637 index :: ByteString -> Int -> Char
638 index = (w2c .) . B.index
639 {-# INLINE index #-}
640
641 -- | /O(n)/ The 'elemIndex' function returns the index of the first
642 -- element in the given 'ByteString' which is equal (by memchr) to the
643 -- query element, or 'Nothing' if there is no such element.
644 elemIndex :: Char -> ByteString -> Maybe Int
645 elemIndex = B.elemIndex . c2w
646 {-# INLINE elemIndex #-}
647
648 -- | /O(n)/ The 'elemIndexEnd' function returns the last index of the
649 -- element in the given 'ByteString' which is equal to the query
650 -- element, or 'Nothing' if there is no such element. The following
651 -- holds:
652 --
653 -- > elemIndexEnd c xs == 
654 -- > (-) (length xs - 1) `fmap` elemIndex c (reverse xs)
655 --
656 elemIndexEnd :: Char -> ByteString -> Maybe Int
657 elemIndexEnd = B.elemIndexEnd . c2w
658 {-# INLINE elemIndexEnd #-}
659
660 -- | /O(n)/ The 'elemIndices' function extends 'elemIndex', by returning
661 -- the indices of all elements equal to the query element, in ascending order.
662 elemIndices :: Char -> ByteString -> [Int]
663 elemIndices = B.elemIndices . c2w
664 {-# INLINE elemIndices #-}
665
666 -- | The 'findIndex' function takes a predicate and a 'ByteString' and
667 -- returns the index of the first element in the ByteString satisfying the predicate.
668 findIndex :: (Char -> Bool) -> ByteString -> Maybe Int
669 findIndex f = B.findIndex (f . w2c)
670 {-# INLINE findIndex #-}
671
672 -- | The 'findIndices' function extends 'findIndex', by returning the
673 -- indices of all elements satisfying the predicate, in ascending order.
674 findIndices :: (Char -> Bool) -> ByteString -> [Int]
675 findIndices f = B.findIndices (f . w2c)
676
677 -- | count returns the number of times its argument appears in the ByteString
678 --
679 -- > count = length . elemIndices
680 -- 
681 -- Also
682 --  
683 -- > count '\n' == length . lines
684 --
685 -- But more efficiently than using length on the intermediate list.
686 count :: Char -> ByteString -> Int
687 count c = B.count (c2w c)
688
689 -- | /O(n)/ 'elem' is the 'ByteString' membership predicate. This
690 -- implementation uses @memchr(3)@.
691 elem :: Char -> ByteString -> Bool
692 elem    c = B.elem (c2w c)
693 {-# INLINE elem #-}
694
695 -- | /O(n)/ 'notElem' is the inverse of 'elem'
696 notElem :: Char -> ByteString -> Bool
697 notElem c = B.notElem (c2w c)
698 {-# INLINE notElem #-}
699
700 -- | /O(n)/ 'filter', applied to a predicate and a ByteString,
701 -- returns a ByteString containing those characters that satisfy the
702 -- predicate.
703 filter :: (Char -> Bool) -> ByteString -> ByteString
704 filter f = B.filter (f . w2c)
705 {-# INLINE filter #-}
706
707 -- | /O(n)/ The 'find' function takes a predicate and a ByteString,
708 -- and returns the first element in matching the predicate, or 'Nothing'
709 -- if there is no such element.
710 find :: (Char -> Bool) -> ByteString -> Maybe Char
711 find f ps = w2c `fmap` B.find (f . w2c) ps
712 {-# INLINE find #-}
713
714 {-
715 -- | /O(n)/ A first order equivalent of /filter . (==)/, for the common
716 -- case of filtering a single Char. It is more efficient to use
717 -- filterChar in this case.
718 --
719 -- > filterChar == filter . (==)
720 --
721 -- filterChar is around 10x faster, and uses much less space, than its
722 -- filter equivalent
723 --
724 filterChar :: Char -> ByteString -> ByteString
725 filterChar c = B.filterByte (c2w c)
726 {-# INLINE filterChar #-}
727
728 -- | /O(n)/ A first order equivalent of /filter . (\/=)/, for the common
729 -- case of filtering a single Char out of a list. It is more efficient
730 -- to use /filterNotChar/ in this case.
731 --
732 -- > filterNotChar == filter . (/=)
733 --
734 -- filterNotChar is around 3x faster, and uses much less space, than its
735 -- filter equivalent
736 --
737 filterNotChar :: Char -> ByteString -> ByteString
738 filterNotChar c = B.filterNotByte (c2w c)
739 {-# INLINE filterNotChar #-}
740 -}
741
742 -- | /O(n)/ 'zip' takes two ByteStrings and returns a list of
743 -- corresponding pairs of Chars. If one input ByteString is short,
744 -- excess elements of the longer ByteString are discarded. This is
745 -- equivalent to a pair of 'unpack' operations, and so space
746 -- usage may be large for multi-megabyte ByteStrings
747 zip :: ByteString -> ByteString -> [(Char,Char)]
748 zip ps qs
749     | B.null ps || B.null qs = []
750     | otherwise = (unsafeHead ps, unsafeHead qs) : zip (B.unsafeTail ps) (B.unsafeTail qs)
751
752 -- | 'zipWith' generalises 'zip' by zipping with the function given as
753 -- the first argument, instead of a tupling function.  For example,
754 -- @'zipWith' (+)@ is applied to two ByteStrings to produce the list
755 -- of corresponding sums.
756 zipWith :: (Char -> Char -> a) -> ByteString -> ByteString -> [a]
757 zipWith f = B.zipWith ((. w2c) . f . w2c)
758
759 -- | 'unzip' transforms a list of pairs of Chars into a pair of
760 -- ByteStrings. Note that this performs two 'pack' operations.
761 unzip :: [(Char,Char)] -> (ByteString,ByteString)
762 unzip ls = (pack (P.map fst ls), pack (P.map snd ls))
763 {-# INLINE unzip #-}
764
765 -- | A variety of 'head' for non-empty ByteStrings. 'unsafeHead' omits
766 -- the check for the empty case, which is good for performance, but
767 -- there is an obligation on the programmer to provide a proof that the
768 -- ByteString is non-empty.
769 unsafeHead :: ByteString -> Char
770 unsafeHead  = w2c . B.unsafeHead
771 {-# INLINE unsafeHead #-}
772
773 -- ---------------------------------------------------------------------
774 -- Things that depend on the encoding
775
776 {-# RULES
777     "FPS specialise break -> breakSpace"
778         break isSpace = breakSpace
779   #-}
780
781 -- | 'breakSpace' returns the pair of ByteStrings when the argument is
782 -- broken at the first whitespace byte. I.e.
783 -- 
784 -- > break isSpace == breakSpace
785 --
786 breakSpace :: ByteString -> (ByteString,ByteString)
787 breakSpace (PS x s l) = inlinePerformIO $ withForeignPtr x $ \p -> do
788     i <- firstspace (p `plusPtr` s) 0 l
789     return $! case () of {_
790         | i == 0    -> (empty, PS x s l)
791         | i == l    -> (PS x s l, empty)
792         | otherwise -> (PS x s i, PS x (s+i) (l-i))
793     }
794 {-# INLINE breakSpace #-}
795
796 firstspace :: Ptr Word8 -> Int -> Int -> IO Int
797 STRICT3(firstspace)
798 firstspace ptr n m
799     | n >= m    = return n
800     | otherwise = do w <- peekByteOff ptr n
801                      if (not . isSpaceWord8) w then firstspace ptr (n+1) m else return n
802
803 {-# RULES
804     "FPS specialise dropWhile isSpace -> dropSpace"
805         dropWhile isSpace = dropSpace
806   #-}
807
808 -- | 'dropSpace' efficiently returns the 'ByteString' argument with
809 -- white space Chars removed from the front. It is more efficient than
810 -- calling dropWhile for removing whitespace. I.e.
811 -- 
812 -- > dropWhile isSpace == dropSpace
813 --
814 dropSpace :: ByteString -> ByteString
815 dropSpace (PS x s l) = inlinePerformIO $ withForeignPtr x $ \p -> do
816     i <- firstnonspace (p `plusPtr` s) 0 l
817     return $! if i == l then empty else PS x (s+i) (l-i)
818 {-# INLINE dropSpace #-}
819
820 firstnonspace :: Ptr Word8 -> Int -> Int -> IO Int
821 STRICT3(firstnonspace)
822 firstnonspace ptr n m
823     | n >= m    = return n
824     | otherwise = do w <- peekElemOff ptr n
825                      if isSpaceWord8 w then firstnonspace ptr (n+1) m else return n
826
827 {-
828 -- | 'dropSpaceEnd' efficiently returns the 'ByteString' argument with
829 -- white space removed from the end. I.e.
830 -- 
831 -- > reverse . (dropWhile isSpace) . reverse == dropSpaceEnd
832 --
833 -- but it is more efficient than using multiple reverses.
834 --
835 dropSpaceEnd :: ByteString -> ByteString
836 dropSpaceEnd (PS x s l) = inlinePerformIO $ withForeignPtr x $ \p -> do
837     i <- lastnonspace (p `plusPtr` s) (l-1)
838     return $! if i == (-1) then empty else PS x s (i+1)
839 {-# INLINE dropSpaceEnd #-}
840
841 lastnonspace :: Ptr Word8 -> Int -> IO Int
842 STRICT2(lastnonspace)
843 lastnonspace ptr n
844     | n < 0     = return n
845     | otherwise = do w <- peekElemOff ptr n
846                      if isSpaceWord8 w then lastnonspace ptr (n-1) else return n
847 -}
848
849 -- | 'lines' breaks a ByteString up into a list of ByteStrings at
850 -- newline Chars. The resulting strings do not contain newlines.
851 --
852 lines :: ByteString -> [ByteString]
853 lines ps
854     | null ps = []
855     | otherwise = case search ps of
856              Nothing -> [ps]
857              Just n  -> take n ps : lines (drop (n+1) ps)
858     where search = elemIndex '\n'
859 {-# INLINE lines #-}
860
861 {-
862 -- Just as fast, but more complex. Should be much faster, I thought.
863 lines :: ByteString -> [ByteString]
864 lines (PS _ _ 0) = []
865 lines (PS x s l) = inlinePerformIO $ withForeignPtr x $ \p -> do
866         let ptr = p `plusPtr` s
867
868             STRICT1(loop)
869             loop n = do
870                 let q = memchr (ptr `plusPtr` n) 0x0a (fromIntegral (l-n))
871                 if q == nullPtr
872                     then return [PS x (s+n) (l-n)]
873                     else do let i = q `minusPtr` ptr
874                             ls <- loop (i+1)
875                             return $! PS x (s+n) (i-n) : ls
876         loop 0
877 -}
878
879 -- | 'unlines' is an inverse operation to 'lines'.  It joins lines,
880 -- after appending a terminating newline to each.
881 unlines :: [ByteString] -> ByteString
882 unlines [] = empty
883 unlines ss = (concat $ List.intersperse nl ss) `append` nl -- half as much space
884     where nl = singleton '\n'
885
886 -- | 'words' breaks a ByteString up into a list of words, which
887 -- were delimited by Chars representing white space. And
888 --
889 -- > tokens isSpace = words
890 --
891 words :: ByteString -> [ByteString]
892 words = P.filter (not . B.null) . B.splitWith isSpaceWord8
893 {-# INLINE words #-}
894
895 -- | The 'unwords' function is analogous to the 'unlines' function, on words.
896 unwords :: [ByteString] -> ByteString
897 unwords = join (singleton ' ')
898 {-# INLINE unwords #-}
899
900 -- ---------------------------------------------------------------------
901 -- Reading from ByteStrings
902
903 -- | readInt reads an Int from the beginning of the ByteString.  If there is no
904 -- integer at the beginning of the string, it returns Nothing, otherwise
905 -- it just returns the int read, and the rest of the string.
906 readInt :: ByteString -> Maybe (Int, ByteString)
907 readInt as
908     | null as   = Nothing
909     | otherwise =
910         case unsafeHead as of
911             '-' -> loop True  0 0 (unsafeTail as)
912             '+' -> loop False 0 0 (unsafeTail as)
913             _   -> loop False 0 0 as
914
915     where loop :: Bool -> Int -> Int -> ByteString -> Maybe (Int, ByteString)
916           STRICT4(loop)
917           loop neg i n ps
918               | null ps   = end neg i n ps
919               | otherwise =
920                   case B.unsafeHead ps of
921                     w | w >= 0x30
922                      && w <= 0x39 -> loop neg (i+1)
923                                           (n * 10 + (fromIntegral w - 0x30))
924                                           (unsafeTail ps)
925                       | otherwise -> end neg i n ps
926
927           end _    0 _ _  = Nothing
928           end True _ n ps = Just (negate n, ps)
929           end _    _ n ps = Just (n, ps)
930
931 -- | Read an entire file strictly into a 'ByteString'.  This is far more
932 -- efficient than reading the characters into a 'String' and then using
933 -- 'pack'.  It also may be more efficient than opening the file and
934 -- reading it using hGet.
935 readFile :: FilePath -> IO ByteString
936 readFile f = bracket (openFile f ReadMode) hClose
937     (\h -> hFileSize h >>= hGet h . fromIntegral)
938
939 -- | Write a 'ByteString' to a file.
940 writeFile :: FilePath -> ByteString -> IO ()
941 writeFile f txt = bracket (openFile f WriteMode) hClose
942     (\h -> hPut h txt)
943
944 -- | Append a 'ByteString' to a file.
945 appendFile :: FilePath -> ByteString -> IO ()
946 appendFile f txt = bracket (openFile f AppendMode) hClose
947     (\h -> hPut h txt)
948