-- Alfred-Margaret: Fast Aho-Corasick string searching
-- Copyright 2022 Channable
--
-- Licensed under the 3-clause BSD license, see the LICENSE file in the
-- repository root.

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}

-- | This module provides functions that allow treating 'Text' values as series of UTF-8 code units
-- instead of characters. Any calls to 'Text' in @alfred-margaret@ go through this module.
-- Therefore we re-export some 'Text' functions, e.g. 'Text.concat'.
module Data.Text.Utf8
    ( CodePoint
    , CodeUnit
    , CodeUnitIndex (..)
    , Text (..)
    , fromByteList
    , isCaseInvariant
    , lengthUtf8
    , lowerCodePoint
    , lowerUtf8
    , toLowerAscii
    , unicode2utf8
    , unpackUtf8
      -- * Decoding
      --
      -- $decoding
    , decode2
    , decode3
    , decode4
    , decodeUtf8
      -- * Indexing
      --
      -- $indexing
    , indexCodeUnit
    , unsafeIndexCodePoint
    , unsafeIndexCodeUnit
      -- * Slicing Functions
      --
      -- $slicingFunctions
    , unsafeCutUtf8
    , unsafeSliceUtf8
      -- * Functions on Arrays
      --
      -- $functionsOnArrays
    , arrayContents
    , isArrayPinned
    , unsafeIndexCodePoint'
    , unsafeIndexCodeUnit'
      -- * General Functions
      --
      -- $generalFunctions
    , Text.concat
    , Text.dropWhile
    , Text.isInfixOf
    , Text.null
    , Text.pack
    , Text.replicate
    , Text.unpack
    , TextSearch.indices
    ) where

import Control.DeepSeq (NFData)
import Data.Bits (Bits (shiftL), shiftR, (.&.), (.|.))
import Data.Hashable (Hashable)
import Data.Text.Internal (Text (..))
import Data.Word (Word8)
import GHC.Generics (Generic)
import Data.Primitive (ByteArray(ByteArray), byteArrayFromList)
#if defined(HAS_AESON)
import Data.Aeson (FromJSON, ToJSON)
#endif

import qualified Data.Char as Char
import qualified Data.Text as Text
import qualified Data.Text.Array as TextArray
import qualified Data.Text.Internal.Search as TextSearch
import qualified Data.Text.Unsafe as TextUnsafe
import qualified GHC.Exts as Exts

-- | A UTF-8 code unit is a byte. A Unicode code point can be encoded as up to four code units.
type CodeUnit = Word8

-- | A Unicode code point.
type CodePoint = Char

