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