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