15af132c9b75f7ece4c4140dc0f8ba86d084e7de
[ghc-base.git] / Data / ByteString / Lazy / Char8.hs
1 {-# OPTIONS_GHC -cpp -optc-O1 -fno-warn-orphans #-}
2 --
3 -- -optc-O2 breaks with 4.0.4 gcc on debian
4 --
5 -- Module      : Data.ByteString.Lazy.Char8
6 -- Copyright   : (c) Don Stewart 2006
7 -- License     : BSD-style
8 --
9 -- Maintainer  : dons@cse.unsw.edu.au
10 -- Stability   : experimental
11 -- Portability : portable (tested with GHC>=6.4.1 and Hugs 2005)
12 -- 
13
14 --
15 -- | Manipulate /lazy/ 'ByteString's using 'Char' operations. All Chars will
16 -- be truncated to 8 bits. It can be expected that these functions will
17 -- run at identical speeds to their Word8 equivalents in
18 -- "Data.ByteString.Lazy".
19 --
20 -- This module is intended to be imported @qualified@, to avoid name
21 -- clashes with "Prelude" functions.  eg.
22 --
23 -- > import qualified Data.ByteString.Lazy.Char8 as C
24 --
25
26 module Data.ByteString.Lazy.Char8 (
27
28         -- * The @ByteString@ type
29         ByteString(..),         -- instances: Eq, Ord, Show, Read, Data, Typeable
30
31         -- * Introducing and eliminating 'ByteString's
32         empty,                  -- :: ByteString
33         singleton,               -- :: Char   -> ByteString
34         pack,                   -- :: String -> ByteString
35         unpack,                 -- :: ByteString -> String
36
37         -- * Basic interface
38         cons,                   -- :: Char -> ByteString -> ByteString
39         snoc,                   -- :: ByteString -> Char -> ByteString
40         append,                 -- :: ByteString -> ByteString -> ByteString
41         head,                   -- :: ByteString -> Char
42         last,                   -- :: ByteString -> Char
43         tail,                   -- :: ByteString -> ByteString
44         init,                   -- :: ByteString -> ByteString
45         null,                   -- :: ByteString -> Bool
46         length,                 -- :: ByteString -> Int64
47
48         -- * Transformating ByteStrings
49         map,                    -- :: (Char -> Char) -> ByteString -> ByteString
50         reverse,                -- :: ByteString -> ByteString
51 --      intersperse,            -- :: Char -> ByteString -> ByteString
52         transpose,              -- :: [ByteString] -> [ByteString]
53
54         -- * Reducing 'ByteString's (folds)
55         foldl,                  -- :: (a -> Char -> a) -> a -> ByteString -> a
56         foldl',                 -- :: (a -> Char -> a) -> a -> ByteString -> a
57         foldl1,                 -- :: (Char -> Char -> Char) -> ByteString -> Char
58         foldl1',                -- :: (Char -> Char -> Char) -> ByteString -> Char
59         foldr,                  -- :: (Char -> a -> a) -> a -> ByteString -> a
60         foldr1,                 -- :: (Char -> Char -> Char) -> ByteString -> Char
61
62         -- ** Special folds
63         concat,                 -- :: [ByteString] -> ByteString
64         concatMap,              -- :: (Char -> ByteString) -> ByteString -> ByteString
65         any,                    -- :: (Char -> Bool) -> ByteString -> Bool
66         all,                    -- :: (Char -> Bool) -> ByteString -> Bool
67         maximum,                -- :: ByteString -> Char
68         minimum,                -- :: ByteString -> Char
69
70         -- * Building ByteStrings
71         -- ** Scans
72         scanl,                  -- :: (Char -> Char -> Char) -> Char -> ByteString -> ByteString
73 --      scanl1,                 -- :: (Char -> Char -> Char) -> ByteString -> ByteString
74 --      scanr,                  -- :: (Char -> Char -> Char) -> Char -> ByteString -> ByteString
75 --      scanr1,                 -- :: (Char -> Char -> Char) -> ByteString -> ByteString
76
77         -- ** Accumulating maps
78         mapAccumL,   -- :: (acc -> Char -> (acc, Char)) -> acc -> ByteString -> (acc, ByteString)
79         mapIndexed,  -- :: (Int64 -> Char -> Char) -> ByteString -> ByteString
80
81         -- ** Infinite ByteStrings
82         repeat,                 -- :: Char -> ByteString
83         replicate,              -- :: Int64 -> Char -> ByteString
84         cycle,                  -- :: ByteString -> ByteString
85         iterate,                -- :: (Char -> Char) -> Char -> ByteString
86
87         -- ** Unfolding
88         unfoldr,                -- :: (a -> Maybe (Char, a)) -> a -> ByteString
89
90         -- * Substrings
91
92         -- ** Breaking strings
93         take,                   -- :: Int64 -> ByteString -> ByteString
94         drop,                   -- :: Int64 -> ByteString -> ByteString
95         splitAt,                -- :: Int64 -> ByteString -> (ByteString, ByteString)
96         takeWhile,              -- :: (Char -> Bool) -> ByteString -> ByteString
97         dropWhile,              -- :: (Char -> Bool) -> ByteString -> ByteString
98         span,                   -- :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
99         break,                  -- :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
100         group,                  -- :: ByteString -> [ByteString]
101         groupBy,                -- :: (Char -> Char -> Bool) -> ByteString -> [ByteString]
102         inits,                  -- :: ByteString -> [ByteString]
103         tails,                  -- :: ByteString -> [ByteString]
104
105         -- ** Breaking and dropping on specific Chars
106         breakChar,              -- :: Char -> ByteString -> (ByteString, ByteString)
107         spanChar,               -- :: Char -> ByteString -> (ByteString, ByteString)
108
109         -- ** Breaking into many substrings
110         split,                  -- :: Char -> ByteString -> [ByteString]
111         splitWith,              -- :: (Char -> Bool) -> ByteString -> [ByteString]
112         tokens,                 -- :: (Char -> Bool) -> ByteString -> [ByteString]
113
114         -- ** Breaking into lines and words
115         lines,                  -- :: ByteString -> [ByteString]
116         words,                  -- :: ByteString -> [ByteString]
117         unlines,                -- :: [ByteString] -> ByteString
118         unwords,                -- :: ByteString -> [ByteString]
119
120         -- ** Joining strings
121         join,                   -- :: ByteString -> [ByteString] -> ByteString
122         joinWithChar,           -- :: Char -> ByteString -> ByteString -> ByteString
123
124         -- * Predicates
125         isPrefixOf,             -- :: ByteString -> ByteString -> Bool
126 --      isSuffixOf,             -- :: ByteString -> ByteString -> Bool
127
128         -- * Searching ByteStrings
129
130         -- ** Searching by equality
131         elem,                   -- :: Char -> ByteString -> Bool
132         notElem,                -- :: Char -> ByteString -> Bool
133         filterChar,             -- :: Char -> ByteString -> ByteString
134         filterNotChar,          -- :: Char -> ByteString -> ByteString
135
136         -- ** Searching with a predicate
137         find,                   -- :: (Char -> Bool) -> ByteString -> Maybe Char
138         filter,                 -- :: (Char -> Bool) -> ByteString -> ByteString
139 --      partition               -- :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
140
141         -- * Indexing ByteStrings
142         index,                  -- :: ByteString -> Int64 -> Char
143         elemIndex,              -- :: Char -> ByteString -> Maybe Int64
144         elemIndices,            -- :: Char -> ByteString -> [Int64]
145         findIndex,              -- :: (Char -> Bool) -> ByteString -> Maybe Int64
146         findIndices,            -- :: (Char -> Bool) -> ByteString -> [Int64]
147         count,                  -- :: Char -> ByteString -> Int64
148
149         -- * Zipping and unzipping ByteStrings
150         zip,                    -- :: ByteString -> ByteString -> [(Char,Char)]
151         zipWith,                -- :: (Char -> Char -> c) -> ByteString -> ByteString -> [c]
152 --      unzip,                  -- :: [(Char,Char)] -> (ByteString,ByteString)
153
154         -- * Ordered ByteStrings
155 --        sort,                   -- :: ByteString -> ByteString
156
157         -- * Reading from ByteStrings
158         readInt,
159
160         -- * I\/O with 'ByteString's
161
162         -- ** Standard input and output
163         getContents,            -- :: IO ByteString
164         putStr,                 -- :: ByteString -> IO ()
165         putStrLn,               -- :: ByteString -> IO ()
166         interact,               -- :: (ByteString -> ByteString) -> IO ()
167
168         -- ** Files
169         readFile,               -- :: FilePath -> IO ByteString
170         writeFile,              -- :: FilePath -> ByteString -> IO ()
171         appendFile,             -- :: FilePath -> ByteString -> IO ()
172
173         -- ** I\/O with Handles
174         hGetContents,           -- :: Handle -> IO ByteString
175         hGetContentsN,          -- :: Int -> Handle -> IO ByteString
176         hGet,                   -- :: Handle -> Int64 -> IO ByteString
177         hGetN,                  -- :: Int -> Handle -> Int64 -> IO ByteString
178         hPut,                   -- :: Handle -> ByteString -> IO ()
179 #if defined(__GLASGOW_HASKELL__)
180         hGetNonBlocking,        -- :: Handle -> IO ByteString
181         hGetNonBlockingN,       -- :: Int -> Handle -> IO ByteString
182 #endif
183   ) where
184
185 -- Functions transparently exported
186 import Data.ByteString.Lazy 
187         (ByteString(..)
188         ,empty,null,length,tail,init,append,reverse,transpose
189         ,concat,take,drop,splitAt,join,isPrefixOf,group,inits, tails
190         ,hGetContentsN, hGetN, hGetContents, hGet, hPut, getContents
191 #if defined(__GLASGOW_HASKELL__)
192         ,hGetNonBlocking, hGetNonBlockingN
193 #endif
194         ,putStr, putStrLn
195         ,readFile, writeFile, appendFile)
196
197 -- Functions we need to wrap.
198 import qualified Data.ByteString.Lazy as L
199 import qualified Data.ByteString as B
200 import qualified Data.ByteString.Base as B
201 import Data.ByteString.Base (w2c, c2w, isSpaceWord8)
202
203 import Data.Int (Int64)
204 import qualified Data.List as List (intersperse)
205
206 import qualified Prelude as P
207 import Prelude hiding           
208         (reverse,head,tail,last,init,null,length,map,lines,foldl,foldr,unlines
209         ,concat,any,take,drop,splitAt,takeWhile,dropWhile,span,break,elem,filter
210         ,unwords,words,maximum,minimum,all,concatMap,scanl,scanl1,foldl1,foldr1
211         ,readFile,writeFile,appendFile,replicate,getContents,getLine,putStr,putStrLn
212         ,zip,zipWith,unzip,notElem,repeat,iterate)
213
214 #define STRICT1(f) f a | a `seq` False = undefined
215 #define STRICT2(f) f a b | a `seq` b `seq` False = undefined
216 #define STRICT3(f) f a b c | a `seq` b `seq` c `seq` False = undefined
217 #define STRICT4(f) f a b c d | a `seq` b `seq` c `seq` d `seq` False = undefined
218 #define STRICT5(f) f a b c d e | a `seq` b `seq` c `seq` d `seq` e `seq` False = undefined
219
220 ------------------------------------------------------------------------
221
222 -- | /O(1)/ Convert a 'Char' into a 'ByteString'
223 singleton :: Char -> ByteString
224 singleton = L.singleton . c2w
225 {-# INLINE singleton #-}
226
227 -- | /O(n)/ Convert a 'String' into a 'ByteString'. 
228 pack :: [Char] -> ByteString
229 pack = L.packWith c2w
230
231 -- | /O(n)/ Converts a 'ByteString' to a 'String'.
232 unpack :: ByteString -> [Char]
233 unpack = L.unpackWith w2c
234 {-# INLINE unpack #-}
235
236 -- | /O(n)/ 'cons' is analogous to (:) for lists, but of different
237 -- complexity, as it requires a memcpy.
238 cons :: Char -> ByteString -> ByteString
239 cons = L.cons . c2w
240 {-# INLINE cons #-}
241
242 -- | /O(n)/ Append a Char to the end of a 'ByteString'. Similar to
243 -- 'cons', this function performs a memcpy.
244 snoc :: ByteString -> Char -> ByteString
245 snoc p = L.snoc p . c2w
246 {-# INLINE snoc #-}
247
248 -- | /O(1)/ Extract the first element of a ByteString, which must be non-empty.
249 head :: ByteString -> Char
250 head = w2c . L.head
251 {-# INLINE head #-}
252
253 -- | /O(1)/ Extract the last element of a packed string, which must be non-empty.
254 last :: ByteString -> Char
255 last = w2c . L.last
256 {-# INLINE last #-}
257
258 -- | /O(n)/ 'map' @f xs@ is the ByteString obtained by applying @f@ to each element of @xs@
259 map :: (Char -> Char) -> ByteString -> ByteString
260 map f = L.map (c2w . f . w2c)
261 {-# INLINE map #-}
262
263 -- | 'foldl', applied to a binary operator, a starting value (typically
264 -- the left-identity of the operator), and a ByteString, reduces the
265 -- ByteString using the binary operator, from left to right.
266 foldl :: (a -> Char -> a) -> a -> ByteString -> a
267 foldl f = L.foldl (\a c -> f a (w2c c))
268 {-# INLINE foldl #-}
269
270 -- | 'foldl\'' is like foldl, but strict in the accumulator.
271 foldl' :: (a -> Char -> a) -> a -> ByteString -> a
272 foldl' f = L.foldl' (\a c -> f a (w2c c))
273 {-# INLINE foldl' #-}
274
275 -- | 'foldr', applied to a binary operator, a starting value
276 -- (typically the right-identity of the operator), and a packed string,
277 -- reduces the packed string using the binary operator, from right to left.
278 foldr :: (Char -> a -> a) -> a -> ByteString -> a
279 foldr f = L.foldr (\c a -> f (w2c c) a)
280 {-# INLINE foldr #-}
281
282 -- | 'foldl1' is a variant of 'foldl' that has no starting value
283 -- argument, and thus must be applied to non-empty 'ByteStrings'.
284 foldl1 :: (Char -> Char -> Char) -> ByteString -> Char
285 foldl1 f ps = w2c (L.foldl1 (\x y -> c2w (f (w2c x) (w2c y))) ps)
286 {-# INLINE foldl1 #-}
287
288 -- | 'foldl1\'' is like 'foldl1', but strict in the accumulator.
289 foldl1' :: (Char -> Char -> Char) -> ByteString -> Char
290 foldl1' f ps = w2c (L.foldl1' (\x y -> c2w (f (w2c x) (w2c y))) ps)
291
292 -- | 'foldr1' is a variant of 'foldr' that has no starting value argument,
293 -- and thus must be applied to non-empty 'ByteString's
294 foldr1 :: (Char -> Char -> Char) -> ByteString -> Char
295 foldr1 f ps = w2c (L.foldr1 (\x y -> c2w (f (w2c x) (w2c y))) ps)
296 {-# INLINE foldr1 #-}
297
298 -- | Map a function over a 'ByteString' and concatenate the results
299 concatMap :: (Char -> ByteString) -> ByteString -> ByteString
300 concatMap f = L.concatMap (f . w2c)
301 {-# INLINE concatMap #-}
302
303 -- | Applied to a predicate and a ByteString, 'any' determines if
304 -- any element of the 'ByteString' satisfies the predicate.
305 any :: (Char -> Bool) -> ByteString -> Bool
306 any f = L.any (f . w2c)
307 {-# INLINE any #-}
308
309 -- | Applied to a predicate and a 'ByteString', 'all' determines if
310 -- all elements of the 'ByteString' satisfy the predicate.
311 all :: (Char -> Bool) -> ByteString -> Bool
312 all f = L.all (f . w2c)
313 {-# INLINE all #-}
314
315 -- | 'maximum' returns the maximum value from a 'ByteString'
316 maximum :: ByteString -> Char
317 maximum = w2c . L.maximum
318 {-# INLINE maximum #-}
319
320 -- | 'minimum' returns the minimum value from a 'ByteString'
321 minimum :: ByteString -> Char
322 minimum = w2c . L.minimum
323 {-# INLINE minimum #-}
324
325 -- ---------------------------------------------------------------------
326 -- Building ByteStrings
327
328 -- | 'scanl' is similar to 'foldl', but returns a list of successive
329 -- reduced values from the left. This function will fuse.
330 --
331 -- > scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
332 --
333 -- Note that
334 --
335 -- > last (scanl f z xs) == foldl f z xs.
336 scanl :: (Char -> Char -> Char) -> Char -> ByteString -> ByteString
337 scanl f z = L.scanl (\a b -> c2w (f (w2c a) (w2c b))) (c2w z)
338
339 -- | The 'mapAccumL' function behaves like a combination of 'map' and
340 -- 'foldl'; it applies a function to each element of a ByteString,
341 -- passing an accumulating parameter from left to right, and returning a
342 -- final value of this accumulator together with the new ByteString.
343 mapAccumL :: (acc -> Char -> (acc, Char)) -> acc -> ByteString -> (acc, ByteString)
344 mapAccumL f = L.mapAccumL (\a w -> case f a (w2c w) of (a',c) -> (a', c2w c))
345
346 -- | /O(n)/ map Char functions, provided with the index at each position
347 mapIndexed :: (Int -> Char -> Char) -> ByteString -> ByteString
348 mapIndexed f = L.mapIndexed (\i w -> c2w (f i (w2c w)))
349
350 ------------------------------------------------------------------------
351 -- Generating and unfolding ByteStrings
352
353 -- | @'iterate' f x@ returns an infinite ByteString of repeated applications
354 -- of @f@ to @x@:
355 --
356 -- > iterate f x == [x, f x, f (f x), ...]
357 --
358 iterate :: (Char -> Char) -> Char -> ByteString
359 iterate f = L.iterate (c2w . f . w2c) . c2w
360
361 -- | @'repeat' x@ is an infinite ByteString, with @x@ the value of every
362 -- element.
363 --
364 repeat :: Char -> ByteString
365 repeat = L.repeat . c2w
366
367 -- | /O(n)/ @'replicate' n x@ is a ByteString of length @n@ with @x@
368 -- the value of every element.
369 --
370 replicate :: Int64 -> Char -> ByteString
371 replicate w c = L.replicate w (c2w c)
372
373 -- | /O(n)/ The 'unfoldr' function is analogous to the List \'unfoldr\'.
374 -- 'unfoldr' builds a ByteString from a seed value.  The function takes
375 -- the element and returns 'Nothing' if it is done producing the
376 -- ByteString or returns 'Just' @(a,b)@, in which case, @a@ is a
377 -- prepending to the ByteString and @b@ is used as the next element in a
378 -- recursive call.
379 unfoldr :: (a -> Maybe (Char, a)) -> a -> ByteString
380 unfoldr f = L.unfoldr $ \a -> case f a of
381                                     Nothing      -> Nothing
382                                     Just (c, a') -> Just (c2w c, a')
383
384 ------------------------------------------------------------------------
385
386 -- | 'takeWhile', applied to a predicate @p@ and a ByteString @xs@,
387 -- returns the longest prefix (possibly empty) of @xs@ of elements that
388 -- satisfy @p@.
389 takeWhile :: (Char -> Bool) -> ByteString -> ByteString
390 takeWhile f = L.takeWhile (f . w2c)
391 {-# INLINE takeWhile #-}
392
393 -- | 'dropWhile' @p xs@ returns the suffix remaining after 'takeWhile' @p xs@.
394 dropWhile :: (Char -> Bool) -> ByteString -> ByteString
395 dropWhile f = L.dropWhile (f . w2c)
396 {-# INLINE dropWhile #-}
397
398 -- | 'break' @p@ is equivalent to @'span' ('not' . p)@.
399 break :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
400 break f = L.break (f . w2c)
401 {-# INLINE break #-}
402
403 -- | 'span' @p xs@ breaks the ByteString into two segments. It is
404 -- equivalent to @('takeWhile' p xs, 'dropWhile' p xs)@
405 span :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
406 span f = L.span (f . w2c)
407 {-# INLINE span #-}
408
409 -- | 'breakChar' breaks its ByteString argument at the first occurence
410 -- of the specified Char. It is more efficient than 'break' as it is
411 -- implemented with @memchr(3)@. I.e.
412 -- 
413 -- > break (=='c') "abcd" == breakChar 'c' "abcd"
414 --
415 breakChar :: Char -> ByteString -> (ByteString, ByteString)
416 breakChar = L.breakByte . c2w
417 {-# INLINE breakChar #-}
418
419 -- | 'spanChar' breaks its ByteString argument at the first
420 -- occurence of a Char other than its argument. It is more efficient
421 -- than 'span (==)'
422 --
423 -- > span  (=='c') "abcd" == spanByte 'c' "abcd"
424 --
425 spanChar :: Char -> ByteString -> (ByteString, ByteString)
426 spanChar = L.spanByte . c2w
427 {-# INLINE spanChar #-}
428
429 -- | /O(n)/ Break a 'ByteString' into pieces separated by the byte
430 -- argument, consuming the delimiter. I.e.
431 --
432 -- > split '\n' "a\nb\nd\ne" == ["a","b","d","e"]
433 -- > split 'a'  "aXaXaXa"    == ["","X","X","X"]
434 -- > split 'x'  "x"          == ["",""]
435 -- 
436 -- and
437 --
438 -- > join [c] . split c == id
439 -- > split == splitWith . (==)
440 -- 
441 -- As for all splitting functions in this library, this function does
442 -- not copy the substrings, it just constructs new 'ByteStrings' that
443 -- are slices of the original.
444 --
445 split :: Char -> ByteString -> [ByteString]
446 split = L.split . c2w
447 {-# INLINE split #-}
448
449 -- | /O(n)/ Splits a 'ByteString' into components delimited by
450 -- separators, where the predicate returns True for a separator element.
451 -- The resulting components do not contain the separators.  Two adjacent
452 -- separators result in an empty component in the output.  eg.
453 --
454 -- > splitWith (=='a') "aabbaca" == ["","","bb","c",""]
455 --
456 splitWith :: (Char -> Bool) -> ByteString -> [ByteString]
457 splitWith f = L.splitWith (f . w2c)
458 {-# INLINE splitWith #-}
459
460 -- | Like 'splitWith', except that sequences of adjacent separators are
461 -- treated as a single separator. eg.
462 -- 
463 -- > tokens (=='a') "aabbaca" == ["bb","c"]
464 --
465 tokens :: (Char -> Bool) -> ByteString -> [ByteString]
466 tokens f = L.tokens (f . w2c)
467 {-# INLINE tokens #-}
468
469 -- | The 'groupBy' function is the non-overloaded version of 'group'.
470 groupBy :: (Char -> Char -> Bool) -> ByteString -> [ByteString]
471 groupBy k = L.groupBy (\a b -> k (w2c a) (w2c b))
472
473 -- | /O(n)/ joinWithChar. An efficient way to join to two ByteStrings with a
474 -- char. Around 4 times faster than the generalised join.
475 --
476 joinWithChar :: Char -> ByteString -> ByteString -> ByteString
477 joinWithChar = L.joinWithByte . c2w
478 {-# INLINE joinWithChar #-}
479
480 -- | /O(1)/ 'ByteString' index (subscript) operator, starting from 0.
481 index :: ByteString -> Int64 -> Char
482 index = (w2c .) . L.index
483 {-# INLINE index #-}
484
485 -- | /O(n)/ The 'elemIndex' function returns the index of the first
486 -- element in the given 'ByteString' which is equal (by memchr) to the
487 -- query element, or 'Nothing' if there is no such element.
488 elemIndex :: Char -> ByteString -> Maybe Int64
489 elemIndex = L.elemIndex . c2w
490 {-# INLINE elemIndex #-}
491
492 -- | /O(n)/ The 'elemIndices' function extends 'elemIndex', by returning
493 -- the indices of all elements equal to the query element, in ascending order.
494 elemIndices :: Char -> ByteString -> [Int64]
495 elemIndices = L.elemIndices . c2w
496 {-# INLINE elemIndices #-}
497
498 -- | The 'findIndex' function takes a predicate and a 'ByteString' and
499 -- returns the index of the first element in the ByteString satisfying the predicate.
500 findIndex :: (Char -> Bool) -> ByteString -> Maybe Int64
501 findIndex f = L.findIndex (f . w2c)
502 {-# INLINE findIndex #-}
503
504 -- | The 'findIndices' function extends 'findIndex', by returning the
505 -- indices of all elements satisfying the predicate, in ascending order.
506 findIndices :: (Char -> Bool) -> ByteString -> [Int64]
507 findIndices f = L.findIndices (f . w2c)
508
509 -- | count returns the number of times its argument appears in the ByteString
510 --
511 -- > count      == length . elemIndices
512 -- > count '\n' == length . lines
513 --
514 -- But more efficiently than using length on the intermediate list.
515 count :: Char -> ByteString -> Int64
516 count c = L.count (c2w c)
517
518 -- | /O(n)/ 'elem' is the 'ByteString' membership predicate. This
519 -- implementation uses @memchr(3)@.
520 elem :: Char -> ByteString -> Bool
521 elem c = L.elem (c2w c)
522 {-# INLINE elem #-}
523
524 -- | /O(n)/ 'notElem' is the inverse of 'elem'
525 notElem :: Char -> ByteString -> Bool
526 notElem c = L.notElem (c2w c)
527 {-# INLINE notElem #-}
528
529 -- | /O(n)/ 'filter', applied to a predicate and a ByteString,
530 -- returns a ByteString containing those characters that satisfy the
531 -- predicate.
532 filter :: (Char -> Bool) -> ByteString -> ByteString
533 filter f = L.filter (f . w2c)
534 {-# INLINE filter #-}
535
536 -- | /O(n)/ The 'find' function takes a predicate and a ByteString,
537 -- and returns the first element in matching the predicate, or 'Nothing'
538 -- if there is no such element.
539 find :: (Char -> Bool) -> ByteString -> Maybe Char
540 find f ps = w2c `fmap` L.find (f . w2c) ps
541 {-# INLINE find #-}
542
543 -- | /O(n)/ A first order equivalent of /filter . (==)/, for the common
544 -- case of filtering a single Char. It is more efficient to use
545 -- filterChar in this case.
546 --
547 -- > filterChar == filter . (==)
548 --
549 -- filterChar is around 10x faster, and uses much less space, than its
550 -- filter equivalent
551 --
552 filterChar :: Char -> ByteString -> ByteString
553 filterChar c = L.filterByte (c2w c)
554 {-# INLINE filterChar #-}
555
556 -- | /O(n)/ A first order equivalent of /filter . (\/=)/, for the common
557 -- case of filtering a single Char out of a list. It is more efficient
558 -- to use /filterNotChar/ in this case.
559 --
560 -- > filterNotChar == filter . (/=)
561 --
562 -- filterNotChar is around 3x faster, and uses much less space, than its
563 -- filter equivalent
564 --
565 filterNotChar :: Char -> ByteString -> ByteString
566 filterNotChar c = L.filterNotByte (c2w c)
567 {-# INLINE filterNotChar #-}
568
569 -- | /O(n)/ 'zip' takes two ByteStrings and returns a list of
570 -- corresponding pairs of Chars. If one input ByteString is short,
571 -- excess elements of the longer ByteString are discarded. This is
572 -- equivalent to a pair of 'unpack' operations, and so space
573 -- usage may be large for multi-megabyte ByteStrings
574 zip :: ByteString -> ByteString -> [(Char,Char)]
575 zip ps qs
576     | L.null ps || L.null qs = []
577     | otherwise = (head ps, head qs) : zip (L.tail ps) (L.tail qs)
578
579 -- | 'zipWith' generalises 'zip' by zipping with the function given as
580 -- the first argument, instead of a tupling function.  For example,
581 -- @'zipWith' (+)@ is applied to two ByteStrings to produce the list
582 -- of corresponding sums.
583 zipWith :: (Char -> Char -> a) -> ByteString -> ByteString -> [a]
584 zipWith f = L.zipWith ((. w2c) . f . w2c)
585
586 -- | 'lines' breaks a ByteString up into a list of ByteStrings at
587 -- newline Chars. The resulting strings do not contain newlines.
588 --
589 lines :: ByteString -> [ByteString]
590 lines (LPS [])     = []
591 lines (LPS (x:xs)) = loop0 x xs
592     where
593     -- this is a really performance sensitive function but the
594     -- chunked representation makes the general case a bit expensive
595     -- however assuming a large chunk size and normalish line lengths
596     -- we will find line endings much more frequently than chunk
597     -- endings so it makes sense to optimise for that common case.
598     -- So we partition into two special cases depending on whether we
599     -- are keeping back a list of chunks that will eventually be output
600     -- once we get to the end of the current line.
601
602     -- the common special case where we have no existing chunks of
603     -- the current line
604     loop0 :: B.ByteString -> [B.ByteString] -> [ByteString]
605     STRICT2(loop0)
606     loop0 ps pss =
607         case B.elemIndex (c2w '\n') ps of
608             Nothing -> case pss of
609                            []  | B.null ps ->            []
610                                | otherwise -> LPS [ps] : []
611                            (ps':pss')
612                                | B.null ps -> loop0 ps'      pss'
613                                | otherwise -> loop  ps' [ps] pss'
614
615             Just n | n /= 0    -> LPS [B.unsafeTake n ps]
616                                 : loop0 (B.unsafeDrop (n+1) ps) pss
617                    | otherwise -> loop0 (B.unsafeTail ps) pss
618
619     -- the general case when we are building a list of chunks that are
620     -- part of the same line
621     loop :: B.ByteString -> [B.ByteString] -> [B.ByteString] -> [ByteString]
622     STRICT3(loop)
623     loop ps line pss =
624         case B.elemIndex (c2w '\n') ps of
625             Nothing ->
626                 case pss of
627                     [] -> let ps' | B.null ps = P.reverse line
628                                   | otherwise = P.reverse (ps : line)
629                            in ps' `seq` (LPS ps' : [])
630
631                     (ps':pss')
632                         | B.null ps -> loop ps'       line  pss'
633                         | otherwise -> loop ps' (ps : line) pss'
634
635             Just n ->
636                 let ps' | n == 0    = P.reverse line
637                         | otherwise = P.reverse (B.unsafeTake n ps : line)
638                  in ps' `seq` (LPS ps' : loop0 (B.unsafeDrop (n+1) ps) pss)
639
640 -- | 'unlines' is an inverse operation to 'lines'.  It joins lines,
641 -- after appending a terminating newline to each.
642 unlines :: [ByteString] -> ByteString
643 unlines [] = empty
644 unlines ss = (concat $ List.intersperse nl ss) `append` nl -- half as much space
645     where nl = singleton '\n'
646
647 -- | 'words' breaks a ByteString up into a list of words, which
648 -- were delimited by Chars representing white space. And
649 --
650 -- > tokens isSpace = words
651 --
652 words :: ByteString -> [ByteString]
653 words = L.tokens isSpaceWord8
654 {-# INLINE words #-}
655
656 -- | The 'unwords' function is analogous to the 'unlines' function, on words.
657 unwords :: [ByteString] -> ByteString
658 unwords = join (singleton ' ')
659 {-# INLINE unwords #-}
660
661 -- | readInt reads an Int from the beginning of the ByteString.  If
662 -- there is no integer at the beginning of the string, it returns
663 -- Nothing, otherwise it just returns the int read, and the rest of the
664 -- string.
665 readInt :: ByteString -> Maybe (Int, ByteString)
666 readInt (LPS [])     = Nothing
667 readInt (LPS (x:xs)) =
668         case w2c (B.unsafeHead x) of
669             '-' -> loop True  0 0 (B.unsafeTail x) xs
670             '+' -> loop False 0 0 (B.unsafeTail x) xs
671             _   -> loop False 0 0 x xs
672
673     where loop :: Bool -> Int -> Int -> B.ByteString -> [B.ByteString] -> Maybe (Int, ByteString)
674           STRICT5(loop)
675           loop neg i n ps pss
676               | B.null ps = case pss of
677                                 []         -> end  neg i n ps  pss
678                                 (ps':pss') -> loop neg i n ps' pss'
679               | otherwise =
680                   case B.unsafeHead ps of
681                     w | w >= 0x30
682                      && w <= 0x39 -> loop neg (i+1)
683                                           (n * 10 + (fromIntegral w - 0x30))
684                                           (B.unsafeTail ps) pss
685                       | otherwise -> end neg i n ps pss
686
687           end _   0 _ _  _   = Nothing
688           end neg _ n ps pss = let n'  | neg       = negate n
689                                        | otherwise = n
690                                    ps' | B.null ps =    pss
691                                        | otherwise = ps:pss
692                                 in n' `seq` ps' `seq` Just $! (n', LPS ps')
693