-- | An index into the raw UTF-8 data of a `Text`. This is not the code point
-- index as conventionally accepted by `Text`, so we wrap it to avoid confusing
-- the two. Incorrect index manipulation can lead to surrogate pairs being
-- sliced, so manipulate indices with care. This type is also used for lengths.
newtype CodeUnitIndex = CodeUnitIndex
    { CodeUnitIndex -> Int
codeUnitIndex :: Int
    }
    deriving stock (CodeUnitIndex -> CodeUnitIndex -> Bool
(CodeUnitIndex -> CodeUnitIndex -> Bool)
-> (CodeUnitIndex -> CodeUnitIndex -> Bool) -> Eq CodeUnitIndex
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeUnitIndex -> CodeUnitIndex -> Bool
$c/= :: CodeUnitIndex -> CodeUnitIndex -> Bool
== :: CodeUnitIndex -> CodeUnitIndex -> Bool
$c== :: CodeUnitIndex -> CodeUnitIndex -> Bool
Eq, Eq CodeUnitIndex
Eq CodeUnitIndex
-> (CodeUnitIndex -> CodeUnitIndex -> Ordering)
-> (CodeUnitIndex -> CodeUnitIndex -> Bool)
-> (CodeUnitIndex -> CodeUnitIndex -> Bool)
-> (CodeUnitIndex -> CodeUnitIndex -> Bool)
-> (CodeUnitIndex -> CodeUnitIndex -> Bool)
-> (CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex)
-> (CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex)
-> Ord CodeUnitIndex
CodeUnitIndex -> CodeUnitIndex -> Bool
CodeUnitIndex -> CodeUnitIndex -> Ordering
CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
$cmin :: CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
max :: CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
$cmax :: CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
>= :: CodeUnitIndex -> CodeUnitIndex -> Bool
$c>= :: CodeUnitIndex -> CodeUnitIndex -> Bool
> :: CodeUnitIndex -> CodeUnitIndex -> Bool
$c> :: CodeUnitIndex -> CodeUnitIndex -> Bool
<= :: CodeUnitIndex -> CodeUnitIndex -> Bool
$c<= :: CodeUnitIndex -> CodeUnitIndex -> Bool
< :: CodeUnitIndex -> CodeUnitIndex -> Bool
$c< :: CodeUnitIndex -> CodeUnitIndex -> Bool
compare :: CodeUnitIndex -> CodeUnitIndex -> Ordering
$ccompare :: CodeUnitIndex -> CodeUnitIndex -> Ordering
$cp1Ord :: Eq CodeUnitIndex
Ord, Int -> CodeUnitIndex -> ShowS
[CodeUnitIndex] -> ShowS
CodeUnitIndex -> String
(Int -> CodeUnitIndex -> ShowS)
-> (CodeUnitIndex -> String)
-> ([CodeUnitIndex] -> ShowS)
-> Show CodeUnitIndex
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeUnitIndex] -> ShowS
$cshowList :: [CodeUnitIndex] -> ShowS
show :: CodeUnitIndex -> String
$cshow :: CodeUnitIndex -> String
showsPrec :: Int -> CodeUnitIndex -> ShowS
$cshowsPrec :: Int -> CodeUnitIndex -> ShowS
Show, (forall x. CodeUnitIndex -> Rep CodeUnitIndex x)
-> (forall x. Rep CodeUnitIndex x -> CodeUnitIndex)
-> Generic CodeUnitIndex
forall x. Rep CodeUnitIndex x -> CodeUnitIndex
forall x. CodeUnitIndex -> Rep CodeUnitIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CodeUnitIndex x -> CodeUnitIndex
$cfrom :: forall x. CodeUnitIndex -> Rep CodeUnitIndex x
Generic, CodeUnitIndex
CodeUnitIndex -> CodeUnitIndex -> Bounded CodeUnitIndex
forall a. a -> a -> Bounded a
maxBound :: CodeUnitIndex
$cmaxBound :: CodeUnitIndex
minBound :: CodeUnitIndex
$cminBound :: CodeUnitIndex
Bounded)
#if defined(HAS_AESON)
    deriving newtype (Eq CodeUnitIndex
Eq CodeUnitIndex
-> (Int -> CodeUnitIndex -> Int)
-> (CodeUnitIndex -> Int)
-> Hashable CodeUnitIndex
Int -> CodeUnitIndex -> Int
CodeUnitIndex -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: CodeUnitIndex -> Int
$chash :: CodeUnitIndex -> Int
hashWithSalt :: Int -> CodeUnitIndex -> Int
$chashWithSalt :: Int -> CodeUnitIndex -> Int
$cp1Hashable :: Eq CodeUnitIndex
Hashable, Integer -> CodeUnitIndex
CodeUnitIndex -> CodeUnitIndex
CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
(CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex)
-> (CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex)
-> (CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex)
-> (CodeUnitIndex -> CodeUnitIndex)
-> (CodeUnitIndex -> CodeUnitIndex)
-> (CodeUnitIndex -> CodeUnitIndex)
-> (Integer -> CodeUnitIndex)
-> Num CodeUnitIndex
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> CodeUnitIndex
$cfromInteger :: Integer -> CodeUnitIndex
signum :: CodeUnitIndex -> CodeUnitIndex
$csignum :: CodeUnitIndex -> CodeUnitIndex
abs :: CodeUnitIndex -> CodeUnitIndex
$cabs :: CodeUnitIndex -> CodeUnitIndex
negate :: CodeUnitIndex -> CodeUnitIndex
$cnegate :: CodeUnitIndex -> CodeUnitIndex
* :: CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
$c* :: CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
- :: CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
$c- :: CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
+ :: CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
$c+ :: CodeUnitIndex -> CodeUnitIndex -> CodeUnitIndex
Num, CodeUnitIndex -> ()
(CodeUnitIndex -> ()) -> NFData CodeUnitIndex
forall a. (a -> ()) -> NFData a
rnf :: CodeUnitIndex -> ()
$crnf :: CodeUnitIndex -> ()
NFData, Value -> Parser [CodeUnitIndex]
Value -> Parser CodeUnitIndex
(Value -> Parser CodeUnitIndex)
-> (Value -> Parser [CodeUnitIndex]) -> FromJSON CodeUnitIndex
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CodeUnitIndex]
$cparseJSONList :: Value -> Parser [CodeUnitIndex]
parseJSON :: Value -> Parser CodeUnitIndex
$cparseJSON :: Value -> Parser CodeUnitIndex
FromJSON, [CodeUnitIndex] -> Encoding
[CodeUnitIndex] -> Value
CodeUnitIndex -> Encoding
CodeUnitIndex -> Value
(CodeUnitIndex -> Value)
-> (CodeUnitIndex -> Encoding)
-> ([CodeUnitIndex] -> Value)
-> ([CodeUnitIndex] -> Encoding)
-> ToJSON CodeUnitIndex
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CodeUnitIndex] -> Encoding
$ctoEncodingList :: [CodeUnitIndex] -> Encoding
toJSONList :: [CodeUnitIndex] -> Value
$ctoJSONList :: [CodeUnitIndex] -> Value
toEncoding :: CodeUnitIndex -> Encoding
$ctoEncoding :: CodeUnitIndex -> Encoding
toJSON :: CodeUnitIndex -> Value
$ctoJSON :: CodeUnitIndex -> Value
ToJSON)
#else
    deriving newtype (Hashable, Num, NFData)
