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