{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE BangPatterns, MagicHash, CPP, TypeFamilies #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TemplateHaskellQuotes #-}

-- |
-- Module      : Data.Text.Lazy
-- Copyright   : (c) 2009, 2010, 2012 Bryan O'Sullivan
--
-- License     : BSD-style
-- Maintainer  : bos@serpentine.com
-- Portability : GHC
--
-- A time and space-efficient implementation of Unicode text using
-- lists of packed arrays.
--
-- /Note/: Read below the synopsis for important notes on the use of
-- this module.
--
-- The representation used by this module is suitable for high
-- performance use and for streaming large quantities of data.  It
-- provides a means to manipulate a large body of text without
-- requiring that the entire content be resident in memory.
--
-- Some operations, such as 'concat', 'append', 'reverse' and 'cons',
-- have better time complexity than their "Data.Text" equivalents, due
-- to the underlying representation being a list of chunks. For other
-- operations, lazy 'Text's are usually within a few percent of strict
-- ones, but often with better heap usage if used in a streaming
-- fashion. For data larger than available memory, or if you have
-- tight memory constraints, this module will be the only option.
--
-- This module is intended to be imported @qualified@, to avoid name
-- clashes with "Prelude" functions.  eg.
--
-- > import qualified Data.Text.Lazy as L

module Data.Text.Lazy
    (
    -- * Fusion
    -- $fusion

    -- * Acceptable data
    -- $replacement

    -- * Types
      Text

    -- * Creation and elimination
    , pack
    , unpack
    , singleton
    , empty
    , fromChunks
    , toChunks
    , toStrict
    , fromStrict
    , foldrChunks
    , foldlChunks

    -- * Basic interface
    , cons
    , snoc
    , append
    , uncons
    , unsnoc
    , head
    , last
    , tail
    , init
    , null
    , length
    , compareLength

    -- * Transformations
    , map
    , intercalate
    , intersperse
    , transpose
    , reverse
    , replace

    -- ** Case conversion
    -- $case
    , toCaseFold
    , toLower
    , toUpper
    , toTitle

    -- ** Justification
    , justifyLeft
    , justifyRight
    , center

    -- * Folds
    , foldl
    , foldl'
    , foldl1
    , foldl1'
    , foldr
    , foldr1

    -- ** Special folds
    , concat
    , concatMap
    , any
    , all
    , maximum
    , minimum

    -- * Construction

    -- ** Scans
    , scanl
    , scanl1
    , scanr
    , scanr1

    -- ** Accumulating maps
    , mapAccumL
    , mapAccumR

    -- ** Generation and unfolding
    , repeat
    , replicate
    , cycle
    , iterate
    , unfoldr
    , unfoldrN

    -- * Substrings

    -- ** Breaking strings
    , take
    , takeEnd
    , drop
    , dropEnd
    , takeWhile
    , takeWhileEnd
    , dropWhile
    , dropWhileEnd
    , dropAround
    , strip
    , stripStart
    , stripEnd
    , splitAt
    , span
    , breakOn
    , breakOnEnd
    , break
    , group
    , groupBy
    , inits
    , tails

    -- ** Breaking into many substrings
    -- $split
    , splitOn
    , split
    , chunksOf
    -- , breakSubstring

    -- ** Breaking into lines and words
    , lines
    , words
    , unlines
    , unwords

    -- * Predicates
    , isPrefixOf
    , isSuffixOf
    , isInfixOf

    -- ** View patterns
    , stripPrefix
    , stripSuffix
    , commonPrefixes

    -- * Searching
    , filter
    , find
    , elem
    , breakOnAll
    , partition

    -- , findSubstring

    -- * Indexing
    , index
    , count

    -- * Zipping and unzipping
    , zip
    , zipWith

    -- -* Ordered text
    -- , sort
    ) where

import Prelude (Char, Bool(..), Maybe(..), String,
                Eq(..), Ord(..), Ordering(..), Read(..), Show(..),
                (&&), (||), (+), (-), (.), ($), (++),
                error, flip, fmap, fromIntegral, not, otherwise, quot)
import qualified Prelude as P
import Control.DeepSeq (NFData(..))
import Data.Int (Int64)
import qualified Data.List as L
import Data.Char (isSpace)
import Data.Data (Data(gfoldl, toConstr, gunfold, dataTypeOf), constrIndex,
                  Constr, mkConstr, DataType, mkDataType, Fixity(Prefix))
import Data.Binary (Binary(get, put))
import Data.Monoid (Monoid(..))
import Data.Semigroup (Semigroup(..))
import Data.String (IsString(..))
import qualified Data.Text as T
import qualified Data.Text.Internal as T
import qualified Data.Text.Internal.Fusion.Common as S
import qualified Data.Text.Unsafe as T
import qualified Data.Text.Internal.Lazy.Fusion as S
import Data.Text.Internal.Fusion.Types (PairS(..))
import Data.Text.Internal.Lazy.Fusion (stream, unstream)
import Data.Text.Internal.Lazy (Text(..), chunk, empty, foldlChunks,
                                foldrChunks, smallChunkSize)
import Data.Text.Internal (firstf, safe, text)
import Data.Text.Lazy.Encoding (decodeUtf8', encodeUtf8)
import qualified Data.Text.Internal.Functions as F
import Data.Text.Internal.Lazy.Search (indices)
import qualified GHC.CString as GHC
import qualified GHC.Exts as Exts
import GHC.Prim (Addr#)
import qualified Language.Haskell.TH.Lib as TH
import qualified Language.Haskell.TH.Syntax as TH
import Text.Printf (PrintfArg, formatArg, formatString)

#if defined(ASSERTS)
import GHC.Stack (HasCallStack)
#endif

-- $fusion
--
-- Most of the functions in this module are subject to /fusion/,
-- meaning that a pipeline of such functions will usually allocate at
-- most one 'Text' value.
--
-- As an example, consider the following pipeline:
--
-- > import Data.Text.Lazy as T
-- > import Data.Text.Lazy.Encoding as E
-- > import Data.ByteString.Lazy (ByteString)
-- >
-- > countChars :: ByteString -> Int
-- > countChars = T.length . T.toUpper . E.decodeUtf8
--
-- From the type signatures involved, this looks like it should
-- allocate one 'ByteString' value, and two 'Text' values. However,
-- when a module is compiled with optimisation enabled under GHC, the
-- two intermediate 'Text' values will be optimised away, and the
-- function will be compiled down to a single loop over the source
-- 'ByteString'.
--
-- Functions that can be fused by the compiler are documented with the
-- phrase \"Subject to fusion\".

-- $replacement
--
-- A 'Text' value is a sequence of Unicode scalar values, as defined
-- in
-- <http://www.unicode.org/versions/Unicode5.2.0/ch03.pdf#page=35 §3.9, definition D76 of the Unicode 5.2 standard >.
-- As such, a 'Text' cannot contain values in the range U+D800 to
-- U+DFFF inclusive. Haskell implementations admit all Unicode code
-- points
-- (<http://www.unicode.org/versions/Unicode5.2.0/ch03.pdf#page=13 §3.4, definition D10 >)
-- as 'Char' values, including code points from this invalid range.
-- This means that there are some 'Char' values that are not valid
-- Unicode scalar values, and the functions in this module must handle
-- those cases.
--
-- Within this module, many functions construct a 'Text' from one or
-- more 'Char' values. Those functions will substitute 'Char' values
-- that are not valid Unicode scalar values with the replacement
-- character \"&#xfffd;\" (U+FFFD).  Functions that perform this
-- inspection and replacement are documented with the phrase
-- \"Performs replacement on invalid scalar values\".
--
-- (One reason for this policy of replacement is that internally, a
-- 'Text' value is represented as packed UTF-16 data. Values in the
-- range U+D800 through U+DFFF are used by UTF-16 to denote surrogate
-- code points, and so cannot be represented. The functions replace
-- invalid scalar values, instead of dropping them, as a security
-- measure. For details, see
-- <http://unicode.org/reports/tr36/#Deletion_of_Noncharacters Unicode Technical Report 36, §3.5 >.)

-- $setup
-- >>> import Data.Text
-- >>> import qualified Data.Text as T
-- >>> :seti -XOverloadedStrings

equal :: Text -> Text -> Bool
equal :: Text -> Text -> Bool
equal Text
Empty Text
Empty = Bool
True
equal Text
Empty Text
_     = Bool
False
equal Text
_ Text
Empty     = Bool
False
equal (Chunk Text
a Text
as) (Chunk Text
b Text
bs) =
    case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
lenA Int
lenB of
      Ordering
LT -> Text
a Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== (Int -> Text -> Text
T.takeWord16 Int
lenA Text
b) Bool -> Bool -> Bool
&&
            Text
as Text -> Text -> Bool
`equal` Text -> Text -> Text
Chunk (Int -> Text -> Text
T.dropWord16 Int
lenA Text
b) Text
bs
      Ordering
EQ -> Text
a Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
b Bool -> Bool -> Bool
&& Text
as Text -> Text -> Bool
`equal` Text
bs
      Ordering
GT -> Int -> Text -> Text
T.takeWord16 Int
lenB Text
a Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
b Bool -> Bool -> Bool
&&
            Text -> Text -> Text
Chunk (Int -> Text -> Text
T.dropWord16 Int
lenB Text
a) Text
as Text -> Text -> Bool
`equal` Text
bs
  where lenA :: Int
lenA = Text -> Int
T.lengthWord16 Text
a
        lenB :: Int
lenB = Text -> Int
T.lengthWord16 Text
b

instance Eq Text where
    == :: Text -> Text -> Bool
(==) = Text -> Text -> Bool
equal
    {-# INLINE (==) #-}

instance Ord Text where
    compare :: Text -> Text -> Ordering
compare = Text -> Text -> Ordering
compareText

compareText :: Text -> Text -> Ordering
compareText :: Text -> Text -> Ordering
compareText Text
Empty Text
Empty = Ordering
EQ
compareText Text
Empty Text
_     = Ordering
LT
compareText Text
_     Text
Empty = Ordering
GT
compareText (Chunk Text
a0 Text
as) (Chunk Text
b0 Text
bs) = Text -> Text -> Ordering
outer Text
a0 Text
b0
 where
  outer :: Text -> Text -> Ordering
outer ta :: Text
ta@(T.Text Array
arrA Int
offA Int
lenA) tb :: Text
tb@(T.Text Array
arrB Int
offB Int
lenB) = Int -> Int -> Ordering
go Int
0 Int
0
   where
    go :: Int -> Int -> Ordering
go !Int
i !Int
j
      | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
lenA = Text -> Text -> Ordering
compareText Text
as (Text -> Text -> Text
chunk (Array -> Int -> Int -> Text
T.Text Array
arrB (Int
offBInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
j) (Int
lenBInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
j)) Text
bs)
      | Int
j Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
lenB = Text -> Text -> Ordering
compareText (Text -> Text -> Text
chunk (Array -> Int -> Int -> Text
T.Text Array
arrA (Int
offAInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
i) (Int
lenAInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i)) Text
as) Text
bs
      | Char
a Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
< Char
b     = Ordering
LT
      | Char
a Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
> Char
b     = Ordering
GT
      | Bool
otherwise = Int -> Int -> Ordering
go (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
di) (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
dj)
      where T.Iter Char
a Int
di = Text -> Int -> Iter
T.iter Text
ta Int
i
            T.Iter Char
b Int
dj = Text -> Int -> Iter
T.iter Text
tb Int
j

instance Show Text where
    showsPrec :: Int -> Text -> ShowS
showsPrec Int
p Text
ps String
r = Int -> String -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p (Text -> String
unpack Text
ps) String
r

instance Read Text where
    readsPrec :: Int -> ReadS Text
readsPrec Int
p String
str = [(String -> Text
pack String
x,String
y) | (String
x,String
y) <- Int -> ReadS String
forall a. Read a => Int -> ReadS a
readsPrec Int
p String
str]

-- | @since 1.2.2.0
instance Semigroup Text where
    <> :: Text -> Text -> Text
(<>) = Text -> Text -> Text
append

instance Monoid Text where
    mempty :: Text
mempty  = Text
empty
    mappend :: Text -> Text -> Text
mappend = Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
(<>)
    mconcat :: [Text] -> Text
mconcat = [Text] -> Text
concat

instance IsString Text where
    fromString :: String -> Text
fromString = String -> Text
pack

-- | @since 1.2.0.0
instance Exts.IsList Text where
    type Item Text = Char
    fromList :: [Item Text] -> Text
fromList       = String -> Text
[Item Text] -> Text
pack
    toList :: Text -> [Item Text]
toList         = Text -> String
Text -> [Item Text]
unpack

instance NFData Text where
    rnf :: Text -> ()
rnf Text
Empty        = ()
    rnf (Chunk Text
_ Text
ts) = Text -> ()
forall a. NFData a => a -> ()
rnf Text
ts

-- | @since 1.2.1.0
instance Binary Text where
    put :: Text -> Put
put Text
t = ByteString -> Put
forall t. Binary t => t -> Put
put (Text -> ByteString
encodeUtf8 Text
t)
    get :: Get Text
get   = do
      ByteString
bs <- Get ByteString
forall t. Binary t => Get t
get
      case ByteString -> Either UnicodeException Text
decodeUtf8' ByteString
bs of
        P.Left UnicodeException
exn -> String -> Get Text
forall (m :: * -> *) a. MonadFail m => String -> m a
P.fail (UnicodeException -> String
forall a. Show a => a -> String
P.show UnicodeException
exn)
        P.Right Text
a -> Text -> Get Text
forall (m :: * -> *) a. Monad m => a -> m a
P.return Text
a

-- | This instance preserves data abstraction at the cost of inefficiency.
-- We omit reflection services for the sake of data abstraction.
--
-- This instance was created by copying the updated behavior of
-- @"Data.Text".@'Data.Text.Text'
instance Data Text where
  gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Text -> c Text
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
f forall g. g -> c g
z Text
txt = (String -> Text) -> c (String -> Text)
forall g. g -> c g
z String -> Text
pack c (String -> Text) -> String -> c Text
forall d b. Data d => c (d -> b) -> d -> c b
`f` (Text -> String
unpack Text
txt)
  toConstr :: Text -> Constr
toConstr Text
_     = Constr
packConstr
  gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Text
gunfold forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
c  = case Constr -> Int
constrIndex Constr
c of
    Int
1 -> c (String -> Text) -> c Text
forall b r. Data b => c (b -> r) -> c r
k ((String -> Text) -> c (String -> Text)
forall r. r -> c r
z String -> Text
pack)
    Int
_ -> String -> c Text
forall a. HasCallStack => String -> a
error String
"Data.Text.Lazy.Text.gunfold"
  dataTypeOf :: Text -> DataType
dataTypeOf Text
_   = DataType
textDataType

-- | This instance has similar considerations to the 'Data' instance:
-- it preserves abstraction at the cost of inefficiency.
--
-- @since 1.2.4.0
instance TH.Lift Text where
  lift :: forall (m :: * -> *). Quote m => Text -> m Exp
lift = m Exp -> m Exp -> m Exp
forall (m :: * -> *). Quote m => m Exp -> m Exp -> m Exp
TH.appE (Name -> m Exp
forall (m :: * -> *). Quote m => Name -> m Exp
TH.varE 'pack) (m Exp -> m Exp) -> (Text -> m Exp) -> Text -> m Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m Exp
forall (m :: * -> *). Quote m => String -> m Exp
TH.stringE (String -> m Exp) -> (Text -> String) -> Text -> m Exp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack
#if MIN_VERSION_template_haskell(2,17,0)
  liftTyped :: forall (m :: * -> *). Quote m => Text -> Code m Text
liftTyped = m Exp -> Code m Text
forall a (m :: * -> *). Quote m => m Exp -> Code m a
TH.unsafeCodeCoerce (m Exp -> Code m Text) -> (Text -> m Exp) -> Text -> Code m Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> m Exp
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
TH.lift
#elif MIN_VERSION_template_haskell(2,16,0)
  liftTyped = TH.unsafeTExpCoerce . TH.lift
#endif

-- | @since 1.2.2.0
instance PrintfArg Text where
  formatArg :: Text -> FieldFormatter
formatArg Text
txt = String -> FieldFormatter
forall a. IsChar a => [a] -> FieldFormatter
formatString (String -> FieldFormatter) -> String -> FieldFormatter
forall a b. (a -> b) -> a -> b
$ Text -> String
unpack Text
txt

packConstr :: Constr
packConstr :: Constr
packConstr = DataType -> String -> [String] -> Fixity -> Constr
mkConstr DataType
textDataType String
"pack" [] Fixity
Prefix

textDataType :: DataType
textDataType :: DataType
textDataType = String -> [Constr] -> DataType
mkDataType String
"Data.Text.Lazy.Text" [Constr
packConstr]

-- | /O(n)/ Convert a 'String' into a 'Text'.
--
-- Subject to fusion.  Performs replacement on invalid scalar values.
pack ::
#if defined(ASSERTS)
  HasCallStack =>
#endif
  String -> Text
pack :: String -> Text
pack = Stream Char -> Text
unstream (Stream Char -> Text) -> (String -> Stream Char) -> String -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Stream Char
forall a. [a] -> Stream a
S.streamList (String -> Stream Char) -> ShowS -> String -> Stream Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
L.map Char -> Char
safe
{-# INLINE [1] pack #-}

-- | /O(n)/ Convert a 'Text' into a 'String'.
-- Subject to fusion.
unpack ::
#if defined(ASSERTS)
  HasCallStack =>
#endif
  Text -> String
unpack :: Text -> String
unpack Text
t = Stream Char -> String
forall a. Stream a -> [a]
S.unstreamList (Text -> Stream Char
stream Text
t)
{-# INLINE [1] unpack #-}

-- | /O(n)/ Convert a literal string into a Text.
unpackCString# :: Addr# -> Text
unpackCString# :: Addr# -> Text
unpackCString# Addr#
addr# = Stream Char -> Text
unstream (Addr# -> Stream Char
S.streamCString# Addr#
addr#)
{-# NOINLINE unpackCString# #-}

{-# RULES "TEXT literal" forall a.
    unstream (S.streamList (L.map safe (GHC.unpackCString# a)))
      = unpackCString# a #-}

{-# RULES "TEXT literal UTF8" forall a.
    unstream (S.streamList (L.map safe (GHC.unpackCStringUtf8# a)))
      = unpackCString# a #-}

{-# RULES "LAZY TEXT empty literal"
    unstream (S.streamList (L.map safe []))
      = Empty #-}

{-# RULES "LAZY TEXT empty literal" forall a.
    unstream (S.streamList (L.map safe [a]))
      = Chunk (T.singleton a) Empty #-}

-- | /O(1)/ Convert a character into a Text.  Subject to fusion.
-- Performs replacement on invalid scalar values.
singleton :: Char -> Text
singleton :: Char -> Text
singleton Char
c = Text -> Text -> Text
Chunk (Char -> Text
T.singleton Char
c) Text
Empty
{-# INLINE [1] singleton #-}

{-# RULES
"LAZY TEXT singleton -> fused" [~1] forall c.
    singleton c = unstream (S.singleton c)
"LAZY TEXT singleton -> unfused" [1] forall c.
    unstream (S.singleton c) = singleton c
  #-}

-- | /O(c)/ Convert a list of strict 'T.Text's into a lazy 'Text'.
fromChunks :: [T.Text] -> Text
fromChunks :: [Text] -> Text
fromChunks [Text]
cs = (Text -> Text -> Text) -> Text -> [Text] -> Text
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
L.foldr Text -> Text -> Text
chunk Text
Empty [Text]
cs

-- | /O(n)/ Convert a lazy 'Text' into a list of strict 'T.Text's.
toChunks :: Text -> [T.Text]
toChunks :: Text -> [Text]
toChunks Text
cs = (Text -> [Text] -> [Text]) -> [Text] -> Text -> [Text]
forall a. (Text -> a -> a) -> a -> Text -> a
foldrChunks (:) [] Text
cs

-- | /O(n)/ Convert a lazy 'Text' into a strict 'T.Text'.
toStrict :: Text -> T.Text
toStrict :: Text -> Text
toStrict Text
t = [Text] -> Text
T.concat (Text -> [Text]
toChunks Text
t)
{-# INLINE [1] toStrict #-}

-- | /O(c)/ Convert a strict 'T.Text' into a lazy 'Text'.
fromStrict :: T.Text -> Text
fromStrict :: Text -> Text
fromStrict Text
t = Text -> Text -> Text
chunk Text
t Text
Empty
{-# INLINE [1] fromStrict #-}

-- -----------------------------------------------------------------------------
-- * Basic functions

-- | /O(1)/ Adds a character to the front of a 'Text'.  Subject to fusion.
cons :: Char -> Text -> Text
cons :: Char -> Text -> Text
cons Char
c Text
t = Text -> Text -> Text
Chunk (Char -> Text
T.singleton Char
c) Text
t
{-# INLINE [1] cons #-}

infixr 5 `cons`

{-# RULES
"LAZY TEXT cons -> fused" [~1] forall c t.
    cons c t = unstream (S.cons c (stream t))
"LAZY TEXT cons -> unfused" [1] forall c t.
    unstream (S.cons c (stream t)) = cons c t
 #-}

-- | /O(n)/ Adds a character to the end of a 'Text'.  This copies the
-- entire array in the process, unless fused.  Subject to fusion.
snoc :: Text -> Char -> Text
snoc :: Text -> Char -> Text
snoc Text
t Char
c = (Text -> Text -> Text) -> Text -> Text -> Text
forall a. (Text -> a -> a) -> a -> Text -> a
foldrChunks Text -> Text -> Text
Chunk (Char -> Text
singleton Char
c) Text
t
{-# INLINE [1] snoc #-}

{-# RULES
"LAZY TEXT snoc -> fused" [~1] forall t c.
    snoc t c = unstream (S.snoc (stream t) c)
"LAZY TEXT snoc -> unfused" [1] forall t c.
    unstream (S.snoc (stream t) c) = snoc t c
 #-}

-- | /O(n\/c)/ Appends one 'Text' to another.  Subject to fusion.
append :: Text -> Text -> Text
append :: Text -> Text -> Text
append Text
xs Text
ys = (Text -> Text -> Text) -> Text -> Text -> Text
forall a. (Text -> a -> a) -> a -> Text -> a
foldrChunks Text -> Text -> Text
Chunk Text
ys Text
xs
{-# INLINE [1] append #-}

{-# RULES
"LAZY TEXT append -> fused" [~1] forall t1 t2.
    append t1 t2 = unstream (S.append (stream t1) (stream t2))
"LAZY TEXT append -> unfused" [1] forall t1 t2.
    unstream (S.append (stream t1) (stream t2)) = append t1 t2
 #-}

-- | /O(1)/ Returns the first character and rest of a 'Text', or
-- 'Nothing' if empty. Subject to fusion.
uncons :: Text -> Maybe (Char, Text)
uncons :: Text -> Maybe (Char, Text)
uncons Text
Empty        = Maybe (Char, Text)
forall a. Maybe a
Nothing
uncons (Chunk Text
t Text
ts) = (Char, Text) -> Maybe (Char, Text)
forall a. a -> Maybe a
Just (Text -> Char
T.unsafeHead Text
t, Text
ts')
  where ts' :: Text
ts' | Text -> Int -> Ordering
T.compareLength Text
t Int
1 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
EQ = Text
ts
            | Bool
otherwise                 = Text -> Text -> Text
Chunk (Text -> Text
T.unsafeTail Text
t) Text
ts
{-# INLINE uncons #-}

-- | /O(1)/ Returns the first character of a 'Text', which must be
-- non-empty.  Subject to fusion.
head :: Text -> Char
head :: Text -> Char
head Text
t = Stream Char -> Char
S.head (Text -> Stream Char
stream Text
t)
{-# INLINE head #-}

-- | /O(1)/ Returns all characters after the head of a 'Text', which
-- must be non-empty.  Subject to fusion.
tail :: Text -> Text
tail :: Text -> Text
tail (Chunk Text
t Text
ts) = Text -> Text -> Text
chunk (Text -> Text
T.tail Text
t) Text
ts
tail Text
Empty        = String -> Text
forall a. String -> a
emptyError String
"tail"
{-# INLINE [1] tail #-}

{-# RULES
"LAZY TEXT tail -> fused" [~1] forall t.
    tail t = unstream (S.tail (stream t))
"LAZY TEXT tail -> unfused" [1] forall t.
    unstream (S.tail (stream t)) = tail t
 #-}

-- | /O(n\/c)/ Returns all but the last character of a 'Text', which must
-- be non-empty.  Subject to fusion.
init :: Text -> Text
init :: Text -> Text
init (Chunk Text
t0 Text
ts0) = Text -> Text -> Text
go Text
t0 Text
ts0
    where go :: Text -> Text -> Text
go Text
t (Chunk Text
t' Text
ts) = Text -> Text -> Text
Chunk Text
t (Text -> Text -> Text
go Text
t' Text
ts)
          go Text
t Text
Empty         = Text -> Text -> Text
chunk (Text -> Text
T.init Text
t) Text
Empty
init Text
Empty = String -> Text
forall a. String -> a
emptyError String
"init"
{-# INLINE [1] init #-}

{-# RULES
"LAZY TEXT init -> fused" [~1] forall t.
    init t = unstream (S.init (stream t))
"LAZY TEXT init -> unfused" [1] forall t.
    unstream (S.init (stream t)) = init t
 #-}

-- | /O(n\/c)/ Returns the 'init' and 'last' of a 'Text', or 'Nothing' if
-- empty.
--
-- * It is no faster than using 'init' and 'last'.
--
-- @since 1.2.3.0
unsnoc :: Text -> Maybe (Text, Char)
unsnoc :: Text -> Maybe (Text, Char)
unsnoc Text
Empty          = Maybe (Text, Char)
forall a. Maybe a
Nothing
unsnoc ts :: Text
ts@(Chunk Text
_ Text
_) = (Text, Char) -> Maybe (Text, Char)
forall a. a -> Maybe a
Just (Text -> Text
init Text
ts, Text -> Char
last Text
ts)
{-# INLINE unsnoc #-}

-- | /O(1)/ Tests whether a 'Text' is empty or not.  Subject to
-- fusion.
null :: Text -> Bool
null :: Text -> Bool
null Text
Empty = Bool
True
null Text
_     = Bool
False
{-# INLINE [1] null #-}

{-# RULES
"LAZY TEXT null -> fused" [~1] forall t.
    null t = S.null (stream t)
"LAZY TEXT null -> unfused" [1] forall t.
    S.null (stream t) = null t
 #-}

-- | /O(1)/ Tests whether a 'Text' contains exactly one character.
-- Subject to fusion.
isSingleton :: Text -> Bool
isSingleton :: Text -> Bool
isSingleton = Stream Char -> Bool
S.isSingleton (Stream Char -> Bool) -> (Text -> Stream Char) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Stream Char
stream
{-# INLINE isSingleton #-}

-- | /O(n\/c)/ Returns the last character of a 'Text', which must be
-- non-empty.  Subject to fusion.
last :: Text -> Char
last :: Text -> Char
last Text
Empty        = String -> Char
forall a. String -> a
emptyError String
"last"
last (Chunk Text
t Text
ts) = Text -> Text -> Char
go Text
t Text
ts
    where go :: Text -> Text -> Char
go Text
_ (Chunk Text
t' Text
ts') = Text -> Text -> Char
go Text
t' Text
ts'
          go Text
t' Text
Empty         = Text -> Char
T.last Text
t'
{-# INLINE [1] last #-}

{-# RULES
"LAZY TEXT last -> fused" [~1] forall t.
    last t = S.last (stream t)
"LAZY TEXT last -> unfused" [1] forall t.
    S.last (stream t) = last t
  #-}

-- | /O(n)/ Returns the number of characters in a 'Text'.
-- Subject to fusion.
length :: Text -> Int64
length :: Text -> Int64
length = (Int64 -> Text -> Int64) -> Int64 -> Text -> Int64
forall a. (a -> Text -> a) -> a -> Text -> a
foldlChunks Int64 -> Text -> Int64
go Int64
0
    where
        go :: Int64 -> T.Text -> Int64
        go :: Int64 -> Text -> Int64
go Int64
l Text
t = Int64
l Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int -> Int64
intToInt64 (Text -> Int
T.length Text
t)
{-# INLINE [1] length #-}

{-# RULES
"LAZY TEXT length -> fused" [~1] forall t.
    length t = S.length (stream t)
"LAZY TEXT length -> unfused" [1] forall t.
    S.length (stream t) = length t
 #-}

-- | /O(n)/ Compare the count of characters in a 'Text' to a number.
-- Subject to fusion.
--
-- This function gives the same answer as comparing against the result
-- of 'length', but can short circuit if the count of characters is
-- greater than the number, and hence be more efficient.
compareLength :: Text -> Int64 -> Ordering
compareLength :: Text -> Int64 -> Ordering
compareLength Text
t Int64
n = Stream Char -> Int64 -> Ordering
forall a. Integral a => Stream Char -> a -> Ordering
S.compareLengthI (Text -> Stream Char
stream Text
t) Int64
n
{-# INLINE [1] compareLength #-}

-- We don't apply those otherwise appealing length-to-compareLength
-- rewrite rules here, because they can change the strictness
-- properties of code.

-- | /O(n)/ 'map' @f@ @t@ is the 'Text' obtained by applying @f@ to
-- each element of @t@.  Subject to fusion.  Performs replacement on
-- invalid scalar values.
map :: (Char -> Char) -> Text -> Text
map :: (Char -> Char) -> Text -> Text
map Char -> Char
f Text
t = Stream Char -> Text
unstream ((Char -> Char) -> Stream Char -> Stream Char
S.map (Char -> Char
safe (Char -> Char) -> (Char -> Char) -> Char -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Char
f) (Text -> Stream Char
stream Text
t))
{-# INLINE [1] map #-}

-- | /O(n)/ The 'intercalate' function takes a 'Text' and a list of
-- 'Text's and concatenates the list after interspersing the first
-- argument between each element of the list.
intercalate :: Text -> [Text] -> Text
intercalate :: Text -> [Text] -> Text
intercalate Text
t = [Text] -> Text
concat ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
F.intersperse Text
t)
{-# INLINE intercalate #-}

-- | /O(n)/ The 'intersperse' function takes a character and places it
-- between the characters of a 'Text'.  Subject to fusion.  Performs
-- replacement on invalid scalar values.
intersperse :: Char -> Text -> Text
intersperse :: Char -> Text -> Text
intersperse Char
c Text
t = Stream Char -> Text
unstream (Char -> Stream Char -> Stream Char
S.intersperse (Char -> Char
safe Char
c) (Text -> Stream Char
stream Text
t))
{-# INLINE intersperse #-}

-- | /O(n)/ Left-justify a string to the given length, using the
-- specified fill character on the right. Subject to fusion.  Performs
-- replacement on invalid scalar values.
--
-- Examples:
--
-- > justifyLeft 7 'x' "foo"    == "fooxxxx"
-- > justifyLeft 3 'x' "foobar" == "foobar"
justifyLeft :: Int64 -> Char -> Text -> Text
justifyLeft :: Int64 -> Char -> Text -> Text
justifyLeft Int64
k Char
c Text
t
    | Int64
len Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Int64
k  = Text
t
    | Bool
otherwise = Text
t Text -> Text -> Text
`append` Int64 -> Char -> Text
replicateChar (Int64
kInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int64
len) Char
c
  where len :: Int64
len = Text -> Int64
length Text
t
{-# INLINE [1] justifyLeft #-}

{-# RULES
"LAZY TEXT justifyLeft -> fused" [~1] forall k c t.
    justifyLeft k c t = unstream (S.justifyLeftI k c (stream t))
"LAZY TEXT justifyLeft -> unfused" [1] forall k c t.
    unstream (S.justifyLeftI k c (stream t)) = justifyLeft k c t
  #-}

-- | /O(n)/ Right-justify a string to the given length, using the
-- specified fill character on the left.  Performs replacement on
-- invalid scalar values.
--
-- Examples:
--
-- > justifyRight 7 'x' "bar"    == "xxxxbar"
-- > justifyRight 3 'x' "foobar" == "foobar"
justifyRight :: Int64 -> Char -> Text -> Text
justifyRight :: Int64 -> Char -> Text -> Text
justifyRight Int64
k Char
c Text
t
    | Int64
len Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Int64
k  = Text
t
    | Bool
otherwise = Int64 -> Char -> Text
replicateChar (Int64
kInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int64
len) Char
c Text -> Text -> Text
`append` Text
t
  where len :: Int64
len = Text -> Int64
length Text
t
{-# INLINE justifyRight #-}

-- | /O(n)/ Center a string to the given length, using the specified
-- fill character on either side.  Performs replacement on invalid
-- scalar values.
--
-- Examples:
--
-- > center 8 'x' "HS" = "xxxHSxxx"
center :: Int64 -> Char -> Text -> Text
center :: Int64 -> Char -> Text -> Text
center Int64
k Char
c Text
t
    | Int64
len Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Int64
k  = Text
t
    | Bool
otherwise = Int64 -> Char -> Text
replicateChar Int64
l Char
c Text -> Text -> Text
`append` Text
t Text -> Text -> Text
`append` Int64 -> Char -> Text
replicateChar Int64
r Char
c
  where len :: Int64
len = Text -> Int64
length Text
t
        d :: Int64
d   = Int64
k Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
len
        r :: Int64
r   = Int64
d Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`quot` Int64
2
        l :: Int64
l   = Int64
d Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
r
{-# INLINE center #-}

-- | /O(n)/ The 'transpose' function transposes the rows and columns
-- of its 'Text' argument.  Note that this function uses 'pack',
-- 'unpack', and the list version of transpose, and is thus not very
-- efficient.
transpose :: [Text] -> [Text]
transpose :: [Text] -> [Text]
transpose [Text]
ts = (String -> Text) -> [String] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
L.map (\String
ss -> Text -> Text -> Text
Chunk (String -> Text
T.pack String
ss) Text
Empty)
                     ([String] -> [String]
forall a. [[a]] -> [[a]]
L.transpose ((Text -> String) -> [Text] -> [String]
forall a b. (a -> b) -> [a] -> [b]
L.map Text -> String
unpack [Text]
ts))
-- TODO: make this fast

-- | /O(n)/ 'reverse' @t@ returns the elements of @t@ in reverse order.
reverse ::
#if defined(ASSERTS)
  HasCallStack =>
#endif
  Text -> Text
reverse :: Text -> Text
reverse = Text -> Text -> Text
rev Text
Empty
  where rev :: Text -> Text -> Text
rev Text
a Text
Empty        = Text
a
        rev Text
a (Chunk Text
t Text
ts) = Text -> Text -> Text
rev (Text -> Text -> Text
Chunk (Text -> Text
T.reverse Text
t) Text
a) Text
ts

-- | /O(m+n)/ Replace every non-overlapping occurrence of @needle@ in
-- @haystack@ with @replacement@.
--
-- This function behaves as though it was defined as follows:
--
-- @
-- replace needle replacement haystack =
--   'intercalate' replacement ('splitOn' needle haystack)
-- @
--
-- As this suggests, each occurrence is replaced exactly once.  So if
-- @needle@ occurs in @replacement@, that occurrence will /not/ itself
-- be replaced recursively:
--
-- > replace "oo" "foo" "oo" == "foo"
--
-- In cases where several instances of @needle@ overlap, only the
-- first one will be replaced:
--
-- > replace "ofo" "bar" "ofofo" == "barfo"
--
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards /O(n*m)/.
replace :: Text
        -- ^ @needle@ to search for.  If this string is empty, an
        -- error will occur.
        -> Text
        -- ^ @replacement@ to replace @needle@ with.
        -> Text
        -- ^ @haystack@ in which to search.
        -> Text
replace :: Text -> Text -> Text -> Text
replace Text
s Text
d = Text -> [Text] -> Text
intercalate Text
d ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
splitOn Text
s
{-# INLINE replace #-}

-- ----------------------------------------------------------------------------
-- ** Case conversions (folds)

-- $case
--
-- With Unicode text, it is incorrect to use combinators like @map
-- toUpper@ to case convert each character of a string individually.
-- Instead, use the whole-string case conversion functions from this
-- module.  For correctness in different writing systems, these
-- functions may map one input character to two or three output
-- characters.

-- | /O(n)/ Convert a string to folded case.  Subject to fusion.
--
-- This function is mainly useful for performing caseless (or case
-- insensitive) string comparisons.
--
-- A string @x@ is a caseless match for a string @y@ if and only if:
--
-- @toCaseFold x == toCaseFold y@
--
-- The result string may be longer than the input string, and may
-- differ from applying 'toLower' to the input string.  For instance,
-- the Armenian small ligature men now (U+FB13) is case folded to the
-- bigram men now (U+0574 U+0576), while the micro sign (U+00B5) is
-- case folded to the Greek small letter letter mu (U+03BC) instead of
-- itself.
toCaseFold :: Text -> Text
toCaseFold :: Text -> Text
toCaseFold Text
t = Stream Char -> Text
unstream (Stream Char -> Stream Char
S.toCaseFold (Text -> Stream Char
stream Text
t))
{-# INLINE toCaseFold #-}

-- | /O(n)/ Convert a string to lower case, using simple case
-- conversion.  Subject to fusion.
--
-- The result string may be longer than the input string.  For
-- instance, the Latin capital letter I with dot above (U+0130) maps
-- to the sequence Latin small letter i (U+0069) followed by combining
-- dot above (U+0307).
toLower :: Text -> Text
toLower :: Text -> Text
toLower Text
t = Stream Char -> Text
unstream (Stream Char -> Stream Char
S.toLower (Text -> Stream Char
stream Text
t))
{-# INLINE toLower #-}

-- | /O(n)/ Convert a string to upper case, using simple case
-- conversion.  Subject to fusion.
--
-- The result string may be longer than the input string.  For
-- instance, the German eszett (U+00DF) maps to the two-letter
-- sequence SS.
toUpper :: Text -> Text
toUpper :: Text -> Text
toUpper Text
t = Stream Char -> Text
unstream (Stream Char -> Stream Char
S.toUpper (Text -> Stream Char
stream Text
t))
{-# INLINE toUpper #-}


-- | /O(n)/ Convert a string to title case, using simple case
-- conversion.  Subject to fusion.
--
-- The first letter of the input is converted to title case, as is
-- every subsequent letter that immediately follows a non-letter.
-- Every letter that immediately follows another letter is converted
-- to lower case.
--
-- The result string may be longer than the input string. For example,
-- the Latin small ligature &#xfb02; (U+FB02) is converted to the
-- sequence Latin capital letter F (U+0046) followed by Latin small
-- letter l (U+006C).
--
-- /Note/: this function does not take language or culture specific
-- rules into account. For instance, in English, different style
-- guides disagree on whether the book name \"The Hill of the Red
-- Fox\" is correctly title cased&#x2014;but this function will
-- capitalize /every/ word.
--
-- @since 1.0.0.0
toTitle :: Text -> Text
toTitle :: Text -> Text
toTitle Text
t = Stream Char -> Text
unstream (Stream Char -> Stream Char
S.toTitle (Text -> Stream Char
stream Text
t))
{-# INLINE toTitle #-}

-- | /O(n)/ 'foldl', applied to a binary operator, a starting value
-- (typically the left-identity of the operator), and a 'Text',
-- reduces the 'Text' using the binary operator, from left to right.
-- Subject to fusion.
foldl :: (a -> Char -> a) -> a -> Text -> a
foldl :: forall a. (a -> Char -> a) -> a -> Text -> a
foldl a -> Char -> a
f a
z Text
t = (a -> Char -> a) -> a -> Stream Char -> a
forall b. (b -> Char -> b) -> b -> Stream Char -> b
S.foldl a -> Char -> a
f a
z (Text -> Stream Char
stream Text
t)
{-# INLINE foldl #-}

-- | /O(n)/ A strict version of 'foldl'.
-- Subject to fusion.
foldl' :: (a -> Char -> a) -> a -> Text -> a
foldl' :: forall a. (a -> Char -> a) -> a -> Text -> a
foldl' a -> Char -> a
f a
z Text
t = (a -> Char -> a) -> a -> Stream Char -> a
forall b. (b -> Char -> b) -> b -> Stream Char -> b
S.foldl' a -> Char -> a
f a
z (Text -> Stream Char
stream Text
t)
{-# INLINE foldl' #-}

-- | /O(n)/ A variant of 'foldl' that has no starting value argument,
-- and thus must be applied to a non-empty 'Text'.  Subject to fusion.
foldl1 :: (Char -> Char -> Char) -> Text -> Char
foldl1 :: (Char -> Char -> Char) -> Text -> Char
foldl1 Char -> Char -> Char
f Text
t = (Char -> Char -> Char) -> Stream Char -> Char
S.foldl1 Char -> Char -> Char
f (Text -> Stream Char
stream Text
t)
{-# INLINE foldl1 #-}

-- | /O(n)/ A strict version of 'foldl1'.  Subject to fusion.
foldl1' :: (Char -> Char -> Char) -> Text -> Char
foldl1' :: (Char -> Char -> Char) -> Text -> Char
foldl1' Char -> Char -> Char
f Text
t = (Char -> Char -> Char) -> Stream Char -> Char
S.foldl1' Char -> Char -> Char
f (Text -> Stream Char
stream Text
t)
{-# INLINE foldl1' #-}

-- | /O(n)/ 'foldr', applied to a binary operator, a starting value
-- (typically the right-identity of the operator), and a 'Text',
-- reduces the 'Text' using the binary operator, from right to left.
-- Subject to fusion.
foldr :: (Char -> a -> a) -> a -> Text -> a
foldr :: forall a. (Char -> a -> a) -> a -> Text -> a
foldr Char -> a -> a
f a
z Text
t = (Char -> a -> a) -> a -> Stream Char -> a
forall b. (Char -> b -> b) -> b -> Stream Char -> b
S.foldr Char -> a -> a
f a
z (Text -> Stream Char
stream Text
t)
{-# INLINE foldr #-}

-- | /O(n)/ A variant of 'foldr' that has no starting value argument,
-- and thus must be applied to a non-empty 'Text'.  Subject to
-- fusion.
foldr1 :: (Char -> Char -> Char) -> Text -> Char
foldr1 :: (Char -> Char -> Char) -> Text -> Char
foldr1 Char -> Char -> Char
f Text
t = (Char -> Char -> Char) -> Stream Char -> Char
S.foldr1 Char -> Char -> Char
f (Text -> Stream Char
stream Text
t)
{-# INLINE foldr1 #-}

-- | /O(n)/ Concatenate a list of 'Text's.
concat :: [Text] -> Text
concat :: [Text] -> Text
concat = [Text] -> Text
to
  where
    go :: Text -> [Text] -> Text
go Text
Empty        [Text]
css = [Text] -> Text
to [Text]
css
    go (Chunk Text
c Text
cs) [Text]
css = Text -> Text -> Text
Chunk Text
c (Text -> [Text] -> Text
go Text
cs [Text]
css)
    to :: [Text] -> Text
to []               = Text
Empty
    to (Text
cs:[Text]
css)         = Text -> [Text] -> Text
go Text
cs [Text]
css
{-# INLINE concat #-}

-- | /O(n)/ Map a function over a 'Text' that results in a 'Text', and
-- concatenate the results.
concatMap :: (Char -> Text) -> Text -> Text
concatMap :: (Char -> Text) -> Text -> Text
concatMap Char -> Text
f = [Text] -> Text
concat ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> [Text] -> [Text]) -> [Text] -> Text -> [Text]
forall a. (Char -> a -> a) -> a -> Text -> a
foldr ((:) (Text -> [Text] -> [Text])
-> (Char -> Text) -> Char -> [Text] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
f) []
{-# INLINE concatMap #-}

-- | /O(n)/ 'any' @p@ @t@ determines whether any character in the
-- 'Text' @t@ satisfies the predicate @p@. Subject to fusion.
any :: (Char -> Bool) -> Text -> Bool
any :: (Char -> Bool) -> Text -> Bool
any Char -> Bool
p Text
t = (Char -> Bool) -> Stream Char -> Bool
S.any Char -> Bool
p (Text -> Stream Char
stream Text
t)
{-# INLINE any #-}

-- | /O(n)/ 'all' @p@ @t@ determines whether all characters in the
-- 'Text' @t@ satisfy the predicate @p@. Subject to fusion.
all :: (Char -> Bool) -> Text -> Bool
all :: (Char -> Bool) -> Text -> Bool
all Char -> Bool
p Text
t = (Char -> Bool) -> Stream Char -> Bool
S.all Char -> Bool
p (Text -> Stream Char
stream Text
t)
{-# INLINE all #-}

-- | /O(n)/ 'maximum' returns the maximum value from a 'Text', which
-- must be non-empty. Subject to fusion.
maximum :: Text -> Char
maximum :: Text -> Char
maximum Text
t = Stream Char -> Char
S.maximum (Text -> Stream Char
stream Text
t)
{-# INLINE maximum #-}

-- | /O(n)/ 'minimum' returns the minimum value from a 'Text', which
-- must be non-empty. Subject to fusion.
minimum :: Text -> Char
minimum :: Text -> Char
minimum Text
t = Stream Char -> Char
S.minimum (Text -> Stream Char
stream Text
t)
{-# INLINE minimum #-}

-- | /O(n)/ 'scanl' is similar to 'foldl', but returns a list of
-- successive reduced values from the left. Subject to fusion.
-- Performs replacement on invalid scalar values.
--
-- > scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
--
-- Note that
--
-- > last (scanl f z xs) == foldl f z xs.
scanl :: (Char -> Char -> Char) -> Char -> Text -> Text
scanl :: (Char -> Char -> Char) -> Char -> Text -> Text
scanl Char -> Char -> Char
f Char
z Text
t = Stream Char -> Text
unstream ((Char -> Char -> Char) -> Char -> Stream Char -> Stream Char
S.scanl Char -> Char -> Char
g Char
z (Text -> Stream Char
stream Text
t))
    where g :: Char -> Char -> Char
g Char
a Char
b = Char -> Char
safe (Char -> Char -> Char
f Char
a Char
b)
{-# INLINE scanl #-}

-- | /O(n)/ 'scanl1' is a variant of 'scanl' that has no starting
-- value argument.  Performs replacement on invalid scalar values.
--
-- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
scanl1 :: (Char -> Char -> Char) -> Text -> Text
scanl1 :: (Char -> Char -> Char) -> Text -> Text
scanl1 Char -> Char -> Char
f Text
t0 = case Text -> Maybe (Char, Text)
uncons Text
t0 of
                Maybe (Char, Text)
Nothing -> Text
empty
                Just (Char
t,Text
ts) -> (Char -> Char -> Char) -> Char -> Text -> Text
scanl Char -> Char -> Char
f Char
t Text
ts
{-# INLINE scanl1 #-}

-- | /O(n)/ 'scanr' is the right-to-left dual of 'scanl'.  Performs
-- replacement on invalid scalar values.
--
-- > scanr f v == reverse . scanl (flip f) v . reverse
scanr :: (Char -> Char -> Char) -> Char -> Text -> Text
scanr :: (Char -> Char -> Char) -> Char -> Text -> Text
scanr Char -> Char -> Char
f Char
v = Text -> Text
reverse (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char -> Char) -> Char -> Text -> Text
scanl Char -> Char -> Char
g Char
v (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
reverse
    where g :: Char -> Char -> Char
g Char
a Char
b = Char -> Char
safe (Char -> Char -> Char
f Char
b Char
a)

-- | /O(n)/ 'scanr1' is a variant of 'scanr' that has no starting
-- value argument.  Performs replacement on invalid scalar values.
scanr1 :: (Char -> Char -> Char) -> Text -> Text
scanr1 :: (Char -> Char -> Char) -> Text -> Text
scanr1 Char -> Char -> Char
f Text
t | Text -> Bool
null Text
t    = Text
empty
           | Bool
otherwise = (Char -> Char -> Char) -> Char -> Text -> Text
scanr Char -> Char -> Char
f (Text -> Char
last Text
t) (Text -> Text
init Text
t)

-- | /O(n)/ Like a combination of 'map' and 'foldl''. Applies a
-- function to each element of a 'Text', passing an accumulating
-- parameter from left to right, and returns a final 'Text'.  Performs
-- replacement on invalid scalar values.
mapAccumL :: (a -> Char -> (a,Char)) -> a -> Text -> (a, Text)
mapAccumL :: forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
mapAccumL a -> Char -> (a, Char)
f = a -> Text -> (a, Text)
go
  where
    go :: a -> Text -> (a, Text)
go a
z (Chunk Text
c Text
cs)    = (a
z'', Text -> Text -> Text
Chunk Text
c' Text
cs')
        where (a
z',  Text
c')  = (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
T.mapAccumL a -> Char -> (a, Char)
f a
z Text
c
              (a
z'', Text
cs') = a -> Text -> (a, Text)
go a
z' Text
cs
    go a
z Text
Empty           = (a
z, Text
Empty)
{-# INLINE mapAccumL #-}

-- | The 'mapAccumR' function behaves like a combination of 'map' and
-- a strict 'foldr'; it applies a function to each element of a
-- 'Text', passing an accumulating parameter from right to left, and
-- returning a final value of this accumulator together with the new
-- 'Text'.  Performs replacement on invalid scalar values.
mapAccumR :: (a -> Char -> (a,Char)) -> a -> Text -> (a, Text)
mapAccumR :: forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
mapAccumR a -> Char -> (a, Char)
f = a -> Text -> (a, Text)
go
  where
    go :: a -> Text -> (a, Text)
go a
z (Chunk Text
c Text
cs)   = (a
z'', Text -> Text -> Text
Chunk Text
c' Text
cs')
        where (a
z'', Text
c') = (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
forall a. (a -> Char -> (a, Char)) -> a -> Text -> (a, Text)
T.mapAccumR a -> Char -> (a, Char)
f a
z' Text
c
              (a
z', Text
cs') = a -> Text -> (a, Text)
go a
z Text
cs
    go a
z Text
Empty          = (a
z, Text
Empty)
{-# INLINE mapAccumR #-}

-- | @'repeat' x@ is an infinite 'Text', with @x@ the value of every
-- element.
--
-- @since 1.2.0.5
repeat :: Char -> Text
repeat :: Char -> Text
repeat Char
c = let t :: Text
t = Text -> Text -> Text
Chunk (Int -> Text -> Text
T.replicate Int
smallChunkSize (Char -> Text
T.singleton Char
c)) Text
t
            in Text
t

-- | /O(n*m)/ 'replicate' @n@ @t@ is a 'Text' consisting of the input
-- @t@ repeated @n@ times.
replicate :: Int64 -> Text -> Text
replicate :: Int64 -> Text -> Text
replicate Int64
n Text
t
    | Text -> Bool
null Text
t Bool -> Bool -> Bool
|| Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0 = Text
empty
    | Text -> Bool
isSingleton Text
t    = Int64 -> Char -> Text
replicateChar Int64
n (Text -> Char
head Text
t)
    | Bool
otherwise        = [Text] -> Text
concat (Int64 -> [Text]
rep Int64
0)
    where rep :: Int64 -> [Text]
rep !Int64
i | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Int64
n    = []
                 | Bool
otherwise = Text
t Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Int64 -> [Text]
rep (Int64
iInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+Int64
1)
{-# INLINE [1] replicate #-}

-- | 'cycle' ties a finite, non-empty 'Text' into a circular one, or
-- equivalently, the infinite repetition of the original 'Text'.
--
-- @since 1.2.0.5
cycle :: Text -> Text
cycle :: Text -> Text
cycle Text
Empty = String -> Text
forall a. String -> a
emptyError String
"cycle"
cycle Text
t     = let t' :: Text
t' = (Text -> Text -> Text) -> Text -> Text -> Text
forall a. (Text -> a -> a) -> a -> Text -> a
foldrChunks Text -> Text -> Text
Chunk Text
t' Text
t
               in Text
t'

-- | @'iterate' f x@ returns an infinite 'Text' of repeated applications
-- of @f@ to @x@:
--
-- > iterate f x == [x, f x, f (f x), ...]
--
-- @since 1.2.0.5
iterate :: (Char -> Char) -> Char -> Text
iterate :: (Char -> Char) -> Char -> Text
iterate Char -> Char
f Char
c = let t :: Char -> Text
t Char
c' = Text -> Text -> Text
Chunk (Char -> Text
T.singleton Char
c') (Char -> Text
t (Char -> Char
f Char
c'))
               in Char -> Text
t Char
c

-- | /O(n)/ 'replicateChar' @n@ @c@ is a 'Text' of length @n@ with @c@ the
-- value of every element. Subject to fusion.
replicateChar :: Int64 -> Char -> Text
replicateChar :: Int64 -> Char -> Text
replicateChar Int64
n Char
c = Stream Char -> Text
unstream (Int64 -> Char -> Stream Char
forall a. Integral a => a -> Char -> Stream Char
S.replicateCharI Int64
n (Char -> Char
safe Char
c))
{-# INLINE replicateChar #-}

{-# RULES
"LAZY TEXT replicate/singleton -> replicateChar" [~1] forall n c.
    replicate n (singleton c) = replicateChar n c
"LAZY TEXT replicate/unstream/singleton -> replicateChar" [~1] forall n c.
    replicate n (unstream (S.singleton c)) = replicateChar n c
  #-}

-- | /O(n)/, where @n@ is the length of the result. The 'unfoldr'
-- function is analogous to the List 'L.unfoldr'. 'unfoldr' builds a
-- 'Text' from a seed value. The function takes the element and
-- returns 'Nothing' if it is done producing the 'Text', otherwise
-- 'Just' @(a,b)@.  In this case, @a@ is the next 'Char' in the
-- string, and @b@ is the seed value for further production.
-- Subject to fusion.
-- Performs replacement on invalid scalar values.
unfoldr :: (a -> Maybe (Char,a)) -> a -> Text
unfoldr :: forall a. (a -> Maybe (Char, a)) -> a -> Text
unfoldr a -> Maybe (Char, a)
f a
s = Stream Char -> Text
unstream ((a -> Maybe (Char, a)) -> a -> Stream Char
forall a. (a -> Maybe (Char, a)) -> a -> Stream Char
S.unfoldr ((Char -> Char) -> Maybe (Char, a) -> Maybe (Char, a)
forall a c b. (a -> c) -> Maybe (a, b) -> Maybe (c, b)
firstf Char -> Char
safe (Maybe (Char, a) -> Maybe (Char, a))
-> (a -> Maybe (Char, a)) -> a -> Maybe (Char, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe (Char, a)
f) a
s)
{-# INLINE unfoldr #-}

-- | /O(n)/ Like 'unfoldr', 'unfoldrN' builds a 'Text' from a seed
-- value. However, the length of the result should be limited by the
-- first argument to 'unfoldrN'. This function is more efficient than
-- 'unfoldr' when the maximum length of the result is known and
-- correct, otherwise its performance is similar to 'unfoldr'.
-- Subject to fusion.
-- Performs replacement on invalid scalar values.
unfoldrN :: Int64 -> (a -> Maybe (Char,a)) -> a -> Text
unfoldrN :: forall a. Int64 -> (a -> Maybe (Char, a)) -> a -> Text
unfoldrN Int64
n a -> Maybe (Char, a)
f a
s = Stream Char -> Text
unstream (Int64 -> (a -> Maybe (Char, a)) -> a -> Stream Char
forall a. Int64 -> (a -> Maybe (Char, a)) -> a -> Stream Char
S.unfoldrN Int64
n ((Char -> Char) -> Maybe (Char, a) -> Maybe (Char, a)
forall a c b. (a -> c) -> Maybe (a, b) -> Maybe (c, b)
firstf Char -> Char
safe (Maybe (Char, a) -> Maybe (Char, a))
-> (a -> Maybe (Char, a)) -> a -> Maybe (Char, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe (Char, a)
f) a
s)
{-# INLINE unfoldrN #-}

-- | /O(n)/ 'take' @n@, applied to a 'Text', returns the prefix of the
-- 'Text' of length @n@, or the 'Text' itself if @n@ is greater than
-- the length of the Text. Subject to fusion.
take :: Int64 -> Text -> Text
take :: Int64 -> Text -> Text
take Int64
i Text
_ | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0 = Text
Empty
take Int64
i Text
t0         = Int64 -> Text -> Text
take' Int64
i Text
t0
  where
    take' :: Int64 -> Text -> Text
    take' :: Int64 -> Text -> Text
take' Int64
0 Text
_            = Text
Empty
    take' Int64
_ Text
Empty        = Text
Empty
    take' Int64
n (Chunk Text
t Text
ts)
        | Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
len   = Text -> Text -> Text
Chunk (Int -> Text -> Text
T.take (Int64 -> Int
int64ToInt Int64
n) Text
t) Text
Empty
        | Bool
otherwise = Text -> Text -> Text
Chunk Text
t (Int64 -> Text -> Text
take' (Int64
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
len) Text
ts)
        where len :: Int64
len = Int -> Int64
intToInt64 (Text -> Int
T.length Text
t)
{-# INLINE [1] take #-}

{-# RULES
"LAZY TEXT take -> fused" [~1] forall n t.
    take n t = unstream (S.take n (stream t))
"LAZY TEXT take -> unfused" [1] forall n t.
    unstream (S.take n (stream t)) = take n t
  #-}

-- | /O(n)/ 'takeEnd' @n@ @t@ returns the suffix remaining after
-- taking @n@ characters from the end of @t@.
--
-- Examples:
--
-- > takeEnd 3 "foobar" == "bar"
--
-- @since 1.1.1.0
takeEnd :: Int64 -> Text -> Text
takeEnd :: Int64 -> Text -> Text
takeEnd Int64
n Text
t0
    | Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0    = Text
empty
    | Bool
otherwise = Int64 -> Text -> [Text] -> Text
takeChunk Int64
n Text
empty ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
forall a. [a] -> [a]
L.reverse ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
toChunks (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
t0
  where
    takeChunk :: Int64 -> Text -> [T.Text] -> Text
    takeChunk :: Int64 -> Text -> [Text] -> Text
takeChunk Int64
_ Text
acc [] = Text
acc
    takeChunk Int64
i Text
acc (Text
t:[Text]
ts)
      | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
l    = Text -> Text -> Text
chunk (Int -> Text -> Text
T.takeEnd (Int64 -> Int
int64ToInt Int64
i) Text
t) Text
acc
      | Bool
otherwise = Int64 -> Text -> [Text] -> Text
takeChunk (Int64
iInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int64
l) (Text -> Text -> Text
Chunk Text
t Text
acc) [Text]
ts
      where l :: Int64
l = Int -> Int64
intToInt64 (Text -> Int
T.length Text
t)

-- | /O(n)/ 'drop' @n@, applied to a 'Text', returns the suffix of the
-- 'Text' after the first @n@ characters, or the empty 'Text' if @n@
-- is greater than the length of the 'Text'. Subject to fusion.
drop :: Int64 -> Text -> Text
drop :: Int64 -> Text -> Text
drop Int64
i Text
t0
    | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0    = Text
t0
    | Bool
otherwise = Int64 -> Text -> Text
drop' Int64
i Text
t0
  where
    drop' :: Int64 -> Text -> Text
    drop' :: Int64 -> Text -> Text
drop' Int64
0 Text
ts           = Text
ts
    drop' Int64
_ Text
Empty        = Text
Empty
    drop' Int64
n (Chunk Text
t Text
ts)
        | Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
len   = Text -> Text -> Text
Chunk (Int -> Text -> Text
T.drop (Int64 -> Int
int64ToInt Int64
n) Text
t) Text
ts
        | Bool
otherwise = Int64 -> Text -> Text
drop' (Int64
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
len) Text
ts
        where len :: Int64
len   = Int -> Int64
intToInt64 (Text -> Int
T.length Text
t)
{-# INLINE [1] drop #-}

{-# RULES
"LAZY TEXT drop -> fused" [~1] forall n t.
    drop n t = unstream (S.drop n (stream t))
"LAZY TEXT drop -> unfused" [1] forall n t.
    unstream (S.drop n (stream t)) = drop n t
  #-}

-- | /O(n)/ 'dropEnd' @n@ @t@ returns the prefix remaining after
-- dropping @n@ characters from the end of @t@.
--
-- Examples:
--
-- > dropEnd 3 "foobar" == "foo"
--
-- @since 1.1.1.0
dropEnd :: Int64 -> Text -> Text
dropEnd :: Int64 -> Text -> Text
dropEnd Int64
n Text
t0
    | Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0    = Text
t0
    | Bool
otherwise = Int64 -> [Text] -> Text
dropChunk Int64
n ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
forall a. [a] -> [a]
L.reverse ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
toChunks (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
t0
  where
    dropChunk :: Int64 -> [T.Text] -> Text
    dropChunk :: Int64 -> [Text] -> Text
dropChunk Int64
_ [] = Text
empty
    dropChunk Int64
m (Text
t:[Text]
ts)
      | Int64
m Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Int64
l    = Int64 -> [Text] -> Text
dropChunk (Int64
mInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int64
l) [Text]
ts
      | Bool
otherwise = [Text] -> Text
fromChunks ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
forall a. [a] -> [a]
L.reverse ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$
                    Int -> Text -> Text
T.dropEnd (Int64 -> Int
int64ToInt Int64
m) Text
t Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
ts
      where l :: Int64
l = Int -> Int64
intToInt64 (Text -> Int
T.length Text
t)

-- | /O(n)/ 'dropWords' @n@ returns the suffix with @n@ 'Word16'
-- values dropped, or the empty 'Text' if @n@ is greater than the
-- number of 'Word16' values present.
dropWords :: Int64 -> Text -> Text
dropWords :: Int64 -> Text -> Text
dropWords Int64
i Text
t0
    | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0    = Text
t0
    | Bool
otherwise = Int64 -> Text -> Text
drop' Int64
i Text
t0
  where
    drop' :: Int64 -> Text -> Text
    drop' :: Int64 -> Text -> Text
drop' Int64
0 Text
ts           = Text
ts
    drop' Int64
_ Text
Empty        = Text
Empty
    drop' Int64
n (Chunk (T.Text Array
arr Int
off Int
len) Text
ts)
        | Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
len'  = Text -> Text -> Text
chunk (Array -> Int -> Int -> Text
text Array
arr (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n') (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n')) Text
ts
        | Bool
otherwise = Int64 -> Text -> Text
drop' (Int64
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
len') Text
ts
        where len' :: Int64
len'  = Int -> Int64
intToInt64 Int
len
              n' :: Int
n'    = Int64 -> Int
int64ToInt Int64
n

-- | /O(n)/ 'takeWhile', applied to a predicate @p@ and a 'Text',
-- returns the longest prefix (possibly empty) of elements that
-- satisfy @p@.  Subject to fusion.
takeWhile :: (Char -> Bool) -> Text -> Text
takeWhile :: (Char -> Bool) -> Text -> Text
takeWhile Char -> Bool
p Text
t0 = Text -> Text
takeWhile' Text
t0
  where takeWhile' :: Text -> Text
takeWhile' Text
Empty        = Text
Empty
        takeWhile' (Chunk Text
t Text
ts) =
          case (Char -> Bool) -> Text -> Maybe Int
T.findIndex (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) Text
t of
            Just Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0     -> Text -> Text -> Text
Chunk (Int -> Text -> Text
T.take Int
n Text
t) Text
Empty
                   | Bool
otherwise -> Text
Empty
            Maybe Int
Nothing            -> Text -> Text -> Text
Chunk Text
t (Text -> Text
takeWhile' Text
ts)
{-# INLINE [1] takeWhile #-}

{-# RULES
"LAZY TEXT takeWhile -> fused" [~1] forall p t.
    takeWhile p t = unstream (S.takeWhile p (stream t))
"LAZY TEXT takeWhile -> unfused" [1] forall p t.
    unstream (S.takeWhile p (stream t)) = takeWhile p t
  #-}
-- | /O(n)/ 'takeWhileEnd', applied to a predicate @p@ and a 'Text',
-- returns the longest suffix (possibly empty) of elements that
-- satisfy @p@.
-- Examples:
--
-- > takeWhileEnd (=='o') "foo" == "oo"
--
-- @since 1.2.2.0
takeWhileEnd :: (Char -> Bool) -> Text -> Text
takeWhileEnd :: (Char -> Bool) -> Text -> Text
takeWhileEnd Char -> Bool
p = Text -> [Text] -> Text
takeChunk Text
empty ([Text] -> Text) -> (Text -> [Text]) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
forall a. [a] -> [a]
L.reverse ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
toChunks
  where takeChunk :: Text -> [Text] -> Text
takeChunk Text
acc []     = Text
acc
        takeChunk Text
acc (Text
t:[Text]
ts)
          | Text -> Int
T.lengthWord16 Text
t' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Text -> Int
T.lengthWord16 Text
t
                             = Text -> Text -> Text
chunk Text
t' Text
acc
          | Bool
otherwise        = Text -> [Text] -> Text
takeChunk (Text -> Text -> Text
Chunk Text
t' Text
acc) [Text]
ts
          where t' :: Text
t' = (Char -> Bool) -> Text -> Text
T.takeWhileEnd Char -> Bool
p Text
t
{-# INLINE takeWhileEnd #-}

-- | /O(n)/ 'dropWhile' @p@ @t@ returns the suffix remaining after
-- 'takeWhile' @p@ @t@.  Subject to fusion.
dropWhile :: (Char -> Bool) -> Text -> Text
dropWhile :: (Char -> Bool) -> Text -> Text
dropWhile Char -> Bool
p Text
t0 = Text -> Text
dropWhile' Text
t0
  where dropWhile' :: Text -> Text
dropWhile' Text
Empty        = Text
Empty
        dropWhile' (Chunk Text
t Text
ts) =
          case (Char -> Bool) -> Text -> Maybe Int
T.findIndex (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) Text
t of
            Just Int
n  -> Text -> Text -> Text
Chunk (Int -> Text -> Text
T.drop Int
n Text
t) Text
ts
            Maybe Int
Nothing -> Text -> Text
dropWhile' Text
ts
{-# INLINE [1] dropWhile #-}

{-# RULES
"LAZY TEXT dropWhile -> fused" [~1] forall p t.
    dropWhile p t = unstream (S.dropWhile p (stream t))
"LAZY TEXT dropWhile -> unfused" [1] forall p t.
    unstream (S.dropWhile p (stream t)) = dropWhile p t
  #-}

-- | /O(n)/ 'dropWhileEnd' @p@ @t@ returns the prefix remaining after
-- dropping characters that satisfy the predicate @p@ from the end of
-- @t@.
--
-- Examples:
--
-- > dropWhileEnd (=='.') "foo..." == "foo"
dropWhileEnd :: (Char -> Bool) -> Text -> Text
dropWhileEnd :: (Char -> Bool) -> Text -> Text
dropWhileEnd Char -> Bool
p = Text -> Text
go
  where go :: Text -> Text
go Text
Empty = Text
Empty
        go (Chunk Text
t Text
Empty) = if Text -> Bool
T.null Text
t'
                             then Text
Empty
                             else Text -> Text -> Text
Chunk Text
t' Text
Empty
            where t' :: Text
t' = (Char -> Bool) -> Text -> Text
T.dropWhileEnd Char -> Bool
p Text
t
        go (Chunk Text
t Text
ts) = case Text -> Text
go Text
ts of
                            Text
Empty -> Text -> Text
go (Text -> Text -> Text
Chunk Text
t Text
Empty)
                            Text
ts' -> Text -> Text -> Text
Chunk Text
t Text
ts'
{-# INLINE dropWhileEnd #-}

-- | /O(n)/ 'dropAround' @p@ @t@ returns the substring remaining after
-- dropping characters that satisfy the predicate @p@ from both the
-- beginning and end of @t@.
dropAround :: (Char -> Bool) -> Text -> Text
dropAround :: (Char -> Bool) -> Text -> Text
dropAround Char -> Bool
p = (Char -> Bool) -> Text -> Text
dropWhile Char -> Bool
p (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
dropWhileEnd Char -> Bool
p
{-# INLINE [1] dropAround #-}

-- | /O(n)/ Remove leading white space from a string.  Equivalent to:
--
-- > dropWhile isSpace
stripStart :: Text -> Text
stripStart :: Text -> Text
stripStart = (Char -> Bool) -> Text -> Text
dropWhile Char -> Bool
isSpace
{-# INLINE stripStart #-}

-- | /O(n)/ Remove trailing white space from a string.  Equivalent to:
--
-- > dropWhileEnd isSpace
stripEnd :: Text -> Text
stripEnd :: Text -> Text
stripEnd = (Char -> Bool) -> Text -> Text
dropWhileEnd Char -> Bool
isSpace
{-# INLINE [1] stripEnd #-}

-- | /O(n)/ Remove leading and trailing white space from a string.
-- Equivalent to:
--
-- > dropAround isSpace
strip :: Text -> Text
strip :: Text -> Text
strip = (Char -> Bool) -> Text -> Text
dropAround Char -> Bool
isSpace
{-# INLINE [1] strip #-}

-- | /O(n)/ 'splitAt' @n t@ returns a pair whose first element is a
-- prefix of @t@ of length @n@, and whose second is the remainder of
-- the string. It is equivalent to @('take' n t, 'drop' n t)@.
splitAt :: Int64 -> Text -> (Text, Text)
splitAt :: Int64 -> Text -> (Text, Text)
splitAt = Int64 -> Text -> (Text, Text)
loop
  where
    loop :: Int64 -> Text -> (Text, Text)
    loop :: Int64 -> Text -> (Text, Text)
loop Int64
_ Text
Empty      = (Text
empty, Text
empty)
    loop Int64
n Text
t | Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0 = (Text
empty, Text
t)
    loop Int64
n (Chunk Text
t Text
ts)
         | Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
len   = let (Text
t',Text
t'') = Int -> Text -> (Text, Text)
T.splitAt (Int64 -> Int
int64ToInt Int64
n) Text
t
                       in (Text -> Text -> Text
Chunk Text
t' Text
Empty, Text -> Text -> Text
Chunk Text
t'' Text
ts)
         | Bool
otherwise = let (Text
ts',Text
ts'') = Int64 -> Text -> (Text, Text)
loop (Int64
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
len) Text
ts
                       in (Text -> Text -> Text
Chunk Text
t Text
ts', Text
ts'')
         where len :: Int64
len = Int -> Int64
intToInt64 (Text -> Int
T.length Text
t)

-- | /O(n)/ 'splitAtWord' @n t@ returns a strict pair whose first
-- element is a prefix of @t@ whose chunks contain @n@ 'Word16'
-- values, and whose second is the remainder of the string.
splitAtWord :: Int64 -> Text -> PairS Text Text
splitAtWord :: Int64 -> Text -> PairS Text Text
splitAtWord Int64
_ Text
Empty = Text
empty Text -> Text -> PairS Text Text
forall a b. a -> b -> PairS a b
:*: Text
empty
splitAtWord Int64
x (Chunk c :: Text
c@(T.Text Array
arr Int
off Int
len) Text
cs)
    | Int
y Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
len  = let Text
h :*: Text
t = Int64 -> Text -> PairS Text Text
splitAtWord (Int64
xInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int -> Int64
intToInt64 Int
len) Text
cs
                  in  Text -> Text -> Text
Chunk Text
c Text
h Text -> Text -> PairS Text Text
forall a b. a -> b -> PairS a b
:*: Text
t
    | Bool
otherwise = Text -> Text -> Text
chunk (Array -> Int -> Int -> Text
text Array
arr Int
off Int
y) Text
empty Text -> Text -> PairS Text Text
forall a b. a -> b -> PairS a b
:*:
                  Text -> Text -> Text
chunk (Array -> Int -> Int -> Text
text Array
arr (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y) (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
y)) Text
cs
    where y :: Int
y = Int64 -> Int
int64ToInt Int64
x

-- | /O(n+m)/ Find the first instance of @needle@ (which must be
-- non-'null') in @haystack@.  The first element of the returned tuple
-- is the prefix of @haystack@ before @needle@ is matched.  The second
-- is the remainder of @haystack@, starting with the match.
--
-- Examples:
--
-- > breakOn "::" "a::b::c" ==> ("a", "::b::c")
-- > breakOn "/" "foobar"   ==> ("foobar", "")
--
-- Laws:
--
-- > append prefix match == haystack
-- >   where (prefix, match) = breakOn needle haystack
--
-- If you need to break a string by a substring repeatedly (e.g. you
-- want to break on every instance of a substring), use 'breakOnAll'
-- instead, as it has lower startup overhead.
--
-- This function is strict in its first argument, and lazy in its
-- second.
--
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards /O(n*m)/.
breakOn :: Text -> Text -> (Text, Text)
breakOn :: Text -> Text -> (Text, Text)
breakOn Text
pat Text
src
    | Text -> Bool
null Text
pat  = String -> (Text, Text)
forall a. String -> a
emptyError String
"breakOn"
    | Bool
otherwise = case Text -> Text -> [Int64]
indices Text
pat Text
src of
                    []    -> (Text
src, Text
empty)
                    (Int64
x:[Int64]
_) -> let Text
h :*: Text
t = Int64 -> Text -> PairS Text Text
splitAtWord Int64
x Text
src
                             in  (Text
h, Text
t)

-- | /O(n+m)/ Similar to 'breakOn', but searches from the end of the string.
--
-- The first element of the returned tuple is the prefix of @haystack@
-- up to and including the last match of @needle@.  The second is the
-- remainder of @haystack@, following the match.
--
-- > breakOnEnd "::" "a::b::c" ==> ("a::b::", "c")
breakOnEnd :: Text -> Text -> (Text, Text)
breakOnEnd :: Text -> Text -> (Text, Text)
breakOnEnd Text
pat Text
src = let (Text
a,Text
b) = Text -> Text -> (Text, Text)
breakOn (Text -> Text
reverse Text
pat) (Text -> Text
reverse Text
src)
                   in  (Text -> Text
reverse Text
b, Text -> Text
reverse Text
a)
{-# INLINE breakOnEnd #-}

-- | /O(n+m)/ Find all non-overlapping instances of @needle@ in
-- @haystack@.  Each element of the returned list consists of a pair:
--
-- * The entire string prior to the /k/th match (i.e. the prefix)
--
-- * The /k/th match, followed by the remainder of the string
--
-- Examples:
--
-- > breakOnAll "::" ""
-- > ==> []
-- > breakOnAll "/" "a/b/c/"
-- > ==> [("a", "/b/c/"), ("a/b", "/c/"), ("a/b/c", "/")]
--
-- This function is strict in its first argument, and lazy in its
-- second.
--
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards /O(n*m)/.
--
-- The @needle@ parameter may not be empty.
breakOnAll :: Text              -- ^ @needle@ to search for
           -> Text              -- ^ @haystack@ in which to search
           -> [(Text, Text)]
breakOnAll :: Text -> Text -> [(Text, Text)]
breakOnAll Text
pat Text
src
    | Text -> Bool
null Text
pat  = String -> [(Text, Text)]
forall a. String -> a
emptyError String
"breakOnAll"
    | Bool
otherwise = Int64 -> Text -> Text -> [Int64] -> [(Text, Text)]
go Int64
0 Text
empty Text
src (Text -> Text -> [Int64]
indices Text
pat Text
src)
  where
    go :: Int64 -> Text -> Text -> [Int64] -> [(Text, Text)]
go !Int64
n Text
p Text
s (Int64
x:[Int64]
xs) = let Text
h :*: Text
t = Int64 -> Text -> PairS Text Text
splitAtWord (Int64
xInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int64
n) Text
s
                           h' :: Text
h'      = Text -> Text -> Text
append Text
p Text
h
                       in (Text
h',Text
t) (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: Int64 -> Text -> Text -> [Int64] -> [(Text, Text)]
go Int64
x Text
h' Text
t [Int64]
xs
    go Int64
_  Text
_ Text
_ [Int64]
_      = []

-- | /O(n)/ 'break' is like 'span', but the prefix returned is over
-- elements that fail the predicate @p@.
--
-- >>> T.break (=='c') "180cm"
-- ("180","cm")
break :: (Char -> Bool) -> Text -> (Text, Text)
break :: (Char -> Bool) -> Text -> (Text, Text)
break Char -> Bool
p Text
t0 = Text -> (Text, Text)
break' Text
t0
  where break' :: Text -> (Text, Text)
break' Text
Empty          = (Text
empty, Text
empty)
        break' c :: Text
c@(Chunk Text
t Text
ts) =
          case (Char -> Bool) -> Text -> Maybe Int
T.findIndex Char -> Bool
p Text
t of
            Maybe Int
Nothing      -> let (Text
ts', Text
ts'') = Text -> (Text, Text)
break' Text
ts
                            in (Text -> Text -> Text
Chunk Text
t Text
ts', Text
ts'')
            Just Int
n | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0    -> (Text
Empty, Text
c)
                   | Bool
otherwise -> let (Text
a,Text
b) = Int -> Text -> (Text, Text)
T.splitAt Int
n Text
t
                                  in (Text -> Text -> Text
Chunk Text
a Text
Empty, Text -> Text -> Text
Chunk Text
b Text
ts)

-- | /O(n)/ 'span', applied to a predicate @p@ and text @t@, returns
-- a pair whose first element is the longest prefix (possibly empty)
-- of @t@ of elements that satisfy @p@, and whose second is the
-- remainder of the list.
--
-- >>> T.span (=='0') "000AB"
-- ("000","AB")
span :: (Char -> Bool) -> Text -> (Text, Text)
span :: (Char -> Bool) -> Text -> (Text, Text)
span Char -> Bool
p = (Char -> Bool) -> Text -> (Text, Text)
break (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p)
{-# INLINE span #-}

-- | The 'group' function takes a 'Text' and returns a list of 'Text's
-- such that the concatenation of the result is equal to the argument.
-- Moreover, each sublist in the result contains only equal elements.
-- For example,
--
-- > group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]
--
-- It is a special case of 'groupBy', which allows the programmer to
-- supply their own equality test.
group :: Text -> [Text]
group :: Text -> [Text]
group =  (Char -> Char -> Bool) -> Text -> [Text]
groupBy Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
(==)
{-# INLINE group #-}

-- | The 'groupBy' function is the non-overloaded version of 'group'.
groupBy :: (Char -> Char -> Bool) -> Text -> [Text]
groupBy :: (Char -> Char -> Bool) -> Text -> [Text]
groupBy Char -> Char -> Bool
_  Text
Empty        = []
groupBy Char -> Char -> Bool
eq (Chunk Text
t Text
ts) = Char -> Text -> Text
cons Char
x Text
ys Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: (Char -> Char -> Bool) -> Text -> [Text]
groupBy Char -> Char -> Bool
eq Text
zs
                          where (Text
ys,Text
zs) = (Char -> Bool) -> Text -> (Text, Text)
span (Char -> Char -> Bool
eq Char
x) Text
xs
                                x :: Char
x  = Text -> Char
T.unsafeHead Text
t
                                xs :: Text
xs = Text -> Text -> Text
chunk (Text -> Text
T.unsafeTail Text
t) Text
ts

-- | /O(n)/ Return all initial segments of the given 'Text',
-- shortest first.
inits :: Text -> [Text]
inits :: Text -> [Text]
inits = (Text
Empty Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:) ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
inits'
  where inits' :: Text -> [Text]
inits' Text
Empty        = []
        inits' (Chunk Text
t Text
ts) = (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
L.map (\Text
t' -> Text -> Text -> Text
Chunk Text
t' Text
Empty) ([Text] -> [Text]
forall a. [a] -> [a]
L.tail (Text -> [Text]
T.inits Text
t))
                           [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
L.map (Text -> Text -> Text
Chunk Text
t) (Text -> [Text]
inits' Text
ts)

-- | /O(n)/ Return all final segments of the given 'Text', longest
-- first.
tails :: Text -> [Text]
tails :: Text -> [Text]
tails Text
Empty         = Text
Empty Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: []
tails ts :: Text
ts@(Chunk Text
t Text
ts')
  | Text -> Int
T.length Text
t Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = Text
ts Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Text -> [Text]
tails Text
ts'
  | Bool
otherwise       = Text
ts Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Text -> [Text]
tails (Text -> Text -> Text
Chunk (Text -> Text
T.unsafeTail Text
t) Text
ts')

-- $split
--
-- Splitting functions in this library do not perform character-wise
-- copies to create substrings; they just construct new 'Text's that
-- are slices of the original.

-- | /O(m+n)/ Break a 'Text' into pieces separated by the first 'Text'
-- argument (which cannot be an empty string), consuming the
-- delimiter. An empty delimiter is invalid, and will cause an error
-- to be raised.
--
-- Examples:
--
-- > splitOn "\r\n" "a\r\nb\r\nd\r\ne" == ["a","b","d","e"]
-- > splitOn "aaa"  "aaaXaaaXaaaXaaa"  == ["","X","X","X",""]
-- > splitOn "x"    "x"                == ["",""]
--
-- and
--
-- > intercalate s . splitOn s         == id
-- > splitOn (singleton c)             == split (==c)
--
-- (Note: the string @s@ to split on above cannot be empty.)
--
-- This function is strict in its first argument, and lazy in its
-- second.
--
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards /O(n*m)/.
splitOn :: Text
        -- ^ String to split on. If this string is empty, an error
        -- will occur.
        -> Text
        -- ^ Input text.
        -> [Text]
splitOn :: Text -> Text -> [Text]
splitOn Text
pat Text
src
    | Text -> Bool
null Text
pat        = String -> [Text]
forall a. String -> a
emptyError String
"splitOn"
    | Text -> Bool
isSingleton Text
pat = (Char -> Bool) -> Text -> [Text]
split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Char
head Text
pat) Text
src
    | Bool
otherwise       = Int64 -> [Int64] -> Text -> [Text]
go Int64
0 (Text -> Text -> [Int64]
indices Text
pat Text
src) Text
src
  where
    go :: Int64 -> [Int64] -> Text -> [Text]
go  Int64
_ []     Text
cs = [Text
cs]
    go !Int64
i (Int64
x:[Int64]
xs) Text
cs = let Text
h :*: Text
t = Int64 -> Text -> PairS Text Text
splitAtWord (Int64
xInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
-Int64
i) Text
cs
                      in  Text
h Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Int64 -> [Int64] -> Text -> [Text]
go (Int64
xInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+Int64
l) [Int64]
xs (Int64 -> Text -> Text
dropWords Int64
l Text
t)
    l :: Int64
l = (Int64 -> Text -> Int64) -> Int64 -> Text -> Int64
forall a. (a -> Text -> a) -> a -> Text -> a
foldlChunks (\Int64
a (T.Text Array
_ Int
_ Int
b) -> Int64
a Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int -> Int64
intToInt64 Int
b) Int64
0 Text
pat
{-# INLINE [1] splitOn #-}

{-# RULES
"LAZY TEXT splitOn/singleton -> split/==" [~1] forall c t.
    splitOn (singleton c) t = split (==c) t
  #-}

-- | /O(n)/ Splits a 'Text' into components delimited by separators,
-- where the predicate returns True for a separator element.  The
-- resulting components do not contain the separators.  Two adjacent
-- separators result in an empty component in the output.  eg.
--
-- > split (=='a') "aabbaca" == ["","","bb","c",""]
-- > split (=='a') []        == [""]
split :: (Char -> Bool) -> Text -> [Text]
split :: (Char -> Bool) -> Text -> [Text]
split Char -> Bool
_ Text
Empty = [Text
Empty]
split Char -> Bool
p (Chunk Text
t0 Text
ts0) = [Text] -> [Text] -> Text -> [Text]
comb [] ((Char -> Bool) -> Text -> [Text]
T.split Char -> Bool
p Text
t0) Text
ts0
  where comb :: [Text] -> [Text] -> Text -> [Text]
comb [Text]
acc (Text
s:[]) Text
Empty        = [Text] -> Text
revChunks (Text
sText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
acc) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: []
        comb [Text]
acc (Text
s:[]) (Chunk Text
t Text
ts) = [Text] -> [Text] -> Text -> [Text]
comb (Text
sText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
acc) ((Char -> Bool) -> Text -> [Text]
T.split Char -> Bool
p Text
t) Text
ts
        comb [Text]
acc (Text
s:[Text]
ss) Text
ts           = [Text] -> Text
revChunks (Text
sText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
acc) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text] -> [Text] -> Text -> [Text]
comb [] [Text]
ss Text
ts
        comb [Text]
_   []     Text
_            = String -> [Text]
forall a. String -> a
impossibleError String
"split"
{-# INLINE split #-}

-- | /O(n)/ Splits a 'Text' into components of length @k@.  The last
-- element may be shorter than the other chunks, depending on the
-- length of the input. Examples:
--
-- > chunksOf 3 "foobarbaz"   == ["foo","bar","baz"]
-- > chunksOf 4 "haskell.org" == ["hask","ell.","org"]
chunksOf :: Int64 -> Text -> [Text]
chunksOf :: Int64 -> Text -> [Text]
chunksOf Int64
k = Text -> [Text]
go
  where
    go :: Text -> [Text]
go Text
t = case Int64 -> Text -> (Text, Text)
splitAt Int64
k Text
t of
             (Text
a,Text
b) | Text -> Bool
null Text
a    -> []
                   | Bool
otherwise -> Text
a Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Text -> [Text]
go Text
b
{-# INLINE chunksOf #-}

-- | /O(n)/ Breaks a 'Text' up into a list of 'Text's at
-- newline 'Char's. The resulting strings do not contain newlines.
lines :: Text -> [Text]
lines :: Text -> [Text]
lines Text
Empty = []
lines Text
t = let (Text
l,Text
t') = (Char -> Bool) -> Text -> (Text, Text)
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
(==) Char
'\n') Text
t
          in Text
l Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: if Text -> Bool
null Text
t' then []
                 else Text -> [Text]
lines (Text -> Text
tail Text
t')

-- | /O(n)/ Breaks a 'Text' up into a list of words, delimited by 'Char's
-- representing white space.
words :: Text -> [Text]
words :: Text -> [Text]
words = (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
L.filter (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
null) ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> [Text]
split Char -> Bool
isSpace
{-# INLINE words #-}

-- | /O(n)/ Joins lines, after appending a terminating newline to
-- each.
unlines :: [Text] -> Text
unlines :: [Text] -> Text
unlines = [Text] -> Text
concat ([Text] -> Text) -> ([Text] -> [Text]) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
L.map (Text -> Char -> Text
`snoc` Char
'\n')
{-# INLINE unlines #-}

-- | /O(n)/ Joins words using single space characters.
unwords :: [Text] -> Text
unwords :: [Text] -> Text
unwords = Text -> [Text] -> Text
intercalate (Char -> Text
singleton Char
' ')
{-# INLINE unwords #-}

-- | /O(n)/ The 'isPrefixOf' function takes two 'Text's and returns
-- 'True' iff the first is a prefix of the second.  Subject to fusion.
isPrefixOf :: Text -> Text -> Bool
isPrefixOf :: Text -> Text -> Bool
isPrefixOf Text
Empty Text
_  = Bool
True
isPrefixOf Text
_ Text
Empty  = Bool
False
isPrefixOf (Chunk Text
x Text
xs) (Chunk Text
y Text
ys)
    | Int
lx Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
ly  = Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
y  Bool -> Bool -> Bool
&& Text -> Text -> Bool
isPrefixOf Text
xs Text
ys
    | Int
lx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<  Int
ly  = Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
yh Bool -> Bool -> Bool
&& Text -> Text -> Bool
isPrefixOf Text
xs (Text -> Text -> Text
Chunk Text
yt Text
ys)
    | Bool
otherwise = Text
xh Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
y Bool -> Bool -> Bool
&& Text -> Text -> Bool
isPrefixOf (Text -> Text -> Text
Chunk Text
xt Text
xs) Text
ys
  where (Text
xh,Text
xt) = Int -> Text -> (Text, Text)
T.splitAt Int
ly Text
x
        (Text
yh,Text
yt) = Int -> Text -> (Text, Text)
T.splitAt Int
lx Text
y
        lx :: Int
lx = Text -> Int
T.length Text
x
        ly :: Int
ly = Text -> Int
T.length Text
y
{-# INLINE [1] isPrefixOf #-}

{-# RULES
"LAZY TEXT isPrefixOf -> fused" [~1] forall s t.
    isPrefixOf s t = S.isPrefixOf (stream s) (stream t)
"LAZY TEXT isPrefixOf -> unfused" [1] forall s t.
    S.isPrefixOf (stream s) (stream t) = isPrefixOf s t
  #-}

-- | /O(n)/ The 'isSuffixOf' function takes two 'Text's and returns
-- 'True' iff the first is a suffix of the second.
isSuffixOf :: Text -> Text -> Bool
isSuffixOf :: Text -> Text -> Bool
isSuffixOf Text
x Text
y = Text -> Text
reverse Text
x Text -> Text -> Bool
`isPrefixOf` Text -> Text
reverse Text
y
{-# INLINE isSuffixOf #-}
-- TODO: a better implementation

-- | /O(n+m)/ The 'isInfixOf' function takes two 'Text's and returns
-- 'True' iff the first is contained, wholly and intact, anywhere
-- within the second.
--
-- This function is strict in its first argument, and lazy in its
-- second.
--
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards /O(n*m)/.
isInfixOf :: Text -> Text -> Bool
isInfixOf :: Text -> Text -> Bool
isInfixOf Text
needle Text
haystack
    | Text -> Bool
null Text
needle        = Bool
True
    | Text -> Bool
isSingleton Text
needle = Char -> Stream Char -> Bool
S.elem (Text -> Char
head Text
needle) (Stream Char -> Bool) -> (Text -> Stream Char) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Stream Char
S.stream (Text -> Bool) -> Text -> Bool
forall a b. (a -> b) -> a -> b
$ Text
haystack
    | Bool
otherwise          = Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int64] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
L.null ([Int64] -> Bool) -> (Text -> [Int64]) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Int64]
indices Text
needle (Text -> Bool) -> Text -> Bool
forall a b. (a -> b) -> a -> b
$ Text
haystack
{-# INLINE [1] isInfixOf #-}

{-# RULES
"LAZY TEXT isInfixOf/singleton -> S.elem/S.stream" [~1] forall n h.
    isInfixOf (singleton n) h = S.elem n (S.stream h)
  #-}

-------------------------------------------------------------------------------
-- * View patterns

-- | /O(n)/ Return the suffix of the second string if its prefix
-- matches the entire first string.
--
-- Examples:
--
-- > stripPrefix "foo" "foobar" == Just "bar"
-- > stripPrefix ""    "baz"    == Just "baz"
-- > stripPrefix "foo" "quux"   == Nothing
--
-- This is particularly useful with the @ViewPatterns@ extension to
-- GHC, as follows:
--
-- > {-# LANGUAGE ViewPatterns #-}
-- > import Data.Text.Lazy as T
-- >
-- > fnordLength :: Text -> Int
-- > fnordLength (stripPrefix "fnord" -> Just suf) = T.length suf
-- > fnordLength _                                 = -1
stripPrefix :: Text -> Text -> Maybe Text
stripPrefix :: Text -> Text -> Maybe Text
stripPrefix Text
p Text
t
    | Text -> Bool
null Text
p    = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t
    | Bool
otherwise = case Text -> Text -> Maybe (Text, Text, Text)
commonPrefixes Text
p Text
t of
                    Just (Text
_,Text
c,Text
r) | Text -> Bool
null Text
c -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
r
                    Maybe (Text, Text, Text)
_                     -> Maybe Text
forall a. Maybe a
Nothing

-- | /O(n)/ Find the longest non-empty common prefix of two strings
-- and return it, along with the suffixes of each string at which they
-- no longer match.
--
-- If the strings do not have a common prefix or either one is empty,
-- this function returns 'Nothing'.
--
-- Examples:
--
-- > commonPrefixes "foobar" "fooquux" == Just ("foo","bar","quux")
-- > commonPrefixes "veeble" "fetzer"  == Nothing
-- > commonPrefixes "" "baz"           == Nothing
commonPrefixes :: Text -> Text -> Maybe (Text,Text,Text)
commonPrefixes :: Text -> Text -> Maybe (Text, Text, Text)
commonPrefixes Text
Empty Text
_ = Maybe (Text, Text, Text)
forall a. Maybe a
Nothing
commonPrefixes Text
_ Text
Empty = Maybe (Text, Text, Text)
forall a. Maybe a
Nothing
commonPrefixes Text
a0 Text
b0   = (Text, Text, Text) -> Maybe (Text, Text, Text)
forall a. a -> Maybe a
Just (Text -> Text -> [Text] -> (Text, Text, Text)
go Text
a0 Text
b0 [])
  where
    go :: Text -> Text -> [Text] -> (Text, Text, Text)
go t0 :: Text
t0@(Chunk Text
x Text
xs) t1 :: Text
t1@(Chunk Text
y Text
ys) [Text]
ps
        = case Text -> Text -> Maybe (Text, Text, Text)
T.commonPrefixes Text
x Text
y of
            Just (Text
p,Text
a,Text
b)
              | Text -> Bool
T.null Text
a  -> Text -> Text -> [Text] -> (Text, Text, Text)
go Text
xs (Text -> Text -> Text
chunk Text
b Text
ys) (Text
pText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
ps)
              | Text -> Bool
T.null Text
b  -> Text -> Text -> [Text] -> (Text, Text, Text)
go (Text -> Text -> Text
chunk Text
a Text
xs) Text
ys (Text
pText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
ps)
              | Bool
otherwise -> ([Text] -> Text
fromChunks ([Text] -> [Text]
forall a. [a] -> [a]
L.reverse (Text
pText -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:[Text]
ps)),Text -> Text -> Text
chunk Text
a Text
xs, Text -> Text -> Text
chunk Text
b Text
ys)
            Maybe (Text, Text, Text)
Nothing       -> ([Text] -> Text
fromChunks ([Text] -> [Text]
forall a. [a] -> [a]
L.reverse [Text]
ps),Text
t0,Text
t1)
    go Text
t0 Text
t1 [Text]
ps = ([Text] -> Text
fromChunks ([Text] -> [Text]
forall a. [a] -> [a]
L.reverse [Text]
ps),Text
t0,Text
t1)

-- | /O(n)/ Return the prefix of the second string if its suffix
-- matches the entire first string.
--
-- Examples:
--
-- > stripSuffix "bar" "foobar" == Just "foo"
-- > stripSuffix ""    "baz"    == Just "baz"
-- > stripSuffix "foo" "quux"   == Nothing
--
-- This is particularly useful with the @ViewPatterns@ extension to
-- GHC, as follows:
--
-- > {-# LANGUAGE ViewPatterns #-}
-- > import Data.Text.Lazy as T
-- >
-- > quuxLength :: Text -> Int
-- > quuxLength (stripSuffix "quux" -> Just pre) = T.length pre
-- > quuxLength _                                = -1
stripSuffix :: Text -> Text -> Maybe Text
stripSuffix :: Text -> Text -> Maybe Text
stripSuffix Text
p Text
t = Text -> Text
reverse (Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Text -> Text -> Maybe Text
stripPrefix (Text -> Text
reverse Text
p) (Text -> Text
reverse Text
t)

-- | /O(n)/ 'filter', applied to a predicate and a 'Text',
-- returns a 'Text' containing those characters that satisfy the
-- predicate.
filter :: (Char -> Bool) -> Text -> Text
filter :: (Char -> Bool) -> Text -> Text
filter Char -> Bool
p Text
t = Stream Char -> Text
unstream ((Char -> Bool) -> Stream Char -> Stream Char
S.filter Char -> Bool
p (Text -> Stream Char
stream Text
t))
{-# INLINE filter #-}

-- | /O(n)/ The 'find' function takes a predicate and a 'Text', and
-- returns the first element in matching the predicate, or 'Nothing'
-- if there is no such element. Subject to fusion.
find :: (Char -> Bool) -> Text -> Maybe Char
find :: (Char -> Bool) -> Text -> Maybe Char
find Char -> Bool
p Text
t = (Char -> Bool) -> Stream Char -> Maybe Char
S.findBy Char -> Bool
p (Text -> Stream Char
stream Text
t)
{-# INLINE find #-}

-- | /O(n)/ The 'elem' function takes a character and a 'Text', and
-- returns 'True' if the element is found in the given 'Text', or
-- 'False' otherwise.
elem :: Char -> Text -> Bool
elem :: Char -> Text -> Bool
elem Char
c Text
t = (Char -> Bool) -> Stream Char -> Bool
S.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
c) (Text -> Stream Char
stream Text
t)
{-# INLINE elem #-}

-- | /O(n)/ The 'partition' function takes a predicate and a 'Text',
-- and returns the pair of 'Text's with elements which do and do not
-- satisfy the predicate, respectively; i.e.
--
-- > partition p t == (filter p t, filter (not . p) t)
partition :: (Char -> Bool) -> Text -> (Text, Text)
partition :: (Char -> Bool) -> Text -> (Text, Text)
partition Char -> Bool
p Text
t = ((Char -> Bool) -> Text -> Text
filter Char -> Bool
p Text
t, (Char -> Bool) -> Text -> Text
filter (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) Text
t)
{-# INLINE partition #-}

-- | /O(n)/ 'Text' index (subscript) operator, starting from 0.
-- Subject to fusion.
index :: Text -> Int64 -> Char
index :: Text -> Int64 -> Char
index Text
t Int64
n = Stream Char -> Int64 -> Char
S.index (Text -> Stream Char
stream Text
t) Int64
n
{-# INLINE index #-}

-- | /O(n+m)/ The 'count' function returns the number of times the
-- query string appears in the given 'Text'. An empty query string is
-- invalid, and will cause an error to be raised.
--
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards /O(n*m)/.
count :: Text -> Text -> Int64
count :: Text -> Text -> Int64
count Text
pat Text
src
    | Text -> Bool
null Text
pat        = String -> Int64
forall a. String -> a
emptyError String
"count"
    | Bool
otherwise       = Int64 -> [Int64] -> Int64
forall {t} {a}. Num t => t -> [a] -> t
go Int64
0 (Text -> Text -> [Int64]
indices Text
pat Text
src)
  where go :: t -> [a] -> t
go !t
n []     = t
n
        go !t
n (a
_:[a]
xs) = t -> [a] -> t
go (t
nt -> t -> t
forall a. Num a => a -> a -> a
+t
1) [a]
xs
{-# INLINE [1] count #-}

{-# RULES
"LAZY TEXT count/singleton -> countChar" [~1] forall c t.
    count (singleton c) t = countChar c t
  #-}

-- | /O(n)/ The 'countChar' function returns the number of times the
-- query element appears in the given 'Text'.  Subject to fusion.
countChar :: Char -> Text -> Int64
countChar :: Char -> Text -> Int64
countChar Char
c Text
t = Char -> Stream Char -> Int64
S.countChar Char
c (Text -> Stream Char
stream Text
t)

-- | /O(n)/ 'zip' takes two 'Text's and returns a list of
-- corresponding pairs of bytes. If one input 'Text' is short,
-- excess elements of the longer 'Text' are discarded. This is
-- equivalent to a pair of 'unpack' operations.
zip :: Text -> Text -> [(Char,Char)]
zip :: Text -> Text -> [(Char, Char)]
zip Text
a Text
b = Stream (Char, Char) -> [(Char, Char)]
forall a. Stream a -> [a]
S.unstreamList (Stream (Char, Char) -> [(Char, Char)])
-> Stream (Char, Char) -> [(Char, Char)]
forall a b. (a -> b) -> a -> b
$ (Char -> Char -> (Char, Char))
-> Stream Char -> Stream Char -> Stream (Char, Char)
forall a b. (a -> a -> b) -> Stream a -> Stream a -> Stream b
S.zipWith (,) (Text -> Stream Char
stream Text
a) (Text -> Stream Char
stream Text
b)
{-# INLINE [0] zip #-}

-- | /O(n)/ 'zipWith' generalises 'zip' by zipping with the function
-- given as the first argument, instead of a tupling function.
-- Performs replacement on invalid scalar values.
zipWith :: (Char -> Char -> Char) -> Text -> Text -> Text
zipWith :: (Char -> Char -> Char) -> Text -> Text -> Text
zipWith Char -> Char -> Char
f Text
t1 Text
t2 = Stream Char -> Text
unstream ((Char -> Char -> Char) -> Stream Char -> Stream Char -> Stream Char
forall a b. (a -> a -> b) -> Stream a -> Stream a -> Stream b
S.zipWith Char -> Char -> Char
g (Text -> Stream Char
stream Text
t1) (Text -> Stream Char
stream Text
t2))
    where g :: Char -> Char -> Char
g Char
a Char
b = Char -> Char
safe (Char -> Char -> Char
f Char
a Char
b)
{-# INLINE [0] zipWith #-}

revChunks :: [T.Text] -> Text
revChunks :: [Text] -> Text
revChunks = (Text -> Text -> Text) -> Text -> [Text] -> Text
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
L.foldl' ((Text -> Text -> Text) -> Text -> Text -> Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Text -> Text
chunk) Text
Empty

emptyError :: String -> a
emptyError :: forall a. String -> a
emptyError String
fun = String -> a
forall a. HasCallStack => String -> a
P.error (String
"Data.Text.Lazy." String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
fun String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
": empty input")

impossibleError :: String -> a
impossibleError :: forall a. String -> a
impossibleError String
fun = String -> a
forall a. HasCallStack => String -> a
P.error (String
"Data.Text.Lazy." String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
fun String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
": impossible case")

intToInt64 :: Exts.Int -> Int64
intToInt64 :: Int -> Int64
intToInt64 = Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral

int64ToInt :: Int64 -> Exts.Int
int64ToInt :: Int64 -> Int
int64ToInt = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral