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