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