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