#endif

{-# INLINABLE unpackUtf8 #-}
unpackUtf8 :: Text -> [CodeUnit]
unpackUtf8 :: Text -> [CodeUnit]
unpackUtf8 (Text Array
u8data Int
offset Int
len) =
  let
    go :: Int -> t -> [CodeUnit]
go Int
_ t
0 = []
    go Int
i t
n = Array -> CodeUnitIndex -> CodeUnit
unsafeIndexCodeUnit' Array
u8data (Int -> CodeUnitIndex
CodeUnitIndex Int
i) CodeUnit -> [CodeUnit] -> [CodeUnit]
forall a. a -> [a] -> [a]
: Int -> t -> [CodeUnit]
go (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1)
  in
    Int -> Int -> [CodeUnit]
forall t. (Eq t, Num t) => Int -> t -> [CodeUnit]
go Int
offset Int
len

-- | The return value of this function is not really an index.
-- However the signature is supposed to make it clear that the length is returned in terms of code units, not code points.
lengthUtf8 :: Text -> CodeUnitIndex
lengthUtf8 :: Text -> CodeUnitIndex
lengthUtf8 (Text Array
_ Int
_ !Int
len) = Int -> CodeUnitIndex
CodeUnitIndex Int
len

-- | Lower-case the ASCII code points A-Z and leave the rest of ASCII intact.
{-# INLINE toLowerAscii #-}
toLowerAscii :: Char -> Char
toLowerAscii :: Char -> Char
toLowerAscii Char
cp
  | Char -> Bool
Char.isAsciiUpper Char
cp = Int -> Char
Char.chr (Char -> Int
Char.ord Char
cp Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
0x20)
  | Bool
otherwise = Char
cp

-- | Lowercase a 'Text' by applying 'lowerCodePoint' to each 'Char'.
{-# INLINE lowerUtf8 #-}
lowerUtf8 :: Text -> Text
lowerUtf8 :: Text -> Text
lowerUtf8 = (Char -> Char) -> Text -> Text
Text.map Char -> Char
lowerCodePoint

asciiCount :: Int
asciiCount :: Int
asciiCount = Int
128

{-# INLINE lowerCodePoint #-}
-- | Lower-Case a UTF-8 codepoint.
-- Uses 'toLowerAscii' for ASCII and 'Char.toLower' otherwise.
lowerCodePoint :: Char -> Char
lowerCodePoint :: Char -> Char
lowerCodePoint Char
cp
  | Char -> Int
Char.ord Char
cp Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
asciiCount = Char -> Char
toLowerAscii Char
cp
  | Bool
otherwise = Char -> Char
Char.toLower Char
cp

-- | Convert a Unicode Code Point 'c' into a list of UTF-8 code units (bytes).
unicode2utf8 :: (Ord a, Num a, Bits a) => a -> [a]
unicode2utf8 :: a -> [a]
unicode2utf8 a
c
    | a
c a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0x80    = [a
c]
    | a
c a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0x800   = [a
0xc0 a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
c a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` Int
6), a
0x80 a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
0x3f a -> a -> a
forall a. Bits a => a -> a -> a
.&. a
c)]
    | a
c a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0x10000 = [a
0xe0 a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
c a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` Int
12), a
0x80 a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
0x3f a -> a -> a
forall a. Bits a => a -> a -> a
.&. (a
c a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` Int
6)), a
0x80 a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
0x3f a -> a -> a
forall a. Bits a => a -> a -> a
.&. a
c)]
    | Bool
otherwise   = [a
0xf0 a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
c a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` Int
18), a
0x80 a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
0x3f a -> a -> a
forall a. Bits a => a -> a -> a
.&. (a
c a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` Int
12)), a
0x80 a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
0x3f a -> a -> a
forall a. Bits a => a -> a -> a
.&. (a
c a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftR` Int
6)), a
0x80 a -> a -> a
forall a. Bits a => a -> a -> a
.|. (a
0x3f a -> a -> a
forall a. Bits a => a -> a -> a
.&. a
c)]

fromByteList :: [Word8] -> Text
fromByteList :: [CodeUnit] -> Text
fromByteList [CodeUnit]
byteList = Array -> Int -> Int -> Text
Text (ByteArray# -> Array
TextArray.ByteArray ByteArray#
ba#) Int
0 ([CodeUnit] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [CodeUnit]
byteList)
  where !(ByteArray ByteArray#
ba#) = [CodeUnit] -> ByteArray
forall a. Prim a => [a] -> ByteArray
byteArrayFromList [CodeUnit]
byteList

-- | Return whether text is the same lowercase as uppercase, such that this
-- function will not return true when Aho–Corasick would differentiate when
-- doing case-insensitive matching.
{-# INLINE isCaseInvariant #-}
isCaseInvariant :: Text -> Bool
isCaseInvariant :: Text -> Bool
isCaseInvariant = (Char -> Bool) -> Text -> Bool
Text.all (\Char
c -> Char -> Char
Char.toLower Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> Char
Char.toUpper Char
c)

-- $decoding
--
-- Functions that turns code unit sequences into code point sequences.

-- | Decode 2 UTF-8 code units into their code point.
-- The given code units should have the following format:
--
-- > ┌───────────────┬───────────────┐
-- > │1 1 0 x x x x x│1 0 x x x x x x│
-- > └───────────────┴───────────────┘
{-# INLINE decode2 #-}
decode2 :: CodeUnit -> CodeUnit -> CodePoint
decode2 :: CodeUnit -> CodeUnit -> Char
decode2 CodeUnit
cu0 CodeUnit
cu1 =
  Int -> Char
Char.chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ (CodeUnit -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CodeUnit
cu0 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x1f) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
6 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. CodeUnit -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CodeUnit
cu1 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x3f

-- | Decode 3 UTF-8 code units into their code point.
-- The given code units should have the following format:
--
-- > ┌───────────────┬───────────────┬───────────────┐
-- > │1 1 1 0 x x x x│1 0 x x x x x x│1 0 x x x x x x│
-- > └───────────────┴───────────────┴───────────────┘
{-# INLINE decode3 #-}
decode3 :: CodeUnit -> CodeUnit -> CodeUnit -> CodePoint
decode3 :: CodeUnit -> CodeUnit -> CodeUnit -> Char
decode3 CodeUnit
cu0 CodeUnit
cu1 CodeUnit
cu2 =
  Int -> Char
Char.chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ (CodeUnit -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CodeUnit
cu0 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0xf) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
12 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. (CodeUnit -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CodeUnit
cu1 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x3f) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
6 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. (CodeUnit -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CodeUnit
cu2 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x3f)

-- | Decode 4 UTF-8 code units into their code point.
-- The given code units should have the following format:
--
-- > ┌───────────────┬───────────────┬───────────────┬───────────────┐
-- > │1 1 1 1 0 x x x│1 0 x x x x x x│1 0 x x x x x x│1 0 x x x x x x│
-- > └───────────────┴───────────────┴───────────────┴───────────────┘
{-# INLINE decode4 #-}
decode4 :: CodeUnit -> CodeUnit -> CodeUnit -> CodeUnit -> CodePoint
decode4 :: CodeUnit -> CodeUnit -> CodeUnit -> CodeUnit -> Char
decode4 CodeUnit
cu0 CodeUnit
cu1 CodeUnit
cu2 CodeUnit
cu3 =
  Int -> Char
Char.chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ (CodeUnit -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CodeUnit
cu0 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x7) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
18 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. (CodeUnit -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CodeUnit
cu1 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x3f) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
12 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. (CodeUnit -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CodeUnit
cu2 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x3f) Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
6 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. (CodeUnit -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CodeUnit
cu3 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
0x3f)

-- | Decode a list of UTF-8 code units into a list of code points.
decodeUtf8 :: [CodeUnit] -> [CodePoint]
decodeUtf8 :: [CodeUnit] -> String
decodeUtf8 [] = []
decodeUtf8 (CodeUnit
cu0 : [CodeUnit]
cus) | CodeUnit
cu0 CodeUnit -> CodeUnit -> Bool
forall a. Ord a => a -> a -> Bool
< CodeUnit
0xc0 = Int -> Char
Char.chr (CodeUnit -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CodeUnit
cu0) Char -> ShowS
forall a. a -> [a] -> [a]
: [CodeUnit] -> String
decodeUtf8 [CodeUnit]
cus
decodeUtf8 (CodeUnit
cu0 : CodeUnit
cu1 : [CodeUnit]
cus) | CodeUnit
cu0 CodeUnit -> CodeUnit -> Bool
forall a. Ord a => a -> a -> Bool
< CodeUnit
0xe0 = CodeUnit -> CodeUnit -> Char
decode2 CodeUnit
cu0 CodeUnit
cu1 Char -> ShowS
forall a. a -> [a] -> [a]
: [CodeUnit] -> String
decodeUtf8 [CodeUnit]
cus
decodeUtf8 (CodeUnit
cu0 : CodeUnit
cu1 : CodeUnit
cu2 : [CodeUnit]
cus) | CodeUnit
cu0 CodeUnit -> CodeUnit -> Bool
forall a. Ord a => a -> a -> Bool
< CodeUnit
0xf0 = CodeUnit -> CodeUnit -> CodeUnit -> Char
decode3 CodeUnit
cu0 CodeUnit
cu1 CodeUnit
cu2 Char -> ShowS
forall a. a -> [a] -> [a]
: [CodeUnit] -> String
decodeUtf8 [CodeUnit]
cus
decodeUtf8 (CodeUnit
cu0 : CodeUnit
cu1 : CodeUnit
cu2 : CodeUnit
cu3 : [CodeUnit]
cus) | CodeUnit
cu0 CodeUnit -> CodeUnit -> Bool
forall a. Ord a => a -> a -> Bool
< CodeUnit
0xf8 = CodeUnit -> CodeUnit -> CodeUnit -> CodeUnit -> Char
decode4 CodeUnit
cu0 CodeUnit
cu1 CodeUnit
cu2 CodeUnit
cu3 Char -> ShowS
forall a. a -> [a] -> [a]
: [CodeUnit] -> String
decodeUtf8 [CodeUnit]
cus
decodeUtf8 [CodeUnit]
cus = ShowS
forall a. HasCallStack => String -> a
error ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String
"Invalid UTF-8 input sequence at " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [CodeUnit] -> String
forall a. Show a => a -> String
show (Int -> [CodeUnit] -> [CodeUnit]
forall a. Int -> [a] -> [a]
take Int
4 [CodeUnit]
cus)

-- $indexing
--
-- 'Text' can be indexed by code units or code points.
-- A 'CodePoint' is a 21-bit Unicode code point and can consist of up to four code units.
-- A 'CodeUnit' is a single byte.

-- | Does exactly the same thing as 'unsafeIndexCodePoint'', but on 'Text' values.
{-# INLINE unsafeIndexCodePoint #-}
unsafeIndexCodePoint :: Text -> CodeUnitIndex -> (CodeUnitIndex, CodePoint)
unsafeIndexCodePoint :: Text -> CodeUnitIndex -> (CodeUnitIndex, Char)
unsafeIndexCodePoint (Text !Array
u8data !Int
off !Int
_len) (CodeUnitIndex !Int
index) =
  Array -> CodeUnitIndex -> (CodeUnitIndex, Char)
unsafeIndexCodePoint' Array
u8data (CodeUnitIndex -> (CodeUnitIndex, Char))
-> CodeUnitIndex -> (CodeUnitIndex, Char)
forall a b. (a -> b) -> a -> b
$ Int -> CodeUnitIndex
CodeUnitIndex (Int -> CodeUnitIndex) -> Int -> CodeUnitIndex
forall a b. (a -> b) -> a -> b
$ Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
index

-- | Get the code unit at the given 'CodeUnitIndex'.
-- Performs bounds checking.
{-# INLINE indexCodeUnit #-}
indexCodeUnit :: Text -> CodeUnitIndex -> CodeUnit
indexCodeUnit :: Text -> CodeUnitIndex -> CodeUnit
indexCodeUnit !Text
text (CodeUnitIndex !Int
index)
  | Int
index Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
index Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= CodeUnitIndex -> Int
codeUnitIndex (Text -> CodeUnitIndex
lengthUtf8 Text
text) = String -> CodeUnit
forall a. HasCallStack => String -> a
error (String -> CodeUnit) -> String -> CodeUnit
forall a b. (a -> b) -> a -> b
$ String
"Index out of bounds " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
index
  | Bool
otherwise = Text -> CodeUnitIndex -> CodeUnit
unsafeIndexCodeUnit Text
text (CodeUnitIndex -> CodeUnit) -> CodeUnitIndex -> CodeUnit
forall a b. (a -> b) -> a -> b
$ Int -> CodeUnitIndex
CodeUnitIndex Int
index

{-# INLINE unsafeIndexCodeUnit #-}
unsafeIndexCodeUnit :: Text -> CodeUnitIndex -> CodeUnit
unsafeIndexCodeUnit :: Text -> CodeUnitIndex -> CodeUnit
unsafeIndexCodeUnit (Text !Array
u8data !Int
off !Int
_len) (CodeUnitIndex !Int
index) =
  Array -> CodeUnitIndex -> CodeUnit
unsafeIndexCodeUnit' Array
u8data (CodeUnitIndex -> CodeUnit) -> CodeUnitIndex -> CodeUnit
forall a b. (a -> b) -> a -> b
$ Int -> CodeUnitIndex
CodeUnitIndex (Int -> CodeUnitIndex) -> Int -> CodeUnitIndex
forall a b. (a -> b) -> a -> b
$ Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
index

-- $slicingFunctions
--
-- 'unsafeCutUtf8' and 'unsafeSliceUtf8' are used to retrieve slices of 'Text' values.
-- @unsafeSliceUtf8 begin length@ returns a substring of length @length@ starting at @begin@.
-- @unsafeSliceUtf8 begin length@ returns a tuple of the "surrounding" substrings.
--
-- They satisfy the following property:
--
-- > let (prefix, suffix) = unsafeCutUtf8 begin length t
-- > in concat [prefix, unsafeSliceUtf8 begin length t, suffix] == t
--
-- The following diagram visualizes the relevant offsets for @begin = CodeUnitIndex 2@, @length = CodeUnitIndex 6@ and @t = \"BCDEFGHIJKL\"@.
--
-- >  off                 off+len
-- >   │                     │
-- >   ▼                     ▼
-- > ──┬─┬─┬─┬─┬─┬─┬─┬─┬─┬─┬─┬─┬──
-- >  A│B│C│D│E│F│G│H│I│J│K│L│M│N
-- > ──┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┴──
-- >       ▲           ▲
-- >       │           │
-- >  off+begin   off+begin+length
-- >
-- > unsafeSliceUtf8 begin length t == "DEFGHI"
-- > unsafeCutUtf8 begin length t == ("BC", "JKL")
--
-- The shown array is open at each end because in general, @t@ may be a slice as well.
--
-- __WARNING__: As their name implies, these functions are not (necessarily) bounds-checked. Use at your own risk.

unsafeCutUtf8 :: CodeUnitIndex -- ^ Starting position of substring.
  -> CodeUnitIndex -- ^ Length of substring.
  -> Text -- ^ Initial string.
  -> (Text, Text)
unsafeCutUtf8 :: CodeUnitIndex -> CodeUnitIndex -> Text -> (Text, Text)
unsafeCutUtf8 (CodeUnitIndex !Int
begin) (CodeUnitIndex !Int
len) !Text
text =
  ( Int -> Text -> Text
TextUnsafe.takeWord8 Int
begin Text
text
  , Int -> Text -> Text
TextUnsafe.dropWord8 (Int
begin Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len) Text
text
  )

unsafeSliceUtf8 :: CodeUnitIndex -> CodeUnitIndex -> Text -> Text
unsafeSliceUtf8 :: CodeUnitIndex -> CodeUnitIndex -> Text -> Text
unsafeSliceUtf8 (CodeUnitIndex !Int
begin) (CodeUnitIndex !Int
len) !Text
text =
  Int -> Text -> Text
TextUnsafe.takeWord8 Int
len (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
TextUnsafe.dropWord8 Int
begin Text
text

-- $functionsOnArrays
--
-- Functions for working with 'TextArray.Array' values.

-- | See 'Data.Primitive.isByteArrayPinned'.
isArrayPinned :: TextArray.Array -> Bool
isArrayPinned :: Array -> Bool
isArrayPinned (TextArray.ByteArray ByteArray#
ba#) = Int# -> Bool
Exts.isTrue# (ByteArray# -> Int#
Exts.isByteArrayPinned# ByteArray#
ba#)

-- | See 'Data.Primitive.byteArrayContents'.
arrayContents :: TextArray.Array -> Exts.Ptr Word8
arrayContents :: Array -> Ptr CodeUnit
arrayContents (TextArray.ByteArray ByteArray#
ba#) = Addr# -> Ptr CodeUnit
forall a. Addr# -> Ptr a
Exts.Ptr (ByteArray# -> Addr#
Exts.byteArrayContents# ByteArray#
ba#)

-- | Decode a code point at the given 'CodeUnitIndex'.
-- Returns garbage if there is no valid code point at that position.
-- Does not perform bounds checking.
-- See 'decode2', 'decode3' and 'decode4' for the expected format of multi-byte code points.
{-# INLINE unsafeIndexCodePoint' #-}
unsafeIndexCodePoint' :: TextArray.Array -> CodeUnitIndex -> (CodeUnitIndex, CodePoint)
unsafeIndexCodePoint' :: Array -> CodeUnitIndex -> (CodeUnitIndex, Char)
unsafeIndexCodePoint' !Array
u8data (CodeUnitIndex !Int
idx)
  | CodeUnit
cu0 CodeUnit -> CodeUnit -> Bool
forall a. Ord a => a -> a -> Bool
< CodeUnit
0xc0 = (CodeUnitIndex
1, Int -> Char
Char.chr (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ CodeUnit -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CodeUnit
cu0)
  | CodeUnit
cu0 CodeUnit -> CodeUnit -> Bool
forall a. Ord a => a -> a -> Bool
< CodeUnit
0xe0 = (CodeUnitIndex
2, CodeUnit -> CodeUnit -> Char
decode2 CodeUnit
cu0 (Int -> CodeUnit
cuAt Int
1))
  | CodeUnit
cu0 CodeUnit -> CodeUnit -> Bool
forall a. Ord a => a -> a -> Bool
< CodeUnit
0xf0 = (CodeUnitIndex
3, CodeUnit -> CodeUnit -> CodeUnit -> Char
decode3 CodeUnit
cu0 (Int -> CodeUnit
cuAt Int
1) (Int -> CodeUnit
cuAt Int
2))
  | Bool
otherwise = (CodeUnitIndex
4, CodeUnit -> CodeUnit -> CodeUnit -> CodeUnit -> Char
decode4 CodeUnit
cu0 (Int -> CodeUnit
cuAt Int
1) (Int -> CodeUnit
cuAt Int
2) (Int -> CodeUnit
cuAt Int
3))
  where
    cuAt :: Int -> CodeUnit
cuAt !Int
i = Array -> CodeUnitIndex -> CodeUnit
unsafeIndexCodeUnit' Array
u8data (CodeUnitIndex -> CodeUnit) -> CodeUnitIndex -> CodeUnit
forall a b. (a -> b) -> a -> b
$ Int -> CodeUnitIndex
CodeUnitIndex (Int -> CodeUnitIndex) -> Int -> CodeUnitIndex
forall a b. (a -> b) -> a -> b
$ Int
idx Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
i
    !cu0 :: CodeUnit
cu0 = Int -> CodeUnit
cuAt Int
0

{-# INLINE unsafeIndexCodeUnit' #-}
unsafeIndexCodeUnit' :: TextArray.Array -> CodeUnitIndex -> CodeUnit
unsafeIndexCodeUnit' :: Array -> CodeUnitIndex -> CodeUnit
unsafeIndexCodeUnit' !Array
u8data (CodeUnitIndex !Int
idx) = Array -> Int -> CodeUnit
TextArray.unsafeIndex Array
u8data Int
idx

-- $generalFunctions
--
-- Re-exported from 'Text'.