{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

-- |
-- Module        : Data.Text.Lazy.Sized
-- Copyright     : Gautier DI FOLCO
-- License       : BSD2
--
-- Maintainer    : Gautier DI FOLCO <gautier.difolco@gmail.com>
-- Stability     : Unstable
-- Portability   : GHC
--
-- 'Sized' wrappers around `Data.Text.Lazy`
--
-- This module is intended to be imported @qualified@, to avoid name
-- clashes with "Prelude" functions.  eg.
--
-- > import qualified Data.Text.Lazy.Sized as NEL
module Data.Text.Lazy.Sized
  ( -- * Types
    SizedText,
    SizedLazyText,

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

    -- * Basic interface
    cons,
    snoc,
    uncons,
    unsnoc,
    head,
    last,
    tail,
    init,
    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
    replicate,
    cycle,
    iterate,

    -- * Substrings

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

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

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

    -- * Predicates
    isPrefixOf,
    isSuffixOf,
    isInfixOf,

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

    -- * Searching
    filter,
    breakOnAll,
    find,
#if MIN_VERSION_text(1,2,5)
    elem,
#endif
    partition,

    -- * Indexing
    index,
    count,

    -- * Zipping
    zip,
    zipWith,
  )
where

import Data.Bifunctor(bimap, first)
import Data.Proxy
import Data.Int (Int64)
import Data.Sized
import qualified Data.Text.Lazy as T
import Data.Text.Sized (SizedStrictText)
import GHC.Stack
import GHC.TypeNats
import Prelude (Bool (..), Char, Maybe (..),  Ordering, String, fmap, fst, snd, uncurry, ($), (.), fromInteger, fromIntegral)
import GHC.Natural (naturalToInteger)

type SizedLazyText s = Sized s T.Text

type SizedText s = SizedLazyText s

instance SizedSingleton T.Text where
  type SizedSingletonElement T.Text = Char
  sizedSingleton :: Proxy Text -> SizedSingletonElement Text -> Text
sizedSingleton Proxy Text
_ = Char -> Text
SizedSingletonElement Text -> Text
T.singleton

instance SizedFromContainer T.Text where
  calculateSize :: Text -> Int
calculateSize = Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int) -> (Text -> Int64) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Int64
T.length

-- -----------------------------------------------------------------------------

-- * Conversion to/from 'SizedLazyText'

