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