{-# LANGUAGE BangPatterns, CPP, MagicHash, Rank2Types, UnboxedTuples #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Data.Text
(
Text
, pack
, unpack
, singleton
, empty
, cons
, snoc
, append
, uncons
, head
, last
, tail
, init
, null
, length
, compareLength
, map
, intercalate
, intersperse
, transpose
, reverse
, replace
, toCaseFold
, toLower
, toUpper
, toTitle
, justifyLeft
, justifyRight
, center
, foldl
, foldl'
, foldl1
, foldl1'
, foldr
, foldr1
, concat
, concatMap
, any
, all
, maximum
, minimum
, scanl
, scanl1
, scanr
, scanr1
, mapAccumL
, mapAccumR
, replicate
, unfoldr
, unfoldrN
, take
, takeEnd
, drop
, dropEnd
, takeWhile
, dropWhile
, dropWhileEnd
, dropAround
, strip
, stripStart
, stripEnd
, splitAt
, breakOn
, breakOnEnd
, break
, span
, group
, groupBy
, inits
, tails
, splitOn
, split
, chunksOf
, lines
, words
, unlines
, unwords
, isPrefixOf
, isSuffixOf
, isInfixOf
, stripPrefix
, stripSuffix
, commonPrefixes
, filter
, breakOnAll
, find
, partition
, index
, findIndex
, count
, zip
, zipWith
, copy
) where
import Prelude (Char, Bool(..), Int, Maybe(..), String,
Eq(..), Ord(..), Ordering(..), (++),
Read(..), Show(..),
(&&), (||), (+), (-), (.), ($), ($!), (>>), (*),
maxBound, not, return, otherwise, quot)
#if defined(HAVE_DEEPSEQ)
import Control.DeepSeq (NFData)
#endif
#if defined(ASSERTS)
import Control.Exception (assert)
#endif
import Data.Char (isSpace)
import Data.Data (Data(gfoldl, toConstr, gunfold, dataTypeOf), constrIndex,
Constr, mkConstr, DataType, mkDataType, Fixity(Prefix))
import Control.Monad (foldM)
import qualified Data.Text.Array as A
import qualified Data.List as L
import Data.Monoid (Monoid(..))
import Data.String (IsString(..))
import qualified Data.Text.Internal.Fusion as S
import qualified Data.Text.Internal.Fusion.Common as S
import Data.Text.Internal.Fusion (stream, reverseStream, unstream)
import Data.Text.Internal.Private (span_)
import Data.Text.Internal (Text(..), empty, firstf, safe, text)
import qualified Prelude as P
import Data.Text.Unsafe (Iter(..), iter, iter_, lengthWord16, reverseIter,
reverseIter_, unsafeHead, unsafeTail)
import Data.Text.Internal.Unsafe.Char (unsafeChr)
import qualified Data.Text.Internal.Functions as F
import qualified Data.Text.Internal.Encoding.Utf16 as U16
import Data.Text.Internal.Search (indices)
#if defined(__HADDOCK__)
import Data.ByteString (ByteString)
import qualified Data.Text.Lazy as L
import Data.Int (Int64)
#endif
#if __GLASGOW_HASKELL__ >= 702
import qualified GHC.CString as GHC
#else
import qualified GHC.Base as GHC
#endif
import GHC.Prim (Addr#)
instance Eq Text where
Text arrA offA lenA == Text arrB offB lenB
| lenA == lenB = A.equal arrA offA arrB offB lenA
| otherwise = False
{-# INLINE (==) #-}
instance Ord Text where
compare = compareText
instance Show Text where
showsPrec p ps r = showsPrec p (unpack ps) r
instance Read Text where
readsPrec p str = [(pack x,y) | (x,y) <- readsPrec p str]
instance Monoid Text where
mempty = empty
mappend = append
mconcat = concat
instance IsString Text where
fromString = pack
#if defined(HAVE_DEEPSEQ)
instance NFData Text
#endif
instance Data Text where
gfoldl f z txt = z pack `f` (unpack txt)
toConstr _ = packConstr
gunfold k z c = case constrIndex c of
1 -> k (z pack)
_ -> P.error "gunfold"
dataTypeOf _ = textDataType
packConstr :: Constr
packConstr = mkConstr textDataType "pack" [] Prefix
textDataType :: DataType
textDataType = mkDataType "Data.Text.Text" [packConstr]
compareText :: Text -> Text -> Ordering
compareText ta@(Text _arrA _offA lenA) tb@(Text _arrB _offB lenB)
| lenA == 0 && lenB == 0 = EQ
| otherwise = go 0 0
where
go !i !j
| i >= lenA || j >= lenB = compare lenA lenB
| a < b = LT
| a > b = GT
| otherwise = go (i+di) (j+dj)
where Iter a di = iter ta i
Iter b dj = iter tb j
pack :: String -> Text
pack = unstream . S.map safe . S.streamList
{-# INLINE [1] pack #-}
unpack :: Text -> String
unpack = S.unstreamList . stream
{-# INLINE [1] unpack #-}
unpackCString# :: Addr# -> Text
unpackCString# addr# = unstream (S.streamCString# addr#)
{-# NOINLINE unpackCString# #-}
{-# RULES "TEXT literal" forall a.
unstream (S.map safe (S.streamList (GHC.unpackCString# a)))
= unpackCString# a #-}
{-# RULES "TEXT literal UTF8" forall a.
unstream (S.map safe (S.streamList (GHC.unpackCStringUtf8# a)))
= unpackCString# a #-}
singleton :: Char -> Text
singleton = unstream . S.singleton . safe
{-# INLINE [1] singleton #-}
cons :: Char -> Text -> Text
cons c t = unstream (S.cons (safe c) (stream t))
{-# INLINE cons #-}
infixr 5 `cons`
snoc :: Text -> Char -> Text
snoc t c = unstream (S.snoc (stream t) (safe c))
{-# INLINE snoc #-}
append :: Text -> Text -> Text
append a@(Text arr1 off1 len1) b@(Text arr2 off2 len2)
| len1 == 0 = b
| len2 == 0 = a
| len > 0 = Text (A.run x) 0 len
| otherwise = overflowError "append"
where
len = len1+len2
x = do
arr <- A.new len
A.copyI arr 0 arr1 off1 len1
A.copyI arr len1 arr2 off2 len
return arr
{-# NOINLINE append #-}
{-# RULES
"TEXT append -> fused" [~1] forall t1 t2.
append t1 t2 = unstream (S.append (stream t1) (stream t2))
"TEXT append -> unfused" [1] forall t1 t2.
unstream (S.append (stream t1) (stream t2)) = append t1 t2
#-}
head :: Text -> Char
head t = S.head (stream t)
{-# INLINE head #-}
uncons :: Text -> Maybe (Char, Text)
uncons t@(Text arr off len)
| len <= 0 = Nothing
| otherwise = Just (c, text arr (off+d) (len-d))
where Iter c d = iter t 0
{-# INLINE [1] uncons #-}
second :: (b -> c) -> (a,b) -> (a,c)
second f (a, b) = (a, f b)
last :: Text -> Char
last (Text arr off len)
| len <= 0 = emptyError "last"
| n < 0xDC00 || n > 0xDFFF = unsafeChr n
| otherwise = U16.chr2 n0 n
where n = A.unsafeIndex arr (off+len-1)
n0 = A.unsafeIndex arr (off+len-2)
{-# INLINE [1] last #-}
{-# RULES
"TEXT last -> fused" [~1] forall t.
last t = S.last (stream t)
"TEXT last -> unfused" [1] forall t.
S.last (stream t) = last t
#-}
tail :: Text -> Text
tail t@(Text arr off len)
| len <= 0 = emptyError "tail"
| otherwise = text arr (off+d) (len-d)
where d = iter_ t 0
{-# INLINE [1] tail #-}
{-# RULES
"TEXT tail -> fused" [~1] forall t.
tail t = unstream (S.tail (stream t))
"TEXT tail -> unfused" [1] forall t.
unstream (S.tail (stream t)) = tail t
#-}
init :: Text -> Text
init (Text arr off len) | len <= 0 = emptyError "init"
| n >= 0xDC00 && n <= 0xDFFF = text arr off (len-2)
| otherwise = text arr off (len-1)
where
n = A.unsafeIndex arr (off+len-1)
{-# INLINE [1] init #-}
{-# RULES
"TEXT init -> fused" [~1] forall t.
init t = unstream (S.init (stream t))
"TEXT init -> unfused" [1] forall t.
unstream (S.init (stream t)) = init t
#-}
null :: Text -> Bool
null (Text _arr _off len) =
#if defined(ASSERTS)
assert (len >= 0) $
#endif
len <= 0
{-# INLINE [1] null #-}
{-# RULES
"TEXT null -> fused" [~1] forall t.
null t = S.null (stream t)
"TEXT null -> unfused" [1] forall t.
S.null (stream t) = null t
#-}
isSingleton :: Text -> Bool
isSingleton = S.isSingleton . stream
{-# INLINE isSingleton #-}
length :: Text -> Int
length t = S.length (stream t)
{-# INLINE length #-}
compareLength :: Text -> Int -> Ordering
compareLength t n = S.compareLengthI (stream t) n
{-# INLINE [1] compareLength #-}
{-# RULES
"TEXT compareN/length -> compareLength" [~1] forall t n.
compare (length t) n = compareLength t n
#-}
{-# RULES
"TEXT ==N/length -> compareLength/==EQ" [~1] forall t n.
(==) (length t) n = compareLength t n == EQ
#-}
{-# RULES
"TEXT /=N/length -> compareLength//=EQ" [~1] forall t n.
(/=) (length t) n = compareLength t n /= EQ
#-}
{-# RULES
"TEXT <N/length -> compareLength/==LT" [~1] forall t n.
(<) (length t) n = compareLength t n == LT
#-}
{-# RULES
"TEXT <=N/length -> compareLength//=GT" [~1] forall t n.
(<=) (length t) n = compareLength t n /= GT
#-}
{-# RULES
"TEXT >N/length -> compareLength/==GT" [~1] forall t n.
(>) (length t) n = compareLength t n == GT
#-}
{-# RULES
"TEXT >=N/length -> compareLength//=LT" [~1] forall t n.
(>=) (length t) n = compareLength t n /= LT
#-}
map :: (Char -> Char) -> Text -> Text
map f t = unstream (S.map (safe . f) (stream t))
{-# INLINE [1] map #-}
intercalate :: Text -> [Text] -> Text
intercalate t = concat . (F.intersperse t)
{-# INLINE intercalate #-}
intersperse :: Char -> Text -> Text
intersperse c t = unstream (S.intersperse (safe c) (stream t))
{-# INLINE intersperse #-}
reverse :: Text -> Text
reverse t = S.reverse (stream t)
{-# INLINE reverse #-}
replace :: Text -> Text -> Text -> Text
replace needle@(Text _ _ neeLen)
(Text repArr repOff repLen)
haystack@(Text hayArr hayOff hayLen)
| neeLen == 0 = emptyError "replace"
| L.null ixs = haystack
| len > 0 = Text (A.run x) 0 len
| len < 0 = overflowError "replace"
| otherwise = empty
where
ixs = indices needle haystack
len = hayLen - (neeLen - repLen) * L.length ixs
x = do
marr <- A.new len
let loop (i:is) o d = do
let d0 = d + i - o
d1 = d0 + repLen
A.copyI marr d hayArr (hayOff+o) d0
A.copyI marr d0 repArr repOff d1
loop is (i + neeLen) d1
loop [] o d = A.copyI marr d hayArr (hayOff+o) len
loop ixs 0 0
return marr
toCaseFold :: Text -> Text
toCaseFold t = unstream (S.toCaseFold (stream t))
{-# INLINE [0] toCaseFold #-}
toLower :: Text -> Text
toLower t = unstream (S.toLower (stream t))
{-# INLINE toLower #-}
toUpper :: Text -> Text
toUpper t = unstream (S.toUpper (stream t))
{-# INLINE toUpper #-}
toTitle :: Text -> Text
toTitle t = unstream (S.toTitle (stream t))
{-# INLINE toTitle #-}
justifyLeft :: Int -> Char -> Text -> Text
justifyLeft k c t
| len >= k = t
| otherwise = t `append` replicateChar (k-len) c
where len = length t
{-# INLINE [1] justifyLeft #-}
{-# RULES
"TEXT justifyLeft -> fused" [~1] forall k c t.
justifyLeft k c t = unstream (S.justifyLeftI k c (stream t))
"TEXT justifyLeft -> unfused" [1] forall k c t.
unstream (S.justifyLeftI k c (stream t)) = justifyLeft k c t
#-}
justifyRight :: Int -> Char -> Text -> Text
justifyRight k c t
| len >= k = t
| otherwise = replicateChar (k-len) c `append` t
where len = length t
{-# INLINE justifyRight #-}
center :: Int -> Char -> Text -> Text
center k c t
| len >= k = t
| otherwise = replicateChar l c `append` t `append` replicateChar r c
where len = length t
d = k - len
r = d `quot` 2
l = d - r
{-# INLINE center #-}
transpose :: [Text] -> [Text]
transpose ts = P.map pack (L.transpose (P.map unpack ts))
foldl :: (a -> Char -> a) -> a -> Text -> a
foldl f z t = S.foldl f z (stream t)
{-# INLINE foldl #-}
foldl' :: (a -> Char -> a) -> a -> Text -> a
foldl' f z t = S.foldl' f z (stream t)
{-# INLINE foldl' #-}
foldl1 :: (Char -> Char -> Char) -> Text -> Char
foldl1 f t = S.foldl1 f (stream t)
{-# INLINE foldl1 #-}
foldl1' :: (Char -> Char -> Char) -> Text -> Char
foldl1' f t = S.foldl1' f (stream t)
{-# INLINE foldl1' #-}
foldr :: (Char -> a -> a) -> a -> Text -> a
foldr f z t = S.foldr f z (stream t)
{-# INLINE foldr #-}
foldr1 :: (Char -> Char -> Char) -> Text -> Char
foldr1 f t = S.foldr1 f (stream t)
{-# INLINE foldr1 #-}
concat :: [Text] -> Text
concat ts = case ts' of
[] -> empty
[t] -> t
_ -> Text (A.run go) 0 len
where
ts' = L.filter (not . null) ts
len = sumP "concat" $ L.map lengthWord16 ts'
go = do
arr <- A.new len
let step i (Text a o l) =
let !j = i + l in A.copyI arr i a o j >> return j
foldM step 0 ts' >> return arr
concatMap :: (Char -> Text) -> Text -> Text
concatMap f = concat . foldr ((:) . f) []
{-# INLINE concatMap #-}
any :: (Char -> Bool) -> Text -> Bool
any p t = S.any p (stream t)
{-# INLINE any #-}
all :: (Char -> Bool) -> Text -> Bool
all p t = S.all p (stream t)
{-# INLINE all #-}
maximum :: Text -> Char
maximum t = S.maximum (stream t)
{-# INLINE maximum #-}
minimum :: Text -> Char
minimum t = S.minimum (stream t)
{-# INLINE minimum #-}
scanl :: (Char -> Char -> Char) -> Char -> Text -> Text
scanl f z t = unstream (S.scanl g z (stream t))
where g a b = safe (f a b)
{-# INLINE scanl #-}
scanl1 :: (Char -> Char -> Char) -> Text -> Text
scanl1 f t | null t = empty
| otherwise = scanl f (unsafeHead t) (unsafeTail t)
{-# INLINE scanl1 #-}
scanr :: (Char -> Char -> Char) -> Char -> Text -> Text
scanr f z = S.reverse . S.reverseScanr g z . reverseStream
where g a b = safe (f a b)
{-# INLINE scanr #-}
scanr1 :: (Char -> Char -> Char) -> Text -> Text
scanr1 f t | null t = empty
| otherwise = scanr f (last t) (init t)
{-# INLINE scanr1 #-}
mapAccumL :: (a -> Char -> (a,Char)) -> a -> Text -> (a, Text)
mapAccumL f z0 = S.mapAccumL g z0 . stream
where g a b = second safe (f a b)
{-# INLINE mapAccumL #-}
mapAccumR :: (a -> Char -> (a,Char)) -> a -> Text -> (a, Text)
mapAccumR f z0 = second reverse . S.mapAccumL g z0 . reverseStream
where g a b = second safe (f a b)
{-# INLINE mapAccumR #-}
replicate :: Int -> Text -> Text
replicate n t@(Text a o l)
| n <= 0 || l <= 0 = empty
| n == 1 = t
| isSingleton t = replicateChar n (unsafeHead t)
| n <= maxBound `quot` l = Text (A.run x) 0 len
| otherwise = overflowError "replicate"
where
len = l * n
x = do
arr <- A.new len
let loop !d !i | i >= n = return arr
| otherwise = let m = d + l
in A.copyI arr d a o m >> loop m (i+1)
loop 0 0
{-# INLINE [1] replicate #-}
{-# RULES
"TEXT replicate/singleton -> replicateChar" [~1] forall n c.
replicate n (singleton c) = replicateChar n c
#-}
replicateChar :: Int -> Char -> Text
replicateChar n c = unstream (S.replicateCharI n (safe c))
{-# INLINE replicateChar #-}
unfoldr :: (a -> Maybe (Char,a)) -> a -> Text
unfoldr f s = unstream (S.unfoldr (firstf safe . f) s)
{-# INLINE unfoldr #-}
unfoldrN :: Int -> (a -> Maybe (Char,a)) -> a -> Text
unfoldrN n f s = unstream (S.unfoldrN n (firstf safe . f) s)
{-# INLINE unfoldrN #-}
take :: Int -> Text -> Text
take n t@(Text arr off len)
| n <= 0 = empty
| n >= len = t
| otherwise = text arr off (iterN n t)
{-# INLINE [1] take #-}
iterN :: Int -> Text -> Int
iterN n t@(Text _arr _off len) = loop 0 0
where loop !i !cnt
| i >= len || cnt >= n = i
| otherwise = loop (i+d) (cnt+1)
where d = iter_ t i
{-# RULES
"TEXT take -> fused" [~1] forall n t.
take n t = unstream (S.take n (stream t))
"TEXT take -> unfused" [1] forall n t.
unstream (S.take n (stream t)) = take n t
#-}
takeEnd :: Int -> Text -> Text
takeEnd n t@(Text arr off len)
| n <= 0 = empty
| n >= len = t
| otherwise = text arr (off+i) (len-i)
where i = iterNEnd n t
iterNEnd :: Int -> Text -> Int
iterNEnd n t@(Text _arr _off len) = loop (len-1) n
where loop i !m
| i <= 0 = 0
| m <= 1 = i
| otherwise = loop (i+d) (m-1)
where d = reverseIter_ t i
drop :: Int -> Text -> Text
drop n t@(Text arr off len)
| n <= 0 = t
| n >= len = empty
| otherwise = text arr (off+i) (len-i)
where i = iterN n t
{-# INLINE [1] drop #-}
{-# RULES
"TEXT drop -> fused" [~1] forall n t.
drop n t = unstream (S.drop n (stream t))
"TEXT drop -> unfused" [1] forall n t.
unstream (S.drop n (stream t)) = drop n t
#-}
dropEnd :: Int -> Text -> Text
dropEnd n t@(Text arr off len)
| n <= 0 = t
| n >= len = empty
| otherwise = text arr off (iterNEnd n t)
takeWhile :: (Char -> Bool) -> Text -> Text
takeWhile p t@(Text arr off len) = loop 0
where loop !i | i >= len = t
| p c = loop (i+d)
| otherwise = text arr off i
where Iter c d = iter t i
{-# INLINE [1] takeWhile #-}
{-# RULES
"TEXT takeWhile -> fused" [~1] forall p t.
takeWhile p t = unstream (S.takeWhile p (stream t))
"TEXT takeWhile -> unfused" [1] forall p t.
unstream (S.takeWhile p (stream t)) = takeWhile p t
#-}
dropWhile :: (Char -> Bool) -> Text -> Text
dropWhile p t@(Text arr off len) = loop 0 0
where loop !i !l | l >= len = empty
| p c = loop (i+d) (l+d)
| otherwise = Text arr (off+i) (len-l)
where Iter c d = iter t i
{-# INLINE [1] dropWhile #-}
{-# RULES
"TEXT dropWhile -> fused" [~1] forall p t.
dropWhile p t = unstream (S.dropWhile p (stream t))
"TEXT dropWhile -> unfused" [1] forall p t.
unstream (S.dropWhile p (stream t)) = dropWhile p t
#-}
dropWhileEnd :: (Char -> Bool) -> Text -> Text
dropWhileEnd p t@(Text arr off len) = loop (len-1) len
where loop !i !l | l <= 0 = empty
| p c = loop (i+d) (l+d)
| otherwise = Text arr off l
where (c,d) = reverseIter t i
{-# INLINE [1] dropWhileEnd #-}
{-# RULES
"TEXT dropWhileEnd -> fused" [~1] forall p t.
dropWhileEnd p t = S.reverse (S.dropWhile p (S.reverseStream t))
"TEXT dropWhileEnd -> unfused" [1] forall p t.
S.reverse (S.dropWhile p (S.reverseStream t)) = dropWhileEnd p t
#-}
dropAround :: (Char -> Bool) -> Text -> Text
dropAround p = dropWhile p . dropWhileEnd p
{-# INLINE [1] dropAround #-}
stripStart :: Text -> Text
stripStart = dropWhile isSpace
{-# INLINE [1] stripStart #-}
stripEnd :: Text -> Text
stripEnd = dropWhileEnd isSpace
{-# INLINE [1] stripEnd #-}
strip :: Text -> Text
strip = dropAround isSpace
{-# INLINE [1] strip #-}
splitAt :: Int -> Text -> (Text, Text)
splitAt n t@(Text arr off len)
| n <= 0 = (empty, t)
| n >= len = (t, empty)
| otherwise = let k = iterN n t
in (text arr off k, text arr (off+k) (len-k))
span :: (Char -> Bool) -> Text -> (Text, Text)
span p t = case span_ p t of
(# hd,tl #) -> (hd,tl)
{-# INLINE span #-}
break :: (Char -> Bool) -> Text -> (Text, Text)
break p = span (not . p)
{-# INLINE break #-}
groupBy :: (Char -> Char -> Bool) -> Text -> [Text]
groupBy p = loop
where
loop t@(Text arr off len)
| null t = []
| otherwise = text arr off n : loop (text arr (off+n) (len-n))
where Iter c d = iter t 0
n = d + findAIndexOrEnd (not . p c) (Text arr (off+d) (len-d))
findAIndexOrEnd :: (Char -> Bool) -> Text -> Int
findAIndexOrEnd q t@(Text _arr _off len) = go 0
where go !i | i >= len || q c = i
| otherwise = go (i+d)
where Iter c d = iter t i
group :: Text -> [Text]
group = groupBy (==)
inits :: Text -> [Text]
inits t@(Text arr off len) = loop 0
where loop i | i >= len = [t]
| otherwise = Text arr off i : loop (i + iter_ t i)
tails :: Text -> [Text]
tails t | null t = [empty]
| otherwise = t : tails (unsafeTail t)
splitOn :: Text -> Text -> [Text]
splitOn pat@(Text _ _ l) src@(Text arr off len)
| l <= 0 = emptyError "splitOn"
| isSingleton pat = split (== unsafeHead pat) src
| otherwise = go 0 (indices pat src)
where
go !s (x:xs) = text arr (s+off) (x-s) : go (x+l) xs
go s _ = [text arr (s+off) (len-s)]
{-# INLINE [1] splitOn #-}
{-# RULES
"TEXT splitOn/singleton -> split/==" [~1] forall c t.
splitOn (singleton c) t = split (==c) t
#-}
split :: (Char -> Bool) -> Text -> [Text]
split _ t@(Text _off _arr 0) = [t]
split p t = loop t
where loop s | null s' = [l]
| otherwise = l : loop (unsafeTail s')
where (# l, s' #) = span_ (not . p) s
{-# INLINE split #-}
chunksOf :: Int -> Text -> [Text]
chunksOf k = go
where
go t = case splitAt k t of
(a,b) | null a -> []
| otherwise -> a : go b
{-# INLINE chunksOf #-}
find :: (Char -> Bool) -> Text -> Maybe Char
find p t = S.findBy p (stream t)
{-# INLINE find #-}
partition :: (Char -> Bool) -> Text -> (Text, Text)
partition p t = (filter p t, filter (not . p) t)
{-# INLINE partition #-}
filter :: (Char -> Bool) -> Text -> Text
filter p t = unstream (S.filter p (stream t))
{-# INLINE filter #-}
breakOn :: Text -> Text -> (Text, Text)
breakOn pat src@(Text arr off len)
| null pat = emptyError "breakOn"
| otherwise = case indices pat src of
[] -> (src, empty)
(x:_) -> (text arr off x, text arr (off+x) (len-x))
{-# INLINE breakOn #-}
breakOnEnd :: Text -> Text -> (Text, Text)
breakOnEnd pat src = (reverse b, reverse a)
where (a,b) = breakOn (reverse pat) (reverse src)
{-# INLINE breakOnEnd #-}
breakOnAll :: Text
-> Text
-> [(Text, Text)]
breakOnAll pat src@(Text arr off slen)
| null pat = emptyError "breakOnAll"
| otherwise = L.map step (indices pat src)
where
step x = (chunk 0 x, chunk x (slen-x))
chunk !n !l = text arr (n+off) l
{-# INLINE breakOnAll #-}
index :: Text -> Int -> Char
index t n = S.index (stream t) n
{-# INLINE index #-}
findIndex :: (Char -> Bool) -> Text -> Maybe Int
findIndex p t = S.findIndex p (stream t)
{-# INLINE findIndex #-}
count :: Text -> Text -> Int
count pat src
| null pat = emptyError "count"
| isSingleton pat = countChar (unsafeHead pat) src
| otherwise = L.length (indices pat src)
{-# INLINE [1] count #-}
{-# RULES
"TEXT count/singleton -> countChar" [~1] forall c t.
count (singleton c) t = countChar c t
#-}
countChar :: Char -> Text -> Int
countChar c t = S.countChar c (stream t)
{-# INLINE countChar #-}
zip :: Text -> Text -> [(Char,Char)]
zip a b = S.unstreamList $ S.zipWith (,) (stream a) (stream b)
{-# INLINE [0] zip #-}
zipWith :: (Char -> Char -> Char) -> Text -> Text -> Text
zipWith f t1 t2 = unstream (S.zipWith g (stream t1) (stream t2))
where g a b = safe (f a b)
{-# INLINE [0] zipWith #-}
words :: Text -> [Text]
words t@(Text arr off len) = loop 0 0
where
loop !start !n
| n >= len = if start == n
then []
else [Text arr (start+off) (n-start)]
| isSpace c =
if start == n
then loop (start+1) (start+1)
else Text arr (start+off) (n-start) : loop (n+d) (n+d)
| otherwise = loop start (n+d)
where Iter c d = iter t n
{-# INLINE words #-}
lines :: Text -> [Text]
lines ps | null ps = []
| otherwise = h : if null t
then []
else lines (unsafeTail t)
where (# h,t #) = span_ (/= '\n') ps
{-# INLINE lines #-}
unlines :: [Text] -> Text
unlines = concat . L.map (`snoc` '\n')
{-# INLINE unlines #-}
unwords :: [Text] -> Text
unwords = intercalate (singleton ' ')
{-# INLINE unwords #-}
isPrefixOf :: Text -> Text -> Bool
isPrefixOf a@(Text _ _ alen) b@(Text _ _ blen) =
alen <= blen && S.isPrefixOf (stream a) (stream b)
{-# INLINE [1] isPrefixOf #-}
{-# RULES
"TEXT isPrefixOf -> fused" [~1] forall s t.
isPrefixOf s t = S.isPrefixOf (stream s) (stream t)
#-}
isSuffixOf :: Text -> Text -> Bool
isSuffixOf a@(Text _aarr _aoff alen) b@(Text barr boff blen) =
d >= 0 && a == b'
where d = blen - alen
b' | d == 0 = b
| otherwise = Text barr (boff+d) alen
{-# INLINE isSuffixOf #-}
isInfixOf :: Text -> Text -> Bool
isInfixOf needle haystack
| null needle = True
| isSingleton needle = S.elem (unsafeHead needle) . S.stream $ haystack
| otherwise = not . L.null . indices needle $ haystack
{-# INLINE [1] isInfixOf #-}
{-# RULES
"TEXT isInfixOf/singleton -> S.elem/S.stream" [~1] forall n h.
isInfixOf (singleton n) h = S.elem n (S.stream h)
#-}
stripPrefix :: Text -> Text -> Maybe Text
stripPrefix p@(Text _arr _off plen) t@(Text arr off len)
| p `isPrefixOf` t = Just $! text arr (off+plen) (len-plen)
| otherwise = Nothing
commonPrefixes :: Text -> Text -> Maybe (Text,Text,Text)
commonPrefixes t0@(Text arr0 off0 len0) t1@(Text arr1 off1 len1) = go 0 0
where
go !i !j | i < len0 && j < len1 && a == b = go (i+d0) (j+d1)
| i > 0 = Just (Text arr0 off0 i,
text arr0 (off0+i) (len0-i),
text arr1 (off1+j) (len1-j))
| otherwise = Nothing
where Iter a d0 = iter t0 i
Iter b d1 = iter t1 j
stripSuffix :: Text -> Text -> Maybe Text
stripSuffix p@(Text _arr _off plen) t@(Text arr off len)
| p `isSuffixOf` t = Just $! text arr off (len-plen)
| otherwise = Nothing
sumP :: String -> [Int] -> Int
sumP fun = go 0
where go !a (x:xs)
| ax >= 0 = go ax xs
| otherwise = overflowError fun
where ax = a + x
go a _ = a
emptyError :: String -> a
emptyError fun = P.error $ "Data.Text." ++ fun ++ ": empty input"
overflowError :: String -> a
overflowError fun = P.error $ "Data.Text." ++ fun ++ ": size overflow"
copy :: Text -> Text
copy (Text arr off len) = Text (A.run go) 0 len
where
go = do
marr <- A.new len
A.copyI marr 0 arr off len
return marr