-- | /O(n)/ Convert a 'Sized String' into a 'SizedLazyText'.
-- Performs replacement on invalid scalar values.
pack :: Sized s String -> SizedLazyText s
pack :: Sized s String -> SizedLazyText s
pack = (String -> Text) -> Sized s String -> SizedLazyText s
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized String -> Text
T.pack
{-# INLINE pack #-}

-- | /O(n)/ Convert a 'SizedLazyText s' into a 'Sized s String'.
unpack :: HasCallStack => SizedLazyText s -> Sized s String
unpack :: SizedLazyText s -> Sized s String
unpack = (Text -> String) -> SizedLazyText s -> Sized s String
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized Text -> String
T.unpack
{-# INLINE unpack #-}

-- | /O(c)/ Convert a list of strict 'SizedStrictText's into a lazy 'SizedLazyText'.
fromChunks :: Sized s [SizedStrictText s'] -> SizedLazyText (s <*> s')
fromChunks :: Sized s [SizedStrictText s'] -> SizedLazyText (s <*> s')
fromChunks = ([SizedStrictText s'] -> Text)
-> Sized s [SizedStrictText s'] -> SizedLazyText (s <*> s')
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized (([SizedStrictText s'] -> Text)
 -> Sized s [SizedStrictText s'] -> SizedLazyText (s <*> s'))
-> ([SizedStrictText s'] -> Text)
-> Sized s [SizedStrictText s']
-> SizedLazyText (s <*> s')
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.fromChunks ([Text] -> Text)
-> ([SizedStrictText s'] -> [Text]) -> [SizedStrictText s'] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SizedStrictText s' -> Text) -> [SizedStrictText s'] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SizedStrictText s' -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE fromChunks #-}

-- | /O(n)/ Convert a lazy 'SizedLazyText' into a list of strict 'SizedStrictText's.
toChunks :: SizedLazyText s -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)]
toChunks :: SizedLazyText s
-> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)]
toChunks = (Text -> [SizedStrictText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)]
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> [SizedStrictText (RestrictAtMost s)])
 -> SizedLazyText s
 -> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)])
-> (Text -> [SizedStrictText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedStrictText (RestrictAtMost s)]
forall a b. (a -> b) -> a -> b
$ (Text -> SizedStrictText (RestrictAtMost s))
-> [Text] -> [SizedStrictText (RestrictAtMost s)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedStrictText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized ([Text] -> [SizedStrictText (RestrictAtMost s)])
-> (Text -> [Text]) -> Text -> [SizedStrictText (RestrictAtMost s)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.toChunks
{-# INLINE toChunks #-}

-- | /O(n)/ Convert a lazy 'SizedLazyText' into a strict 'SizedStrictText'.
toStrict :: SizedLazyText s -> SizedStrictText s
toStrict :: SizedLazyText s -> SizedStrictText s
toStrict = (Text -> Text) -> SizedLazyText s -> SizedStrictText s
forall a b s. (a -> b) -> Sized s a -> Sized s b
overSized Text -> Text
T.toStrict
{-# INLINE toStrict #-}

-- | /O(c)/ Convert a strict 'SizedStrictText' into a lazy 'SizedLazyText'.
fromStrict :: SizedStrictText s -> SizedLazyText s
fromStrict :: SizedStrictText s -> SizedLazyText s
fromStrict = (Text -> Text) -> SizedStrictText s -> SizedLazyText s
forall a b s. (a -> b) -> Sized s a -> Sized s b
overSized Text -> Text
T.fromStrict
{-# INLINE fromStrict #-}

-- -----------------------------------------------------------------------------

-- * Basic functions

-- | /O(n)/ Adds a character to the front of a 'SizedLazyText'.  This function
-- is more costly than its 'List' counterpart because it requires
-- copying a new array.  Performs replacement on
-- invalid scalar values.
cons :: Char -> SizedLazyText s -> SizedLazyText (Exactly 1 <+> s)
cons :: Char -> SizedLazyText s -> SizedLazyText (Exactly 1 <+> s)
cons Char
c = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (Exactly 1 <+> s)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (Exactly 1 <+> s))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (Exactly 1 <+> s)
forall a b. (a -> b) -> a -> b
$ Char -> Text -> Text
T.cons Char
c
{-# INLINE cons #-}

infixr 5 `cons`

-- | /O(n)/ Adds a character to the end of a 'SizedLazyText'.  This copies the
-- entire array in the process.
-- Performs replacement on invalid scalar values.
snoc :: SizedLazyText s -> Char -> SizedLazyText (s <+> Exactly 1)
snoc :: SizedLazyText s -> Char -> SizedLazyText (s <+> Exactly 1)
snoc SizedLazyText s
t Char
c = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (s <+> Exactly 1)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized (Text -> Char -> Text
`T.snoc` Char
c) SizedLazyText s
t
{-# INLINE snoc #-}

-- | /O(1)/ Returns the first character of a 'SizedLazyText'.
head :: IsNotEmpty s => SizedLazyText s -> Char
head :: SizedLazyText s -> Char
head = (Char, SizedLazyText (Exactly 1 <+> s)) -> Char
forall a b. (a, b) -> a
fst ((Char, SizedLazyText (Exactly 1 <+> s)) -> Char)
-> (SizedLazyText s -> (Char, SizedLazyText (Exactly 1 <+> s)))
-> SizedLazyText s
-> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> (Char, SizedLazyText (Exactly 1 <+> s))
forall s s'.
(IsNotEmpty s, (Exactly 1 <+> s) ~ s') =>
SizedLazyText s -> (Char, SizedLazyText s')
uncons
{-# INLINE head #-}

-- | /O(1)/ Returns the first character and rest of a 'SizedLazyText'.
uncons :: (IsNotEmpty s, (Exactly 1 <+> s) ~ s') => SizedLazyText s -> (Char, SizedLazyText s')
uncons :: SizedLazyText s -> (Char, SizedLazyText s')
uncons = (Text -> SizedLazyText s')
-> (Char, Text) -> (Char, SizedLazyText s')
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText s'
forall a s. a -> Sized s a
trustedSized ((Char, Text) -> (Char, SizedLazyText s'))
-> (SizedLazyText s -> (Char, Text))
-> SizedLazyText s
-> (Char, SizedLazyText s')
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Maybe (Char, Text)) -> SizedLazyText s -> (Char, Text)
forall a b s. (a -> Maybe b) -> Sized s a -> b
withSized Text -> Maybe (Char, Text)
T.uncons
{-# INLINE uncons #-}

-- | /O(1)/ Returns the last character of a 'SizedLazyText'.
last :: (IsNotEmpty s, (Exactly 1 <+> s) ~ s') => SizedLazyText s -> Char
last :: SizedLazyText s -> Char
last = (SizedLazyText (s <+> Exactly 1), Char) -> Char
forall a b. (a, b) -> b
snd ((SizedLazyText (s <+> Exactly 1), Char) -> Char)
-> (SizedLazyText s -> (SizedLazyText (s <+> Exactly 1), Char))
-> SizedLazyText s
-> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> (SizedLazyText (s <+> Exactly 1), Char)
forall s s'.
(IsNotEmpty s, (s <+> Exactly 1) ~ s') =>
SizedLazyText s -> (SizedLazyText s', Char)
unsnoc
{-# INLINE last #-}

-- | /O(1)/ Returns all characters after the head of a 'SizedLazyText'.
tail :: (IsNotEmpty s, (Exactly 1 <+> s) ~ s') => SizedLazyText s -> SizedLazyText s'
tail :: SizedLazyText s -> SizedLazyText s'
tail = (Char, SizedLazyText s') -> SizedLazyText s'
forall a b. (a, b) -> b
snd ((Char, SizedLazyText s') -> SizedLazyText s')
-> (SizedLazyText s -> (Char, SizedLazyText s'))
-> SizedLazyText s
-> SizedLazyText s'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> (Char, SizedLazyText s')
forall s s'.
(IsNotEmpty s, (Exactly 1 <+> s) ~ s') =>
SizedLazyText s -> (Char, SizedLazyText s')
uncons
{-# INLINE tail #-}

-- | /O(1)/ Returns all but the last character of a 'SizedLazyText'.
init :: (IsNotEmpty s, (s <+> Exactly 1) ~ s') => SizedLazyText s -> SizedLazyText s'
init :: SizedLazyText s -> SizedLazyText s'
init = (SizedLazyText s', Char) -> SizedLazyText s'
forall a b. (a, b) -> a
fst ((SizedLazyText s', Char) -> SizedLazyText s')
-> (SizedLazyText s -> (SizedLazyText s', Char))
-> SizedLazyText s
-> SizedLazyText s'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> (SizedLazyText s', Char)
forall s s'.
(IsNotEmpty s, (s <+> Exactly 1) ~ s') =>
SizedLazyText s -> (SizedLazyText s', Char)
unsnoc
{-# INLINE init #-}

-- | /O(1)/ Returns all but the last character and the last character of a
-- 'SizedLazyText'.
unsnoc :: (IsNotEmpty s, (s <+> Exactly 1) ~ s') => SizedLazyText s -> (SizedLazyText s', Char)
unsnoc :: SizedLazyText s -> (SizedLazyText s', Char)
unsnoc = (Text -> SizedLazyText s')
-> (Text, Char) -> (SizedLazyText s', Char)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Text -> SizedLazyText s'
forall a s. a -> Sized s a
trustedSized ((Text, Char) -> (SizedLazyText s', Char))
-> (SizedLazyText s -> (Text, Char))
-> SizedLazyText s
-> (SizedLazyText s', Char)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Maybe (Text, Char)) -> SizedLazyText s -> (Text, Char)
forall a b s. (a -> Maybe b) -> Sized s a -> b
withSized Text -> Maybe (Text, Char)
T.unsnoc
{-# INLINE unsnoc #-}

-- | /O(n)/ Returns the number of characters in a 'SizedLazyText'.
length :: SizedLazyText s -> Int64
length :: SizedLazyText s -> Int64
length = Text -> Int64
T.length (Text -> Int64)
-> (SizedLazyText s -> Text) -> SizedLazyText s -> Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE length #-}

-- length needs to be phased after the compareN/length rules otherwise
-- it may inline before the rules have an opportunity to fire.

-- | /O(min(n,c))/ Compare the count of characters in a 'SizedLazyText' to a number.
--
-- @
-- 'compareLength' t c = 'P.compare' ('length' t) c
-- @
--
-- 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 :: (KnownNat n, Includes s n) => SizedLazyText s -> Proxy n -> Ordering
compareLength :: SizedLazyText s -> Proxy n -> Ordering
compareLength SizedLazyText s
x = Text -> Int64 -> Ordering
T.compareLength (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
x) (Int64 -> Ordering) -> (Proxy n -> Int64) -> Proxy n -> Ordering
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN
{-# INLINE compareLength #-}

-- -----------------------------------------------------------------------------

-- * Transformations

-- | /O(n)/ 'map' @f@ @t@ is the 'SizedLazyText' obtained by applying @f@ to
-- each element of @t@.
--
-- Example:
--
-- >>> let message = pack "I am not angry. Not at all."
-- >>> T.map (\c -> if c == '.' then '!' else c) message
-- "I am not angry! Not at all!"
--
-- Performs replacement on invalid scalar values.
map :: (Char -> Char) -> SizedLazyText s -> SizedLazyText s
map :: (Char -> Char) -> SizedLazyText s -> SizedLazyText s
map Char -> Char
f = (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text) -> SizedLazyText s -> SizedLazyText s)
-> (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> Text -> Text
T.map Char -> Char
f
{-# INLINE map #-}

-- | /O(n)/ The 'intercalate' function takes a 'SizedLazyText' and a list of
-- 'SizedLazyText's and concatenates the list after interspersing the first
-- argument between each element of the list.
--
-- Example:
--
-- >>> T.intercalate "NI!" ["We", "seek", "the", "Holy", "Grail"]
-- "WeNI!seekNI!theNI!HolyNI!Grail"
intercalate :: T.Text -> Sized s [SizedLazyText s'] -> SizedLazyText (s <*> s')
intercalate :: Text -> Sized s [SizedLazyText s'] -> SizedLazyText (s <*> s')
intercalate Text
e = Text -> SizedLazyText (s <*> s')
forall a s. a -> Sized s a
trustedSized (Text -> SizedLazyText (s <*> s'))
-> (Sized s [SizedLazyText s'] -> Text)
-> Sized s [SizedLazyText s']
-> SizedLazyText (s <*> s')
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
T.intercalate Text
e ([Text] -> Text)
-> (Sized s [SizedLazyText s'] -> [Text])
-> Sized s [SizedLazyText s']
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SizedLazyText s' -> Text) -> [SizedLazyText s'] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized ([SizedLazyText s'] -> [Text])
-> (Sized s [SizedLazyText s'] -> [SizedLazyText s'])
-> Sized s [SizedLazyText s']
-> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sized s [SizedLazyText s'] -> [SizedLazyText s']
forall s a. Sized s a -> a
getSized
{-# INLINE intercalate #-}

-- | /O(n)/ The 'intersperse' function takes a character and places it
-- between the characters of a 'SizedLazyText'.
--
-- Example:
--
-- >>> T.intersperse '.' "SHIELD"
-- "S.H.I.E.L.D"
--
-- Performs replacement on invalid scalar values.
intersperse :: Char -> SizedLazyText s -> SizedLazyText (s <*> Exactly 2 <-> Exactly 1)
intersperse :: Char
-> SizedLazyText s
-> SizedLazyText ((s <*> Exactly 2) <-> Exactly 1)
intersperse Char
c = (Text -> Text)
-> SizedLazyText s
-> SizedLazyText ((s <*> Exactly 2) <-> Exactly 1)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s
 -> SizedLazyText ((s <*> Exactly 2) <-> Exactly 1))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText ((s <*> Exactly 2) <-> Exactly 1)
forall a b. (a -> b) -> a -> b
$ Char -> Text -> Text
T.intersperse Char
c
{-# INLINE intersperse #-}

-- | /O(n)/ Reverse the characters of a string.
--
-- Example:
--
-- >>> T.reverse "desrever"
-- "reversed"
reverse :: HasCallStack => SizedLazyText s -> SizedLazyText s
reverse :: SizedLazyText s -> SizedLazyText s
reverse = (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized Text -> Text
T.reverse
{-# INLINE reverse #-}

-- | /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 ::
  -- | @needle@ to search for.  If this string is empty, an
  -- error will occur.
  SizedLazyText s0 ->
  -- | @replacement@ to replace @needle@ with.
  SizedLazyText s1 ->
  -- | @haystack@ in which to search.
  SizedLazyText s2 ->
  SizedLazyText Unknown
replace :: SizedLazyText s0
-> SizedLazyText s1 -> SizedLazyText s2 -> SizedLazyText Unknown
replace = (Text -> Text -> Text -> Text)
-> SizedLazyText s0
-> SizedLazyText s1
-> SizedLazyText s2
-> SizedLazyText Unknown
forall a b c d s0 s1 s2 s3.
(a -> b -> c -> d)
-> Sized s0 a -> Sized s1 b -> Sized s2 c -> Sized s3 d
trustedChangeOverSized3 Text -> Text -> Text -> Text
T.replace

-- ----------------------------------------------------------------------------

-- ** Case conversions (folds)

-- $case
--
-- When case converting 'SizedLazyText' values, do not use combinators like
-- @map toUpper@ to case convert each character of a string
-- individually, as this gives incorrect results according to the
-- rules of some writing systems.  The whole-string case conversion
-- functions from this module, such as @toUpper@, obey the correct
-- case conversion rules.  As a result, these functions may map one
-- input character to two or three output characters. For examples,
-- see the documentation of each function.
--
-- /Note/: In some languages, case conversion is a locale- and
-- context-dependent operation. The case conversion functions in this
-- module are /not/ locale sensitive. Programs that require locale
-- sensitivity should use appropriate versions of the
-- <http://hackage.haskell.org/package/text-icu-0.6.3.7/docs/Data-Text-ICU.html#g:4 case mapping functions from the text-icu package >.

-- | /O(n)/ Convert a string to folded case.
--
-- This function is mainly useful for performing caseless (also known
-- as 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 \"&#xfb13;\" (men now, U+FB13) is case
-- folded to the sequence \"&#x574;\" (men, U+0574) followed by
-- \"&#x576;\" (now, U+0576), while the Greek \"&#xb5;\" (micro sign,
-- U+00B5) is case folded to \"&#x3bc;\" (small letter mu, U+03BC)
-- instead of itself.
toCaseFold :: SizedLazyText s -> SizedLazyText s
toCaseFold :: SizedLazyText s -> SizedLazyText s
toCaseFold = (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized Text -> Text
T.toCaseFold
{-# INLINE toCaseFold #-}

-- | /O(n)/ Convert a string to lower case, using simple case
-- conversion.
--
-- The result string may be longer than the input string.  For
-- instance, \"&#x130;\" (Latin capital letter I with dot above,
-- U+0130) maps to the sequence \"i\" (Latin small letter i, U+0069)
-- followed by \" &#x307;\" (combining dot above, U+0307).
toLower :: SizedLazyText s -> SizedLazyText s
toLower :: SizedLazyText s -> SizedLazyText s
toLower = (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized Text -> Text
T.toLower
{-# INLINE toLower #-}

-- | /O(n)/ Convert a string to upper case, using simple case
-- conversion.
--
-- The result string may be longer than the input string.  For
-- instance, the German \"&#xdf;\" (eszett, U+00DF) maps to the
-- two-letter sequence \"SS\".
toUpper :: SizedLazyText s -> SizedLazyText s
toUpper :: SizedLazyText s -> SizedLazyText s
toUpper = (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized Text -> Text
T.toUpper
{-# INLINE toUpper #-}

-- | /O(n)/ Convert a string to title case, using simple case
-- conversion.
--
-- 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.
toTitle :: SizedLazyText s -> SizedLazyText s
toTitle :: SizedLazyText s -> SizedLazyText s
toTitle = (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized Text -> Text
T.toTitle
{-# INLINE toTitle #-}

-- | /O(n)/ Left-justify a string to the given length, using the
-- specified fill character on the right.
-- Performs replacement on invalid scalar values.
--
-- Examples:
--
-- >>> justifyLeft 7 'x' "foo"
-- "fooxxxx"
--
-- >>> justifyLeft 3 'x' "foobar"
-- "foobar"
justifyLeft :: KnownNat n => Proxy n -> Char -> SizedLazyText s -> SizedLazyText (AtLeast n) 
justifyLeft :: Proxy n -> Char -> SizedLazyText s -> SizedLazyText (AtLeast n)
justifyLeft Proxy n
p Char
c = (Text -> Text) -> SizedLazyText s -> SizedLazyText (AtLeast n)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text) -> SizedLazyText s -> SizedLazyText (AtLeast n))
-> (Text -> Text) -> SizedLazyText s -> SizedLazyText (AtLeast n)
forall a b. (a -> b) -> a -> b
$ Int64 -> Char -> Text -> Text
T.justifyLeft (Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN Proxy n
p) Char
c
{-# INLINE justifyLeft #-}

-- | /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 :: KnownNat n => Proxy n -> Char -> SizedLazyText s -> SizedLazyText (AtLeast n) 
justifyRight :: Proxy n -> Char -> SizedLazyText s -> SizedLazyText (AtLeast n)
justifyRight Proxy n
p Char
c = (Text -> Text) -> SizedLazyText s -> SizedLazyText (AtLeast n)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text) -> SizedLazyText s -> SizedLazyText (AtLeast n))
-> (Text -> Text) -> SizedLazyText s -> SizedLazyText (AtLeast n)
forall a b. (a -> b) -> a -> b
$ Int64 -> Char -> Text -> Text
T.justifyRight (Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN Proxy n
p) Char
c
{-# 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 :: KnownNat n => Proxy n -> Char -> SizedLazyText s -> SizedLazyText (AtLeast n) 
center :: Proxy n -> Char -> SizedLazyText s -> SizedLazyText (AtLeast n)
center Proxy n
p Char
c = (Text -> Text) -> SizedLazyText s -> SizedLazyText (AtLeast n)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text) -> SizedLazyText s -> SizedLazyText (AtLeast n))
-> (Text -> Text) -> SizedLazyText s -> SizedLazyText (AtLeast n)
forall a b. (a -> b) -> a -> b
$ Int64 -> Char -> Text -> Text
T.center (Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN Proxy n
p) Char
c
{-# INLINE center #-}

-- | /O(n)/ The 'transpose' function transposes the rows and columns
-- of its 'SizedLazyText' argument.  Note that this function uses 'pack',
-- 'unpack', and the list version of transpose, and is thus not very
-- efficient.
--
-- Examples:
--
-- >>> transpose ["green","orange"]
-- ["go","rr","ea","en","ng","e"]
--
-- >>> transpose ["blue","red"]
-- ["br","le","ud","e"]
transpose :: Sized s [SizedLazyText s'] -> Sized s' [SizedLazyText s]
transpose :: Sized s [SizedLazyText s'] -> Sized s' [SizedLazyText s]
transpose = ([SizedLazyText s'] -> [SizedLazyText s])
-> Sized s [SizedLazyText s'] -> Sized s' [SizedLazyText s]
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized (([SizedLazyText s'] -> [SizedLazyText s])
 -> Sized s [SizedLazyText s'] -> Sized s' [SizedLazyText s])
-> ([SizedLazyText s'] -> [SizedLazyText s])
-> Sized s [SizedLazyText s']
-> Sized s' [SizedLazyText s]
forall a b. (a -> b) -> a -> b
$ (Text -> SizedLazyText s) -> [Text] -> [SizedLazyText s]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText s
forall a s. a -> Sized s a
trustedSized ([Text] -> [SizedLazyText s])
-> ([SizedLazyText s'] -> [Text])
-> [SizedLazyText s']
-> [SizedLazyText s]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> [Text]
T.transpose ([Text] -> [Text])
-> ([SizedLazyText s'] -> [Text]) -> [SizedLazyText s'] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SizedLazyText s' -> Text) -> [SizedLazyText s'] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized

-- -----------------------------------------------------------------------------

-- * Reducing 'SizedLazyText's (folds)

-- | /O(n)/ 'foldl', applied to a binary operator, a starting value
-- (typically the left-identity of the operator), and a 'SizedLazyText',
-- reduces the 'SizedLazyText' using the binary operator, from left to right.
foldl :: (a -> Char -> a) -> a -> SizedLazyText s -> a
foldl :: (a -> Char -> a) -> a -> SizedLazyText s -> a
foldl a -> Char -> a
f a
a = (a -> Char -> a) -> a -> Text -> a
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl a -> Char -> a
f a
a (Text -> a) -> (SizedLazyText s -> Text) -> SizedLazyText s -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE foldl #-}

-- | /O(n)/ A strict version of 'foldl'.
foldl' :: (a -> Char -> a) -> a -> SizedLazyText s -> a
foldl' :: (a -> Char -> a) -> a -> SizedLazyText s -> a
foldl' a -> Char -> a
f a
a = (a -> Char -> a) -> a -> Text -> a
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' a -> Char -> a
f a
a (Text -> a) -> (SizedLazyText s -> Text) -> SizedLazyText s -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE foldl' #-}

-- | /O(n)/ A variant of 'foldl' that has no starting value argument.
foldl1 :: IsNotEmpty s => (Char -> Char -> Char) -> SizedLazyText s -> Char
foldl1 :: (Char -> Char -> Char) -> SizedLazyText s -> Char
foldl1 Char -> Char -> Char
f = (Char -> Text -> Char) -> (Char, Text) -> Char
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((Char -> Char -> Char) -> Char -> Text -> Char
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl Char -> Char -> Char
f) ((Char, Text) -> Char)
-> (SizedLazyText s -> (Char, Text)) -> SizedLazyText s -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Sized (Exactly 1 <+> s) Text -> Text)
-> (Char, Sized (Exactly 1 <+> s) Text) -> (Char, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Sized (Exactly 1 <+> s) Text -> Text
forall s a. Sized s a -> a
getSized ((Char, Sized (Exactly 1 <+> s) Text) -> (Char, Text))
-> (SizedLazyText s -> (Char, Sized (Exactly 1 <+> s) Text))
-> SizedLazyText s
-> (Char, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> (Char, Sized (Exactly 1 <+> s) Text)
forall s s'.
(IsNotEmpty s, (Exactly 1 <+> s) ~ s') =>
SizedLazyText s -> (Char, SizedLazyText s')
uncons
{-# INLINE foldl1 #-}

-- | /O(n)/ A strict version of 'foldl1'.
foldl1' :: IsNotEmpty s => (Char -> Char -> Char) -> SizedLazyText s -> Char
foldl1' :: (Char -> Char -> Char) -> SizedLazyText s -> Char
foldl1' Char -> Char -> Char
f = (Char -> Text -> Char) -> (Char, Text) -> Char
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((Char -> Char -> Char) -> Char -> Text -> Char
forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' Char -> Char -> Char
f) ((Char, Text) -> Char)
-> (SizedLazyText s -> (Char, Text)) -> SizedLazyText s -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Sized (Exactly 1 <+> s) Text -> Text)
-> (Char, Sized (Exactly 1 <+> s) Text) -> (Char, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Sized (Exactly 1 <+> s) Text -> Text
forall s a. Sized s a -> a
getSized ((Char, Sized (Exactly 1 <+> s) Text) -> (Char, Text))
-> (SizedLazyText s -> (Char, Sized (Exactly 1 <+> s) Text))
-> SizedLazyText s
-> (Char, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> (Char, Sized (Exactly 1 <+> s) Text)
forall s s'.
(IsNotEmpty s, (Exactly 1 <+> s) ~ s') =>
SizedLazyText s -> (Char, SizedLazyText s')
uncons
{-# INLINE foldl1' #-}

-- | /O(n)/ 'foldr', applied to a binary operator, a starting value
-- (typically the right-identity of the operator), and a 'SizedLazyText',
-- reduces the 'SizedLazyText' using the binary operator, from right to left.
--
-- If the binary operator is strict in its second argument, use 'foldr''
-- instead.
--
-- 'foldr' is lazy like 'Data.List.foldr' for lists: evaluation actually
-- traverses the 'SizedLazyText' from left to right, only as far as it needs to.
-- @
--
-- Searches from left to right with short-circuiting behavior can
-- also be defined using 'foldr' (/e.g./, 'any', 'all', 'find', 'elem').
foldr :: (Char -> a -> a) -> a -> SizedLazyText s -> a
foldr :: (Char -> a -> a) -> a -> SizedLazyText s -> a
foldr Char -> a -> a
f a
a = (Char -> a -> a) -> a -> Text -> a
forall a. (Char -> a -> a) -> a -> Text -> a
T.foldr Char -> a -> a
f a
a (Text -> a) -> (SizedLazyText s -> Text) -> SizedLazyText s -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE foldr #-}

-- | /O(n)/ A variant of 'foldr' that has no starting value argument.
foldr1 :: IsNotEmpty s => (Char -> Char -> Char) -> SizedLazyText s -> Char
foldr1 :: (Char -> Char -> Char) -> SizedLazyText s -> Char
foldr1 Char -> Char -> Char
f = (Char -> Text -> Char) -> (Char, Text) -> Char
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((Char -> Char -> Char) -> Char -> Text -> Char
forall a. (Char -> a -> a) -> a -> Text -> a
T.foldr Char -> Char -> Char
f) ((Char, Text) -> Char)
-> (SizedLazyText s -> (Char, Text)) -> SizedLazyText s -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Sized (Exactly 1 <+> s) Text -> Text)
-> (Char, Sized (Exactly 1 <+> s) Text) -> (Char, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Sized (Exactly 1 <+> s) Text -> Text
forall s a. Sized s a -> a
getSized ((Char, Sized (Exactly 1 <+> s) Text) -> (Char, Text))
-> (SizedLazyText s -> (Char, Sized (Exactly 1 <+> s) Text))
-> SizedLazyText s
-> (Char, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> (Char, Sized (Exactly 1 <+> s) Text)
forall s s'.
(IsNotEmpty s, (Exactly 1 <+> s) ~ s') =>
SizedLazyText s -> (Char, SizedLazyText s')
uncons
{-# INLINE foldr1 #-}

-- -----------------------------------------------------------------------------

-- ** Special folds

-- | /O(n)/ Concatenate a list of 'SizedLazyText's.
concat :: Sized s [SizedLazyText s'] -> SizedLazyText (s <*> s')
concat :: Sized s [SizedLazyText s'] -> SizedLazyText (s <*> s')
concat = ([SizedLazyText s'] -> Text)
-> Sized s [SizedLazyText s'] -> SizedLazyText (s <*> s')
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized (([SizedLazyText s'] -> Text)
 -> Sized s [SizedLazyText s'] -> SizedLazyText (s <*> s'))
-> ([SizedLazyText s'] -> Text)
-> Sized s [SizedLazyText s']
-> SizedLazyText (s <*> s')
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat ([Text] -> Text)
-> ([SizedLazyText s'] -> [Text]) -> [SizedLazyText s'] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SizedLazyText s' -> Text) -> [SizedLazyText s'] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized

-- | /O(n)/ Map a function over a 'SizedLazyText' that results in a 'SizedLazyText', and
-- concatenate the results.
concatMap :: (Char -> SizedLazyText s') -> SizedLazyText s -> SizedLazyText (s <*> s')
concatMap :: (Char -> SizedLazyText s')
-> SizedLazyText s -> SizedLazyText (s <*> s')
concatMap Char -> SizedLazyText s'
f = (Text -> Text) -> SizedLazyText s -> SizedLazyText (s <*> s')
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text) -> SizedLazyText s -> SizedLazyText (s <*> s'))
-> (Text -> Text) -> SizedLazyText s -> SizedLazyText (s <*> s')
forall a b. (a -> b) -> a -> b
$ (Char -> Text) -> Text -> Text
T.concatMap ((Char -> Text) -> Text -> Text) -> (Char -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized (SizedLazyText s' -> Text)
-> (Char -> SizedLazyText s') -> Char -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> SizedLazyText s'
f
{-# INLINE concatMap #-}

-- | /O(n)/ 'any' @p@ @t@ determines whether any character in the
-- 'SizedLazyText' @t@ satisfies the predicate @p@.
any :: (Char -> Bool) -> SizedLazyText s -> Bool
any :: (Char -> Bool) -> SizedLazyText s -> Bool
any Char -> Bool
p = (Char -> Bool) -> Text -> Bool
T.any Char -> Bool
p (Text -> Bool)
-> (SizedLazyText s -> Text) -> SizedLazyText s -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE any #-}

-- | /O(n)/ 'all' @p@ @t@ determines whether all characters in the
-- 'SizedLazyText' @t@ satisfy the predicate @p@.
all :: (Char -> Bool) -> SizedLazyText s -> Bool
all :: (Char -> Bool) -> SizedLazyText s -> Bool
all Char -> Bool
p = (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
p (Text -> Bool)
-> (SizedLazyText s -> Text) -> SizedLazyText s -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE all #-}

-- | /O(n)/ 'maximum' returns the maximum value from a 'SizedLazyText'.
maximum :: IsNotEmpty s => SizedLazyText s -> Char
maximum :: SizedLazyText s -> Char
maximum = Text -> Char
T.maximum (Text -> Char)
-> (SizedLazyText s -> Text) -> SizedLazyText s -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE maximum #-}

-- | /O(n)/ 'minimum' returns the minimum value from a 'SizedLazyText'.
minimum :: IsNotEmpty s => SizedLazyText s -> Char
minimum :: SizedLazyText s -> Char
minimum = Text -> Char
T.minimum (Text -> Char)
-> (SizedLazyText s -> Text) -> SizedLazyText s -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE minimum #-}

-- -----------------------------------------------------------------------------

-- * Building 'SizedLazyText's

-- | /O(n)/ 'scanl' is similar to 'foldl', but returns a list of
-- successive reduced values from the left.
-- Performs replacement on invalid scalar values.
--
-- > scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
--
-- __Properties__
--
-- @'head' ('scanl' f z xs) = z@
--
-- @'last' ('scanl' f z xs) = 'foldl' f z xs@
scanl :: (Char -> Char -> Char) -> Char -> SizedLazyText s -> SizedLazyText s
scanl :: (Char -> Char -> Char)
-> Char -> SizedLazyText s -> SizedLazyText s
scanl Char -> Char -> Char
f Char
s = (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text) -> SizedLazyText s -> SizedLazyText s)
-> (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b. (a -> b) -> a -> b
$ (Char -> Char -> Char) -> Char -> Text -> Text
T.scanl Char -> Char -> Char
f Char
s
{-# 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 ::  IsNotEmpty s =>(Char -> Char -> Char) -> SizedLazyText s -> SizedLazyText s
scanl1 :: (Char -> Char -> Char) -> SizedLazyText s -> SizedLazyText s
scanl1 Char -> Char -> Char
f = (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text) -> SizedLazyText s -> SizedLazyText s)
-> (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b. (a -> b) -> a -> b
$ (Char -> Char -> Char) -> Text -> Text
T.scanl1 Char -> Char -> Char
f
{-# 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 -> SizedLazyText s -> SizedLazyText s
scanr :: (Char -> Char -> Char)
-> Char -> SizedLazyText s -> SizedLazyText s
scanr Char -> Char -> Char
f Char
s = (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text) -> SizedLazyText s -> SizedLazyText s)
-> (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b. (a -> b) -> a -> b
$ (Char -> Char -> Char) -> Char -> Text -> Text
T.scanr Char -> Char -> Char
f Char
s
{-# INLINE scanr #-}

-- | /O(n)/ 'scanr1' is a variant of 'scanr' that has no starting
-- value argument. Performs replacement on invalid scalar values.
scanr1 :: IsNotEmpty s => (Char -> Char -> Char) -> SizedLazyText s -> SizedLazyText s
scanr1 :: (Char -> Char -> Char) -> SizedLazyText s -> SizedLazyText s
scanr1 Char -> Char -> Char
f = (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text) -> SizedLazyText s -> SizedLazyText s)
-> (Text -> Text) -> SizedLazyText s -> SizedLazyText s
forall a b. (a -> b) -> a -> b
$ (Char -> Char -> Char) -> Text -> Text
T.scanr1 Char -> Char -> Char
f
{-# INLINE scanr1 #-}

-- | /O(n)/ Like a combination of 'map' and 'foldl''. Applies a
-- function to each element of a 'SizedLazyText', passing an accumulating
-- parameter from left to right, and returns a final 'SizedLazyText'.  Performs
-- replacement on invalid scalar values.
mapAccumL :: forall a s. (a -> Char -> (a, Char)) -> a -> SizedLazyText s -> (a, SizedLazyText s)
mapAccumL :: (a -> Char -> (a, Char))
-> a -> SizedLazyText s -> (a, SizedLazyText s)
mapAccumL a -> Char -> (a, Char)
f a
s = (Text -> SizedLazyText s) -> (a, Text) -> (a, SizedLazyText s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText s
forall a s. a -> Sized s a
trustedSized ((a, Text) -> (a, SizedLazyText s))
-> (SizedLazyText s -> (a, Text))
-> SizedLazyText s
-> (a, SizedLazyText s)
forall b c a. (b -> c) -> (a -> b) -> a -> 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
s (Text -> (a, Text))
-> (SizedLazyText s -> Text) -> SizedLazyText s -> (a, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE mapAccumL #-}

-- | The 'mapAccumR' function behaves like a combination of 'map' and
-- a strict 'foldr'; it applies a function to each element of a
-- 'SizedLazyText', passing an accumulating parameter from right to left, and
-- returning a final value of this accumulator together with the new
-- 'SizedLazyText'.
-- Performs replacement on invalid scalar values.
mapAccumR :: forall a s. (a -> Char -> (a, Char)) -> a -> SizedLazyText s -> (a, SizedLazyText s)
mapAccumR :: (a -> Char -> (a, Char))
-> a -> SizedLazyText s -> (a, SizedLazyText s)
mapAccumR a -> Char -> (a, Char)
f a
s = (Text -> SizedLazyText s) -> (a, Text) -> (a, SizedLazyText s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText s
forall a s. a -> Sized s a
trustedSized ((a, Text) -> (a, SizedLazyText s))
-> (SizedLazyText s -> (a, Text))
-> SizedLazyText s
-> (a, SizedLazyText s)
forall b c a. (b -> c) -> (a -> b) -> a -> 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
s (Text -> (a, Text))
-> (SizedLazyText s -> Text) -> SizedLazyText s -> (a, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE mapAccumR #-}

-- -----------------------------------------------------------------------------

-- ** Generating and unfolding 'SizedLazyText's

-- | /O(n*m)/ 'replicate' @n@ @t@ is a 'SizedLazyText' consisting of the input
-- @t@ repeated @n@ times, @n@ should be strictly positive.
replicate :: KnownNat n => Proxy n -> SizedLazyText s -> SizedLazyText (s <*> Exactly n)
replicate :: Proxy n -> SizedLazyText s -> SizedLazyText (s <*> Exactly n)
replicate Proxy n
n = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (s <*> Exactly n)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (s <*> Exactly n))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (s <*> Exactly n)
forall a b. (a -> b) -> a -> b
$ Int64 -> Text -> Text
T.replicate (Int64 -> Text -> Text) -> Int64 -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN Proxy n
n
{-# INLINE replicate #-}

-- | 'cycle' ties a finite, 'SizedLazyText' into a circular one, or
-- equivalently, the infinite repetition of the original 'SizedLazyText'.
cycle :: SizedLazyText s -> SizedLazyText (AtLeast 0)
cycle :: SizedLazyText s -> SizedLazyText (AtLeast 0)
cycle = (Text -> Text) -> SizedLazyText s -> SizedLazyText (AtLeast 0)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized Text -> Text
T.cycle
{-# INLINE cycle #-}

-- | @'iterate' f x@ returns an infinite 'SizedLazyText' of repeated applications
-- of @f@ to @x@:
--
-- > iterate f x == [x, f x, f (f x), ...]
iterate :: (Char -> Char) -> Char -> SizedLazyText (AtLeast 0)
iterate :: (Char -> Char) -> Char -> SizedLazyText (AtLeast 0)
iterate Char -> Char
f = Text -> SizedLazyText (AtLeast 0)
forall a s. a -> Sized s a
trustedSized (Text -> SizedLazyText (AtLeast 0))
-> (Char -> Text) -> Char -> SizedLazyText (AtLeast 0)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char) -> Char -> Text
T.iterate Char -> Char
f
{-# INLINE iterate #-}

-- -----------------------------------------------------------------------------

-- * Substrings

-- | /O(n)/ 'take' @n@, applied to a 'SizedLazyText', returns the prefix of the
-- 'Text' of length @n@, or the 'Text' itself if @n@ is greater than
-- the length of the SizedLazyText.
take :: (KnownNat n, Includes s n) => Proxy n -> SizedLazyText s -> SizedLazyText (AtMost n)
take :: Proxy n -> SizedLazyText s -> SizedLazyText (AtMost n)
take Proxy n
n = (Text -> Text) -> SizedLazyText s -> SizedLazyText (AtMost n)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text) -> SizedLazyText s -> SizedLazyText (AtMost n))
-> (Text -> Text) -> SizedLazyText s -> SizedLazyText (AtMost n)
forall a b. (a -> b) -> a -> b
$ Int64 -> Text -> Text
T.take (Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN Proxy n
n)
{-# INLINE take #-}

-- | /O(n)/ 'takeEnd' @n@ @t@ returns the suffix remaining after
-- taking @n@ characters from the end of @t@.
--
-- Examples:
--
-- >>> takeEnd 3 "foobar"
-- "bar"
takeEnd :: (KnownNat n, Includes s n) => Proxy n -> SizedLazyText s -> SizedLazyText (AtMost n)
takeEnd :: Proxy n -> SizedLazyText s -> SizedLazyText (AtMost n)
takeEnd Proxy n
n = (Text -> Text) -> SizedLazyText s -> SizedLazyText (AtMost n)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text) -> SizedLazyText s -> SizedLazyText (AtMost n))
-> (Text -> Text) -> SizedLazyText s -> SizedLazyText (AtMost n)
forall a b. (a -> b) -> a -> b
$ Int64 -> Text -> Text
T.takeEnd (Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN Proxy n
n)
{-# INLINE takeEnd #-}

-- | /O(n)/ 'drop' @n@, applied to a 'SizedLazyText', returns the suffix of the
-- 'Text' after the first @n@ characters, or the empty 'Text' if @n@
-- is greater than the length of the 'SizedLazyText'.
drop :: (KnownNat n, Includes s n) => Proxy n -> SizedLazyText s -> SizedLazyText (s <-> Exactly n) 
drop :: Proxy n -> SizedLazyText s -> SizedLazyText (s <-> Exactly n)
drop Proxy n
n = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (s <-> Exactly n)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (s <-> Exactly n))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (s <-> Exactly n)
forall a b. (a -> b) -> a -> b
$ Int64 -> Text -> Text
T.drop (Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN Proxy n
n)
{-# INLINE drop #-}

-- | /O(n)/ 'dropEnd' @n@ @t@ returns the prefix remaining after
-- dropping @n@ characters from the end of @t@.
--
-- Examples:
--
-- >>> dropEnd 3 "foobar"
-- "foo"
dropEnd :: (KnownNat n, Includes s n) => Proxy n -> SizedLazyText s -> SizedLazyText (s <-> Exactly n) 
dropEnd :: Proxy n -> SizedLazyText s -> SizedLazyText (s <-> Exactly n)
dropEnd Proxy n
n = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (s <-> Exactly n)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (s <-> Exactly n))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (s <-> Exactly n)
forall a b. (a -> b) -> a -> b
$ Int64 -> Text -> Text
T.dropEnd (Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN Proxy n
n)
{-# INLINE dropEnd #-}

-- | /O(n)/ 'takeWhile', applied to a predicate @p@ and a 'SizedLazyText',
-- returns the longest prefix (possibly empty) of elements that
-- satisfy @p@.
takeWhile :: (Char -> Bool) -> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
takeWhile :: (Char -> Bool)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
takeWhile Char -> Bool
p = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (RestrictAtMost s))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (RestrictAtMost s)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.takeWhile Char -> Bool
p
{-# INLINE takeWhile #-}

-- | /O(n)/ 'takeWhileEnd', applied to a predicate @p@ and a 'SizedLazyText',
-- returns the longest suffix (possibly empty) of elements that
-- satisfy @p@.
-- Examples:
--
-- >>> takeWhileEnd (=='o') "foo"
-- "oo"
takeWhileEnd :: (Char -> Bool) -> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
takeWhileEnd :: (Char -> Bool)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
takeWhileEnd Char -> Bool
p = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (RestrictAtMost s))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (RestrictAtMost s)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.takeWhileEnd Char -> Bool
p
{-# INLINE takeWhileEnd #-}

-- | /O(n)/ 'dropWhile' @p@ @t@ returns the suffix remaining after
-- 'takeWhile' @p@ @t@.
dropWhile :: (Char -> Bool) -> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
dropWhile :: (Char -> Bool)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
dropWhile Char -> Bool
p = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (RestrictAtMost s))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (RestrictAtMost s)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.dropWhile Char -> Bool
p
{-# INLINE dropWhile #-}

-- | /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) -> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
dropWhileEnd :: (Char -> Bool)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
dropWhileEnd Char -> Bool
p = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (RestrictAtMost s))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (RestrictAtMost s)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.dropWhileEnd Char -> Bool
p
{-# 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) -> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
dropAround :: (Char -> Bool)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
dropAround Char -> Bool
p = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (RestrictAtMost s))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (RestrictAtMost s)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.dropAround Char -> Bool
p
{-# INLINE dropAround #-}

-- | /O(n)/ Remove leading white space from a string.  Equivalent to:
--
-- > dropWhile isSpace
stripStart :: SizedLazyText s -> SizedLazyText (RestrictAtMost s)
stripStart :: SizedLazyText s -> SizedLazyText (RestrictAtMost s)
stripStart = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (RestrictAtMost s))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (RestrictAtMost s)
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.stripStart
{-# INLINE stripStart #-}

-- | /O(n)/ Remove trailing white space from a string.  Equivalent to:
--
-- > dropWhileEnd isSpace
stripEnd :: SizedLazyText s -> SizedLazyText (RestrictAtMost s)
stripEnd :: SizedLazyText s -> SizedLazyText (RestrictAtMost s)
stripEnd = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (RestrictAtMost s))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (RestrictAtMost s)
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.stripEnd
{-# INLINE stripEnd #-}

-- | /O(n)/ Remove leading and trailing white space from a string.
-- Equivalent to:
--
-- > dropAround isSpace
strip :: SizedLazyText s -> SizedLazyText (RestrictAtMost s)
strip :: SizedLazyText s -> SizedLazyText (RestrictAtMost s)
strip = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (RestrictAtMost s))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (RestrictAtMost s)
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip
{-# INLINE 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 :: (KnownNat n, Includes s n) => Proxy n -> SizedLazyText s -> (SizedLazyText (RestrictAtMost s), SizedLazyText (RestrictAtMost s)) 
splitAt :: Proxy n
-> SizedLazyText s
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
splitAt Proxy n
n = (Text -> SizedLazyText (RestrictAtMost s))
-> (Text -> SizedLazyText (RestrictAtMost s))
-> (Text, Text)
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized ((Text, Text)
 -> (SizedLazyText (RestrictAtMost s),
     SizedLazyText (RestrictAtMost s)))
-> (SizedLazyText s -> (Text, Text))
-> SizedLazyText s
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Text -> (Text, Text)
T.splitAt (Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN Proxy n
n) (Text -> (Text, Text))
-> (SizedLazyText s -> Text) -> SizedLazyText s -> (Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE splitAt #-}

-- | /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 text.
--
-- >>> T.span (=='0') "000AB"
-- ("000","AB")
span :: (Char -> Bool) -> SizedLazyText s -> (SizedLazyText (RestrictAtMost s), SizedLazyText (RestrictAtMost s)) 
span :: (Char -> Bool)
-> SizedLazyText s
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
span Char -> Bool
p = (Text -> SizedLazyText (RestrictAtMost s))
-> (Text -> SizedLazyText (RestrictAtMost s))
-> (Text, Text)
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized ((Text, Text)
 -> (SizedLazyText (RestrictAtMost s),
     SizedLazyText (RestrictAtMost s)))
-> (SizedLazyText s -> (Text, Text))
-> SizedLazyText s
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> (Text, Text)
T.span Char -> Bool
p (Text -> (Text, Text))
-> (SizedLazyText s -> Text) -> SizedLazyText s -> (Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE span #-}

-- | /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) -> SizedLazyText s -> (SizedLazyText (RestrictAtMost s), SizedLazyText (RestrictAtMost s)) 
break :: (Char -> Bool)
-> SizedLazyText s
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
break Char -> Bool
p = (Text -> SizedLazyText (RestrictAtMost s))
-> (Text -> SizedLazyText (RestrictAtMost s))
-> (Text, Text)
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized ((Text, Text)
 -> (SizedLazyText (RestrictAtMost s),
     SizedLazyText (RestrictAtMost s)))
-> (SizedLazyText s -> (Text, Text))
-> SizedLazyText s
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> (Text, Text)
T.break Char -> Bool
p (Text -> (Text, Text))
-> (SizedLazyText s -> Text) -> SizedLazyText s -> (Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE break #-}

-- | /O(n)/ Group characters in a string according to a predicate.
groupBy :: (Char -> Char -> Bool) -> SizedLazyText s -> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
groupBy :: (Char -> Char -> Bool)
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
groupBy Char -> Char -> Bool
p = (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> [SizedLazyText (RestrictAtMost s)])
 -> SizedLazyText s
 -> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)])
-> (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
forall a b. (a -> b) -> a -> b
$ (Text -> SizedLazyText (RestrictAtMost s))
-> [Text] -> [SizedLazyText (RestrictAtMost s)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized  ([Text] -> [SizedLazyText (RestrictAtMost s)])
-> (Text -> [Text]) -> Text -> [SizedLazyText (RestrictAtMost s)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char -> Bool) -> Text -> [Text]
T.groupBy Char -> Char -> Bool
p
{-# INLINE groupBy #-}

-- | /O(n)/ Group characters in a string by equality.
group :: SizedLazyText s -> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
group :: SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
group = (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> [SizedLazyText (RestrictAtMost s)])
 -> SizedLazyText s
 -> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)])
-> (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
forall a b. (a -> b) -> a -> b
$ (Text -> SizedLazyText (RestrictAtMost s))
-> [Text] -> [SizedLazyText (RestrictAtMost s)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized  ([Text] -> [SizedLazyText (RestrictAtMost s)])
-> (Text -> [Text]) -> Text -> [SizedLazyText (RestrictAtMost s)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.group
{-# INLINE group #-}

-- | /O(n)/ Return all initial segments of the given 'SizedLazyText', shortest
-- first.
inits :: SizedLazyText s -> Sized (s <+> Exactly 1) [SizedLazyText (RestrictAtMost s)]
inits :: SizedLazyText s
-> Sized (s <+> Exactly 1) [SizedLazyText (RestrictAtMost s)]
inits = (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (s <+> Exactly 1) [SizedLazyText (RestrictAtMost s)]
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> [SizedLazyText (RestrictAtMost s)])
 -> SizedLazyText s
 -> Sized (s <+> Exactly 1) [SizedLazyText (RestrictAtMost s)])
-> (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (s <+> Exactly 1) [SizedLazyText (RestrictAtMost s)]
forall a b. (a -> b) -> a -> b
$ (Text -> SizedLazyText (RestrictAtMost s))
-> [Text] -> [SizedLazyText (RestrictAtMost s)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized  ([Text] -> [SizedLazyText (RestrictAtMost s)])
-> (Text -> [Text]) -> Text -> [SizedLazyText (RestrictAtMost s)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.inits
{-# INLINE inits #-}

-- | /O(n)/ Return all final segments of the given 'SizedLazyText', longest
-- first.
tails :: SizedLazyText s -> Sized (s <+> Exactly 1) [SizedLazyText (RestrictAtMost s)]
tails :: SizedLazyText s
-> Sized (s <+> Exactly 1) [SizedLazyText (RestrictAtMost s)]
tails = (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (s <+> Exactly 1) [SizedLazyText (RestrictAtMost s)]
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> [SizedLazyText (RestrictAtMost s)])
 -> SizedLazyText s
 -> Sized (s <+> Exactly 1) [SizedLazyText (RestrictAtMost s)])
-> (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (s <+> Exactly 1) [SizedLazyText (RestrictAtMost s)]
forall a b. (a -> b) -> a -> b
$ (Text -> SizedLazyText (RestrictAtMost s))
-> [Text] -> [SizedLazyText (RestrictAtMost s)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized   ([Text] -> [SizedLazyText (RestrictAtMost s)])
-> (Text -> [Text]) -> Text -> [SizedLazyText (RestrictAtMost s)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.tails
{-# INLINE tails #-}

-- $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 'SizedLazyText' into pieces separated by the first 'Text'
-- argument (which cannot be empty), 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.)
--
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards /O(n*m)/.
splitOn ::
  -- | String to split on. If this string is empty, an error
  -- will occur.
  SizedLazyText s ->
  -- | Input text.
  SizedLazyText s' ->
  Sized (RestrictAtMost s') [SizedLazyText (RestrictAtMost s')]
splitOn :: SizedLazyText s
-> SizedLazyText s'
-> Sized (RestrictAtMost s') [SizedLazyText (RestrictAtMost s')]
splitOn = (Text -> Text -> [SizedLazyText (RestrictAtMost s')])
-> SizedLazyText s
-> SizedLazyText s'
-> Sized (RestrictAtMost s') [SizedLazyText (RestrictAtMost s')]
forall a b c s0 s1 s2.
(a -> b -> c) -> Sized s0 a -> Sized s1 b -> Sized s2 c
trustedChangeOverSized2 ((Text -> Text -> [SizedLazyText (RestrictAtMost s')])
 -> SizedLazyText s
 -> SizedLazyText s'
 -> Sized (RestrictAtMost s') [SizedLazyText (RestrictAtMost s')])
-> (Text -> Text -> [SizedLazyText (RestrictAtMost s')])
-> SizedLazyText s
-> SizedLazyText s'
-> Sized (RestrictAtMost s') [SizedLazyText (RestrictAtMost s')]
forall a b. (a -> b) -> a -> b
$ \Text
x Text
y -> (Text -> SizedLazyText (RestrictAtMost s'))
-> [Text] -> [SizedLazyText (RestrictAtMost s')]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText (RestrictAtMost s')
forall a s. a -> Sized s a
trustedSized ([Text] -> [SizedLazyText (RestrictAtMost s')])
-> [Text] -> [SizedLazyText (RestrictAtMost s')]
forall a b. (a -> b) -> a -> b
$ Text -> Text -> [Text]
T.splitOn Text
x Text
y
{-# INLINE splitOn #-}

-- | /O(n)/ Splits a 'SizedLazyText' 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) -> SizedLazyText s -> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
split :: (Char -> Bool)
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
split Char -> Bool
p = (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized  ((Text -> [SizedLazyText (RestrictAtMost s)])
 -> SizedLazyText s
 -> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)])
-> (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
forall a b. (a -> b) -> a -> b
$ (Text -> SizedLazyText (RestrictAtMost s))
-> [Text] -> [SizedLazyText (RestrictAtMost s)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized   ([Text] -> [SizedLazyText (RestrictAtMost s)])
-> (Text -> [Text]) -> Text -> [SizedLazyText (RestrictAtMost s)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> [Text]
T.split Char -> Bool
p
{-# INLINE split #-}

-- | /O(n)/ Splits a 'SizedLazyText' 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 :: (KnownNat n, Includes s n) => Proxy n -> SizedLazyText s -> Sized (AtMost d) [SizedLazyText (RestrictAtMost s)]
chunksOf :: Proxy n
-> SizedLazyText s
-> Sized (AtMost d) [SizedLazyText (RestrictAtMost s)]
chunksOf Proxy n
p = (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (AtMost d) [SizedLazyText (RestrictAtMost s)]
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized  ((Text -> [SizedLazyText (RestrictAtMost s)])
 -> SizedLazyText s
 -> Sized (AtMost d) [SizedLazyText (RestrictAtMost s)])
-> (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (AtMost d) [SizedLazyText (RestrictAtMost s)]
forall a b. (a -> b) -> a -> b
$ (Text -> SizedLazyText (RestrictAtMost s))
-> [Text] -> [SizedLazyText (RestrictAtMost s)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized  ([Text] -> [SizedLazyText (RestrictAtMost s)])
-> (Text -> [Text]) -> Text -> [SizedLazyText (RestrictAtMost s)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Text -> [Text]
T.chunksOf (Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN Proxy n
p)
{-# INLINE chunksOf #-}

-- ----------------------------------------------------------------------------

-- * Searching

-------------------------------------------------------------------------------

-- ** Searching with a predicate

-- | /O(n)/ The 'elem' function takes a character and a 'SizedLazyText', and
-- returns 'True' if the element is found in the given 'SizedLazyText', or
-- 'False' otherwise.
#if MIN_VERSION_text(1,2,5)
elem :: Char -> SizedLazyText s -> Bool
elem p = T.elem p . getSized
{-# INLINE elem #-}
#endif

-- | /O(n)/ The 'find' function takes a predicate and a 'SizedLazyText', and
-- returns the first element matching the predicate, or 'Nothing' if
-- there is no such element.
find :: (Char -> Bool) -> SizedLazyText s -> Maybe Char
find :: (Char -> Bool) -> SizedLazyText s -> Maybe Char
find Char -> Bool
p = (Char -> Bool) -> Text -> Maybe Char
T.find Char -> Bool
p (Text -> Maybe Char)
-> (SizedLazyText s -> Text) -> SizedLazyText s -> Maybe Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE find #-}

-- | /O(n)/ The 'partition' function takes a predicate and a 'SizedLazyText',
-- 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) -> SizedLazyText s -> (SizedLazyText (RestrictAtMost s), SizedLazyText (RestrictAtMost s))
partition :: (Char -> Bool)
-> SizedLazyText s
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
partition Char -> Bool
p = (Text -> SizedLazyText (RestrictAtMost s))
-> (Text -> SizedLazyText (RestrictAtMost s))
-> (Text, Text)
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized ((Text, Text)
 -> (SizedLazyText (RestrictAtMost s),
     SizedLazyText (RestrictAtMost s)))
-> (SizedLazyText s -> (Text, Text))
-> SizedLazyText s
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> (Text, Text)
T.partition Char -> Bool
p (Text -> (Text, Text))
-> (SizedLazyText s -> Text) -> SizedLazyText s -> (Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE partition #-}

-- | /O(n)/ 'filter', applied to a predicate and a 'SizedLazyText',
-- returns a 'Text' containing those characters that satisfy the
-- predicate.
filter :: (Char -> Bool) -> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
filter :: (Char -> Bool)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
filter Char -> Bool
p = (Text -> Text)
-> SizedLazyText s -> SizedLazyText (RestrictAtMost s)
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> Text)
 -> SizedLazyText s -> SizedLazyText (RestrictAtMost s))
-> (Text -> Text)
-> SizedLazyText s
-> SizedLazyText (RestrictAtMost s)
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.filter Char -> Bool
p
{-# INLINE filter #-}

-- | /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.
--
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards /O(n*m)/.
breakOn :: SizedLazyText s -> SizedLazyText s' -> (SizedLazyText (RestrictAtMost s), SizedLazyText (RestrictAtMost s))
breakOn :: SizedLazyText s
-> SizedLazyText s'
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
breakOn SizedLazyText s
t = (Text -> SizedLazyText (RestrictAtMost s))
-> (Text -> SizedLazyText (RestrictAtMost s))
-> (Text, Text)
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized ((Text, Text)
 -> (SizedLazyText (RestrictAtMost s),
     SizedLazyText (RestrictAtMost s)))
-> (SizedLazyText s' -> (Text, Text))
-> SizedLazyText s'
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> (Text, Text)
T.breakOn (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
t) (Text -> (Text, Text))
-> (SizedLazyText s' -> Text) -> SizedLazyText s' -> (Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized 
{-# INLINE breakOn #-}

-- | /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 :: SizedLazyText s -> SizedLazyText s' -> (SizedLazyText (RestrictAtMost s), SizedLazyText (RestrictAtMost s))
breakOnEnd :: SizedLazyText s
-> SizedLazyText s'
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
breakOnEnd SizedLazyText s
t = (Text -> SizedLazyText (RestrictAtMost s))
-> (Text -> SizedLazyText (RestrictAtMost s))
-> (Text, Text)
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized ((Text, Text)
 -> (SizedLazyText (RestrictAtMost s),
     SizedLazyText (RestrictAtMost s)))
-> (SizedLazyText s' -> (Text, Text))
-> SizedLazyText s'
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> (Text, Text)
T.breakOnEnd (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
t) (Text -> (Text, Text))
-> (SizedLazyText s' -> Text) -> SizedLazyText s' -> (Text, Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized
{-# 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","/")]
--
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards /O(n*m)/.
--
-- The @needle@ parameter may not be empty.
breakOnAll ::
  -- | @needle@ to search for
  SizedLazyText s ->
  -- | @haystack@ in which to search
  SizedLazyText s' ->
  Sized (RestrictAtMost s) [(SizedLazyText (RestrictAtMost s), SizedLazyText (RestrictAtMost s))]
breakOnAll :: SizedLazyText s
-> SizedLazyText s'
-> Sized
     (RestrictAtMost s)
     [(SizedLazyText (RestrictAtMost s),
       SizedLazyText (RestrictAtMost s))]
breakOnAll SizedLazyText s
x SizedLazyText s'
y = [(SizedLazyText (RestrictAtMost s),
  SizedLazyText (RestrictAtMost s))]
-> Sized
     (RestrictAtMost s)
     [(SizedLazyText (RestrictAtMost s),
       SizedLazyText (RestrictAtMost s))]
forall a s. a -> Sized s a
trustedSized  ([(SizedLazyText (RestrictAtMost s),
   SizedLazyText (RestrictAtMost s))]
 -> Sized
      (RestrictAtMost s)
      [(SizedLazyText (RestrictAtMost s),
        SizedLazyText (RestrictAtMost s))])
-> [(SizedLazyText (RestrictAtMost s),
     SizedLazyText (RestrictAtMost s))]
-> Sized
     (RestrictAtMost s)
     [(SizedLazyText (RestrictAtMost s),
       SizedLazyText (RestrictAtMost s))]
forall a b. (a -> b) -> a -> b
$ ((Text, Text)
 -> (SizedLazyText (RestrictAtMost s),
     SizedLazyText (RestrictAtMost s)))
-> [(Text, Text)]
-> [(SizedLazyText (RestrictAtMost s),
     SizedLazyText (RestrictAtMost s))]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Text -> SizedLazyText (RestrictAtMost s))
-> (Text -> SizedLazyText (RestrictAtMost s))
-> (Text, Text)
-> (SizedLazyText (RestrictAtMost s),
    SizedLazyText (RestrictAtMost s))
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized) ([(Text, Text)]
 -> [(SizedLazyText (RestrictAtMost s),
      SizedLazyText (RestrictAtMost s))])
-> [(Text, Text)]
-> [(SizedLazyText (RestrictAtMost s),
     SizedLazyText (RestrictAtMost s))]
forall a b. (a -> b) -> a -> b
$ Text -> Text -> [(Text, Text)]
T.breakOnAll (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
x) (SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s'
y)
{-# INLINE breakOnAll #-}

-------------------------------------------------------------------------------

-- ** Indexing 'SizedLazyText's

-- $index
--
-- If you think of a 'SizedLazyText' value as an array of 'Char' values (which
-- it is not), you run the risk of writing inefficient code.
--
-- An idiom that is common in some languages is to find the numeric
-- offset of a character or substring, then use that number to split
-- or trim the searched string.  With a 'SizedLazyText' value, this approach
-- would require two /O(n)/ operations: one to perform the search, and
-- one to operate from wherever the search ended.
--
-- For example, suppose you have a string that you want to split on
-- the substring @\"::\"@, such as @\"foo::bar::quux\"@. Instead of
-- searching for the index of @\"::\"@ and taking the substrings
-- before and after that index, you would instead use @breakOnAll \"::\"@.

-- | /O(n)/ 'SizedLazyText' index (subscript) operator, starting from 0.
index :: (KnownNat n, Includes s n, HasCallStack) => SizedLazyText s -> Proxy n -> Char
index :: SizedLazyText s -> Proxy n -> Char
index SizedLazyText s
x = Text -> Int64 -> Char
T.index (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
x) (Int64 -> Char) -> (Proxy n -> Int64) -> Proxy n -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy n -> Int64
forall (n :: Nat). KnownNat n => Proxy n -> Int64
getN
{-# INLINE index #-}

-- | /O(n+m)/ The 'count' function returns the number of times the
-- query string appears in the given 'SizedLazyText'. 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 :: SizedLazyText s -> SizedLazyText s' -> Int64
count :: SizedLazyText s -> SizedLazyText s' -> Int64
count SizedLazyText s
x SizedLazyText s'
y = Text -> Text -> Int64
T.count (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
x) (SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s'
y)
{-# INLINE count #-}

-------------------------------------------------------------------------------

-- * Zipping

-- | /O(n)/ 'zip' takes two 'SizedLazyText's and returns a list of
-- corresponding pairs of bytes. If one input 'SizedLazyText' is short,
-- excess elements of the longer 'SizedLazyText' are discarded. This is
-- equivalent to a pair of 'unpack' operations.
zip :: SizedLazyText s -> SizedLazyText s -> Sized s [(Char, Char)]
zip :: SizedLazyText s -> SizedLazyText s -> Sized s [(Char, Char)]
zip = (Text -> Text -> [(Char, Char)])
-> SizedLazyText s -> SizedLazyText s -> Sized s [(Char, Char)]
forall a b c s0 s1 s2.
(a -> b -> c) -> Sized s0 a -> Sized s1 b -> Sized s2 c
trustedChangeOverSized2 Text -> Text -> [(Char, Char)]
T.zip
{-# INLINE 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) -> SizedLazyText s -> SizedLazyText s -> SizedLazyText s
zipWith :: (Char -> Char -> Char)
-> SizedLazyText s -> SizedLazyText s -> SizedLazyText s
zipWith Char -> Char -> Char
p = (Text -> Text -> Text)
-> SizedLazyText s -> SizedLazyText s -> SizedLazyText s
forall a b c s0 s1 s2.
(a -> b -> c) -> Sized s0 a -> Sized s1 b -> Sized s2 c
trustedChangeOverSized2 ((Text -> Text -> Text)
 -> SizedLazyText s -> SizedLazyText s -> SizedLazyText s)
-> (Text -> Text -> Text)
-> SizedLazyText s
-> SizedLazyText s
-> SizedLazyText s
forall a b. (a -> b) -> a -> b
$ (Char -> Char -> Char) -> Text -> Text -> Text
T.zipWith Char -> Char -> Char
p
{-# INLINE zipWith #-}

-- | /O(n)/ Breaks a 'SizedLazyText' up into a list of words, delimited by 'Char's
-- representing white space.
words :: SizedLazyText s -> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
words :: SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
words = (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> [SizedLazyText (RestrictAtMost s)])
 -> SizedLazyText s
 -> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)])
-> (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
forall a b. (a -> b) -> a -> b
$ (Text -> SizedLazyText (RestrictAtMost s))
-> [Text] -> [SizedLazyText (RestrictAtMost s)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized ([Text] -> [SizedLazyText (RestrictAtMost s)])
-> (Text -> [Text]) -> Text -> [SizedLazyText (RestrictAtMost s)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.words
{-# INLINE words #-}

-- | /O(n)/ Breaks a 'SizedLazyText' up into a list of 'SizedLazyText's at newline characters
-- @'\\n'@ (LF, line feed). The resulting strings do not contain newlines.
--
-- 'lines' __does not__ treat @'\\r'@ (CR, carriage return) as a newline character.
lines :: SizedLazyText s -> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
lines :: SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
lines = (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized ((Text -> [SizedLazyText (RestrictAtMost s)])
 -> SizedLazyText s
 -> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)])
-> (Text -> [SizedLazyText (RestrictAtMost s)])
-> SizedLazyText s
-> Sized (RestrictAtMost s) [SizedLazyText (RestrictAtMost s)]
forall a b. (a -> b) -> a -> b
$ (Text -> SizedLazyText (RestrictAtMost s))
-> [Text] -> [SizedLazyText (RestrictAtMost s)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText (RestrictAtMost s)
forall a s. a -> Sized s a
trustedSized ([Text] -> [SizedLazyText (RestrictAtMost s)])
-> (Text -> [Text]) -> Text -> [SizedLazyText (RestrictAtMost s)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.lines
{-# INLINE lines #-}

-- | /O(n)/ Joins lines, after appending a terminating newline to
-- each.
unlines :: Sized s [SizedLazyText s'] -> SizedLazyText (s <*> (s' <+> Exactly 1))
unlines :: Sized s [SizedLazyText s']
-> SizedLazyText (s <*> (s' <+> Exactly 1))
unlines = ([SizedLazyText s'] -> Text)
-> Sized s [SizedLazyText s']
-> SizedLazyText (s <*> (s' <+> Exactly 1))
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized (([SizedLazyText s'] -> Text)
 -> Sized s [SizedLazyText s']
 -> SizedLazyText (s <*> (s' <+> Exactly 1)))
-> ([SizedLazyText s'] -> Text)
-> Sized s [SizedLazyText s']
-> SizedLazyText (s <*> (s' <+> Exactly 1))
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines ([Text] -> Text)
-> ([SizedLazyText s'] -> [Text]) -> [SizedLazyText s'] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SizedLazyText s' -> Text) -> [SizedLazyText s'] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE unlines #-}

-- | /O(n)/ Joins words using single space characters.
unwords :: Sized s [SizedLazyText s'] -> SizedLazyText (s <*> (s' <+> Exactly 1))
unwords :: Sized s [SizedLazyText s']
-> SizedLazyText (s <*> (s' <+> Exactly 1))
unwords = ([SizedLazyText s'] -> Text)
-> Sized s [SizedLazyText s']
-> SizedLazyText (s <*> (s' <+> Exactly 1))
forall a b s0 s1. (a -> b) -> Sized s0 a -> Sized s1 b
trustedChangeOverSized (([SizedLazyText s'] -> Text)
 -> Sized s [SizedLazyText s']
 -> SizedLazyText (s <*> (s' <+> Exactly 1)))
-> ([SizedLazyText s'] -> Text)
-> Sized s [SizedLazyText s']
-> SizedLazyText (s <*> (s' <+> Exactly 1))
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unwords ([Text] -> Text)
-> ([SizedLazyText s'] -> [Text]) -> [SizedLazyText s'] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SizedLazyText s' -> Text) -> [SizedLazyText s'] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized
{-# INLINE unwords #-}

-- | /O(n)/ The 'isPrefixOf' function takes two 'SizedLazyText's and returns
-- 'True' if and only if the first is a prefix of the second.
isPrefixOf :: IsMoreGeneral s' s => SizedLazyText s -> SizedLazyText s' -> Bool
isPrefixOf :: SizedLazyText s -> SizedLazyText s' -> Bool
isPrefixOf SizedLazyText s
x SizedLazyText s'
y = Text -> Text -> Bool
T.isPrefixOf (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
x) (SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s'
y)
{-# INLINE isPrefixOf #-}

-- | /O(n)/ The 'isSuffixOf' function takes two 'SizedLazyText's and returns
-- 'True' if and only if the first is a suffix of the second.
isSuffixOf :: IsMoreGeneral s' s => SizedLazyText s -> SizedLazyText s' -> Bool
isSuffixOf :: SizedLazyText s -> SizedLazyText s' -> Bool
isSuffixOf SizedLazyText s
x SizedLazyText s'
y = Text -> Text -> Bool
T.isSuffixOf (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
x) (SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s'
y)
{-# INLINE isSuffixOf #-}

-- | /O(n+m)/ The 'isInfixOf' function takes two 'SizedLazyText's and returns
-- 'True' if and only if the first is contained, wholly and intact, anywhere
-- within the second.
--
-- In (unlikely) bad cases, this function's time complexity degrades
-- towards /O(n*m)/.
isInfixOf :: (IsMoreGeneral s' s, HasCallStack) => SizedLazyText s -> SizedLazyText s' -> Bool
isInfixOf :: SizedLazyText s -> SizedLazyText s' -> Bool
isInfixOf SizedLazyText s
x SizedLazyText s'
y = Text -> Text -> Bool
T.isInfixOf (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
x) (SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s'
y)
{-# INLINE isInfixOf #-}

-------------------------------------------------------------------------------

-- * 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.Sized as T
-- >
-- > fnordLength :: SizedLazyText -> Int
-- > fnordLength (stripPrefix "fnord" -> Just suf) = T.length suf
-- > fnordLength _                                 = -1
stripPrefix :: SizedLazyText s -> SizedLazyText s' -> Maybe (SizedLazyText (s <-> s'))
stripPrefix :: SizedLazyText s
-> SizedLazyText s' -> Maybe (SizedLazyText (s <-> s'))
stripPrefix SizedLazyText s
x SizedLazyText s'
y = (Text -> SizedLazyText (s <-> s'))
-> Maybe Text -> Maybe (SizedLazyText (s <-> s'))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText (s <-> s')
forall a s. a -> Sized s a
trustedSized (Maybe Text -> Maybe (SizedLazyText (s <-> s')))
-> Maybe Text -> Maybe (SizedLazyText (s <-> s'))
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Maybe Text
T.stripPrefix (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
x) (SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s'
y)
{-# INLINE stripPrefix #-}

-- | /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 :: SizedLazyText s -> SizedLazyText s' -> Maybe (T.Text, T.Text, T.Text)
commonPrefixes :: SizedLazyText s -> SizedLazyText s' -> Maybe (Text, Text, Text)
commonPrefixes SizedLazyText s
x SizedLazyText s'
y = Text -> Text -> Maybe (Text, Text, Text)
T.commonPrefixes (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
x) (SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s'
y)
{-# INLINE commonPrefixes #-}

-- | /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.Sized as T
-- >
-- > quuxLength :: SizedLazyText -> Int
-- > quuxLength (stripSuffix "quux" -> Just pre) = T.length pre
-- > quuxLength _                                = -1
stripSuffix :: SizedLazyText s -> SizedLazyText s' -> Maybe (SizedLazyText (s <-> s'))
stripSuffix :: SizedLazyText s
-> SizedLazyText s' -> Maybe (SizedLazyText (s <-> s'))
stripSuffix SizedLazyText s
x SizedLazyText s'
y = (Text -> SizedLazyText (s <-> s'))
-> Maybe Text -> Maybe (SizedLazyText (s <-> s'))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> SizedLazyText (s <-> s')
forall a s. a -> Sized s a
trustedSized (Maybe Text -> Maybe (SizedLazyText (s <-> s')))
-> Maybe Text -> Maybe (SizedLazyText (s <-> s'))
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Maybe Text
T.stripSuffix  (SizedLazyText s -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s
x) (SizedLazyText s' -> Text
forall s a. Sized s a -> a
getSized SizedLazyText s'
y)
{-# INLINE stripSuffix #-}

getN :: KnownNat n => Proxy n -> Int64
getN :: Proxy n -> Int64
getN = Integer -> Int64
forall a. Num a => Integer -> a
fromInteger (Integer -> Int64) -> (Proxy n -> Integer) -> Proxy n -> Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> Integer
naturalToInteger (Natural -> Integer) -> (Proxy n -> Natural) -> Proxy n -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy n -> Natural
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Natural
natVal