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