{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE Unsafe #-}
{-# LANGUAGE ViewPatterns #-}
module Data.Text.Short.Internal
(
ShortText(..)
, null
, length
, isAscii
, splitAt
, splitAtEnd
, indexEndMaybe
, indexMaybe
, isPrefixOf
, stripPrefix
, isSuffixOf
, stripSuffix
, cons
, snoc
, uncons
, unsnoc
, findIndex
, find
, all
, span
, spanEnd
, split
, intersperse
, intercalate
, reverse
, replicate
, filter
, dropAround
, foldl
, foldl'
, foldr
, foldl1
, foldl1'
, foldr1
, singleton
, Data.Text.Short.Internal.fromString
, toString
, fromText
, toText
, fromShortByteString
, fromShortByteStringUnsafe
, toShortByteString
, fromByteString
, fromByteStringUnsafe
, toByteString
, toBuilder
, BS.ByteString
, T.Text
, module Prelude
, module Data.Monoid
, isValidUtf8
) where
import Prelude
(Bool(..), Ordering(..), Int, Char, String, Maybe(..), IO, Eq, Ord, Num, Read,
Show, ($), ($!), (.), (==), (/=), (+), (*), (-), (>>), (<=), (<), (>), (>=),
compare, show, showsPrec, readsPrec, abs, return, fmap, error,
undefined, otherwise, fromIntegral, max, min, not, fst, snd, map, seq, fail, maybe)
import Control.DeepSeq (NFData)
import Control.Monad.ST (stToIO)
import Data.Binary
import Data.Bits
import qualified Data.ByteString as BS
import qualified Data.ByteString.Builder as BB
import Data.ByteString.Short (ShortByteString)
import qualified Data.ByteString.Short as BSS
import qualified Data.ByteString.Short.Internal as BSSI
import Data.Char (ord)
import Data.Data (Data(..),constrIndex, Constr,
mkConstr, DataType, mkDataType,
Fixity(Prefix))
import Data.Hashable (Hashable)
import Data.Typeable (Typeable)
import qualified Data.List as List
import Data.Maybe (fromMaybe, isNothing)
import Data.Monoid (Monoid, mempty, mconcat)
import Data.Semigroup
import qualified Data.String as S
import qualified Data.Text as T
import Foreign.C
import GHC.Base (assert, unsafeChr)
import qualified GHC.CString as GHC
import GHC.Exts (Addr#, ByteArray#, Int (I#),
Int#, MutableByteArray#,
Ptr (..), RealWorld, Word (W#))
import qualified GHC.Exts
import qualified GHC.Foreign as GHC
import GHC.IO.Encoding
import GHC.ST
import System.IO.Unsafe
import Text.Printf (PrintfArg, formatArg,
formatString)
import qualified Language.Haskell.TH.Syntax as TH
#if MIN_VERSION_text(2,0,0)
import qualified Data.Text.Internal as TI
import qualified Data.Text.Array as TA
#else
import qualified Data.Text.Encoding as T
#endif
import qualified PrimOps
newtype ShortText = ShortText ShortByteString
deriving (Eq ShortText
Eq ShortText =>
(Int -> ShortText -> Int)
-> (ShortText -> Int) -> Hashable ShortText
Int -> ShortText -> Int
ShortText -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> ShortText -> Int
hashWithSalt :: Int -> ShortText -> Int
$chash :: ShortText -> Int
hash :: ShortText -> Int
Hashable,Semigroup ShortText
ShortText
Semigroup ShortText =>
ShortText
-> (ShortText -> ShortText -> ShortText)
-> ([ShortText] -> ShortText)
-> Monoid ShortText
[ShortText] -> ShortText
ShortText -> ShortText -> ShortText
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: ShortText
mempty :: ShortText
$cmappend :: ShortText -> ShortText -> ShortText
mappend :: ShortText -> ShortText -> ShortText
$cmconcat :: [ShortText] -> ShortText
mconcat :: [ShortText] -> ShortText
Monoid,ShortText -> ()
(ShortText -> ()) -> NFData ShortText
forall a. (a -> ()) -> NFData a
$crnf :: ShortText -> ()
rnf :: ShortText -> ()
NFData,NonEmpty ShortText -> ShortText
ShortText -> ShortText -> ShortText
(ShortText -> ShortText -> ShortText)
-> (NonEmpty ShortText -> ShortText)
-> (forall b. Integral b => b -> ShortText -> ShortText)
-> Semigroup ShortText
forall b. Integral b => b -> ShortText -> ShortText
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: ShortText -> ShortText -> ShortText
<> :: ShortText -> ShortText -> ShortText
$csconcat :: NonEmpty ShortText -> ShortText
sconcat :: NonEmpty ShortText -> ShortText
$cstimes :: forall b. Integral b => b -> ShortText -> ShortText
stimes :: forall b. Integral b => b -> ShortText -> ShortText
Data.Semigroup.Semigroup,Typeable)
instance Data ShortText where
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ShortText -> c ShortText
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
f forall g. g -> c g
z ShortText
txt = (String -> ShortText) -> c (String -> ShortText)
forall g. g -> c g
z String -> ShortText
fromString c (String -> ShortText) -> String -> c ShortText
forall d b. Data d => c (d -> b) -> d -> c b
`f` (ShortText -> String
toString ShortText
txt)
toConstr :: ShortText -> Constr
toConstr ShortText
_ = Constr
packConstr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ShortText
gunfold forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
c = case Constr -> Int
constrIndex Constr
c of
Int
1 -> c (String -> ShortText) -> c ShortText
forall b r. Data b => c (b -> r) -> c r
k ((String -> ShortText) -> c (String -> ShortText)
forall r. r -> c r
z String -> ShortText
fromString)
Int
_ -> String -> c ShortText
forall a. (?callStack::CallStack) => String -> a
error String
"gunfold"
dataTypeOf :: ShortText -> DataType
dataTypeOf ShortText
_ = DataType
shortTextDataType
packConstr :: Constr
packConstr :: Constr
packConstr = DataType -> String -> [String] -> Fixity -> Constr
mkConstr DataType
shortTextDataType String
"fromString" [] Fixity
Prefix
shortTextDataType :: DataType
shortTextDataType :: DataType
shortTextDataType = String -> [Constr] -> DataType
mkDataType String
"Data.Text.Short" [Constr
packConstr]
instance Eq ShortText where
{-# INLINE (==) #-}
== :: ShortText -> ShortText -> Bool
(==) ShortText
x ShortText
y
| Int
lx Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
ly = Bool
False
| Int
lx Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Bool
True
| Bool
otherwise = case ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
PrimOps.compareByteArrays# (ShortText -> ByteArray#
toByteArray# ShortText
x) Int#
0# (ShortText -> ByteArray#
toByteArray# ShortText
y) Int#
0# Int#
n# of
Int#
0# -> Bool
True
Int#
_ -> Bool
False
where
!lx :: Int
lx@(I# Int#
n#) = ShortText -> Int
toLength ShortText
x
!ly :: Int
ly = ShortText -> Int
toLength ShortText
y
instance Ord ShortText where
compare :: ShortText -> ShortText -> Ordering
compare ShortText
t1 ShortText
t2
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
n1 Int
n2
| Bool
otherwise = case ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
PrimOps.compareByteArrays# ByteArray#
ba1# Int#
0# ByteArray#
ba2# Int#
0# Int#
n# of
Int#
r# | Int# -> Int
I# Int#
r# Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 -> Ordering
LT
| Int# -> Int
I# Int#
r# Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 -> Ordering
GT
| Int
n1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n2 -> Ordering
LT
| Int
n1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n2 -> Ordering
GT
| Bool
otherwise -> Ordering
EQ
where
ba1# :: ByteArray#
ba1# = ShortText -> ByteArray#
toByteArray# ShortText
t1
ba2# :: ByteArray#
ba2# = ShortText -> ByteArray#
toByteArray# ShortText
t2
!n1 :: Int
n1 = ShortText -> Int
toLength ShortText
t1
!n2 :: Int
n2 = ShortText -> Int
toLength ShortText
t2
!n :: Int
n@(I# Int#
n#) = Int
n1 Int -> Int -> Int
forall a. Ord a => a -> a -> a
`min` Int
n2
instance Show ShortText where
showsPrec :: Int -> ShortText -> ShowS
showsPrec Int
p (ShortText ShortByteString
b) = Int -> String -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
p (TextEncoding -> ShortByteString -> String
decodeStringShort' TextEncoding
utf8 ShortByteString
b)
show :: ShortText -> String
show (ShortText ShortByteString
b) = ShowS
forall a. Show a => a -> String
show (TextEncoding -> ShortByteString -> String
decodeStringShort' TextEncoding
utf8 ShortByteString
b)
instance Read ShortText where
readsPrec :: Int -> ReadS ShortText
readsPrec Int
p = ((String, String) -> (ShortText, String))
-> [(String, String)] -> [(ShortText, String)]
forall a b. (a -> b) -> [a] -> [b]
map (\(String
x,String
s) -> (ShortByteString -> ShortText
ShortText (ShortByteString -> ShortText) -> ShortByteString -> ShortText
forall a b. (a -> b) -> a -> b
$ TextEncoding -> String -> ShortByteString
encodeStringShort TextEncoding
utf8 String
x,String
s)) ([(String, String)] -> [(ShortText, String)])
-> (String -> [(String, String)]) -> ReadS ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> [(String, String)]
forall a. Read a => Int -> ReadS a
readsPrec Int
p
instance PrintfArg ShortText where
formatArg :: ShortText -> FieldFormatter
formatArg ShortText
txt = String -> FieldFormatter
forall a. IsChar a => [a] -> FieldFormatter
formatString (String -> FieldFormatter) -> String -> FieldFormatter
forall a b. (a -> b) -> a -> b
$ ShortText -> String
toString ShortText
txt
instance Binary ShortText where
put :: ShortText -> Put
put = ShortByteString -> Put
forall t. Binary t => t -> Put
put (ShortByteString -> Put)
-> (ShortText -> ShortByteString) -> ShortText -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
toShortByteString
get :: Get ShortText
get = do
ShortByteString
sbs <- Get ShortByteString
forall t. Binary t => Get t
get
case ShortByteString -> Maybe ShortText
fromShortByteString ShortByteString
sbs of
Maybe ShortText
Nothing -> String -> Get ShortText
forall a. String -> Get a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Binary.get(ShortText): Invalid UTF-8 stream"
Just ShortText
st -> ShortText -> Get ShortText
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return ShortText
st
instance TH.Lift ShortText where
lift :: forall (m :: * -> *). Quote m => ShortText -> m Exp
lift ShortText
t = [| fromString s |]
where s :: String
s = ShortText -> String
toString ShortText
t
#if MIN_VERSION_template_haskell(2,17,0)
liftTyped :: forall (m :: * -> *). Quote m => ShortText -> Code m ShortText
liftTyped = m Exp -> Code m ShortText
forall a (m :: * -> *). Quote m => m Exp -> Code m a
TH.unsafeCodeCoerce (m Exp -> Code m ShortText)
-> (ShortText -> m Exp) -> ShortText -> Code m ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> m Exp
forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
forall (m :: * -> *). Quote m => ShortText -> m Exp
TH.lift
#elif MIN_VERSION_template_haskell(2,16,0)
liftTyped = TH.unsafeTExpCoerce . TH.lift
#endif
null :: ShortText -> Bool
null :: ShortText -> Bool
null = ShortByteString -> Bool
BSS.null (ShortByteString -> Bool)
-> (ShortText -> ShortByteString) -> ShortText -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
toShortByteString
length :: ShortText -> Int
length :: ShortText -> Int
length ShortText
st = CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CSize -> Int) -> CSize -> Int
forall a b. (a -> b) -> a -> b
$ IO CSize -> CSize
forall a. IO a -> a
unsafeDupablePerformIO (ByteArray# -> CSize -> IO CSize
c_text_short_length (ShortText -> ByteArray#
toByteArray# ShortText
st) (ShortText -> CSize
toCSize ShortText
st))
foreign import ccall unsafe "hs_text_short_length" c_text_short_length :: ByteArray# -> CSize -> IO CSize
isAscii :: ShortText -> Bool
isAscii :: ShortText -> Bool
isAscii ShortText
st = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) (CInt -> Bool) -> CInt -> Bool
forall a b. (a -> b) -> a -> b
$ IO CInt -> CInt
forall a. IO a -> a
unsafeDupablePerformIO (ByteArray# -> CSize -> IO CInt
c_text_short_is_ascii (ShortText -> ByteArray#
toByteArray# ShortText
st) CSize
sz)
where
sz :: CSize
sz = ShortText -> CSize
toCSize ShortText
st
foreign import ccall unsafe "hs_text_short_is_ascii" c_text_short_is_ascii :: ByteArray# -> CSize -> IO CInt
all :: (Char -> Bool) -> ShortText -> Bool
all :: (Char -> Bool) -> ShortText -> Bool
all Char -> Bool
p ShortText
st = Maybe B -> Bool
forall a. Maybe a -> Bool
isNothing ((Char -> Bool) -> ShortText -> B -> Maybe B
findOfs (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) ShortText
st (Int -> B
B Int
0))
find :: (Char -> Bool) -> ShortText -> Maybe Char
find :: (Char -> Bool) -> ShortText -> Maybe Char
find Char -> Bool
p ShortText
st = B -> Maybe Char
go B
0
where
go :: B -> Maybe Char
go !B
ofs
| B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
sz = Maybe Char
forall a. Maybe a
Nothing
| Bool
otherwise = let (Char
c,B
ofs') = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs
in Char
c Char -> Maybe Char -> Maybe Char
forall a b. a -> b -> b
`seq` B
ofs' B -> Maybe Char -> Maybe Char
forall a b. a -> b -> b
`seq`
if Char -> Bool
p Char
c
then Char -> Maybe Char
forall a. a -> Maybe a
Just Char
c
else B -> Maybe Char
go B
ofs'
!sz :: B
sz = ShortText -> B
toB ShortText
st
findIndex :: (Char -> Bool) -> ShortText -> Maybe Int
findIndex :: (Char -> Bool) -> ShortText -> Maybe Int
findIndex Char -> Bool
p ShortText
st = B -> Int -> Maybe Int
go B
0 Int
0
where
go :: B -> Int -> Maybe Int
go !B
ofs !Int
i
| B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
sz = Maybe Int
forall a. Maybe a
Nothing
| Bool
otherwise = let (Char
c,B
ofs') = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs
in Char
c Char -> Maybe Int -> Maybe Int
forall a b. a -> b -> b
`seq` B
ofs' B -> Maybe Int -> Maybe Int
forall a b. a -> b -> b
`seq`
if Char -> Bool
p Char
c
then Int -> Maybe Int
forall a. a -> Maybe a
Just Int
i
else B -> Int -> Maybe Int
go B
ofs' (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
!sz :: B
sz = ShortText -> B
toB ShortText
st
split :: (Char -> Bool) -> ShortText -> [ShortText]
split :: (Char -> Bool) -> ShortText -> [ShortText]
split Char -> Bool
p ShortText
st0 = B -> [ShortText]
go B
0
where
go :: B -> [ShortText]
go !B
ofs0 = case (Char -> Bool) -> ShortText -> B -> Maybe (B, B)
findOfs' Char -> Bool
p ShortText
st0 B
ofs0 of
Just (B
ofs1,B
ofs2) -> ShortText -> B -> B -> ShortText
slice ShortText
st0 B
ofs0 (B
ofs1B -> B -> B
forall a. Num a => a -> a -> a
-B
ofs0) ShortText -> [ShortText] -> [ShortText]
forall a. a -> [a] -> [a]
: B -> [ShortText]
go B
ofs2
Maybe (B, B)
Nothing
| B
ofs0 B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
0 -> ShortText
st0 ShortText -> [ShortText] -> [ShortText]
forall a. a -> [a] -> [a]
: []
| Bool
otherwise -> ShortText -> B -> B -> ShortText
slice ShortText
st0 B
ofs0 (B
maxOfsB -> B -> B
forall a. Num a => a -> a -> a
-B
ofs0) ShortText -> [ShortText] -> [ShortText]
forall a. a -> [a] -> [a]
: []
!maxOfs :: B
maxOfs = ShortText -> B
toB ShortText
st0
{-# INLINE findOfs #-}
findOfs :: (Char -> Bool) -> ShortText -> B -> Maybe B
findOfs :: (Char -> Bool) -> ShortText -> B -> Maybe B
findOfs Char -> Bool
p ShortText
st = B -> Maybe B
go
where
go :: B -> Maybe B
go :: B -> Maybe B
go !B
ofs | B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
sz = Maybe B
forall a. Maybe a
Nothing
go !B
ofs | Char -> Bool
p Char
c = B -> Maybe B
forall a. a -> Maybe a
Just B
ofs
| Bool
otherwise = B -> Maybe B
go B
ofs'
where
(Char
c,B
ofs') = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs
!sz :: B
sz = ShortText -> B
toB ShortText
st
{-# INLINE findOfs' #-}
findOfs' :: (Char -> Bool) -> ShortText -> B -> Maybe (B,B)
findOfs' :: (Char -> Bool) -> ShortText -> B -> Maybe (B, B)
findOfs' Char -> Bool
p ShortText
st = B -> Maybe (B, B)
go
where
go :: B -> Maybe (B,B)
go :: B -> Maybe (B, B)
go !B
ofs | B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
sz = Maybe (B, B)
forall a. Maybe a
Nothing
go !B
ofs | Char -> Bool
p Char
c = (B, B) -> Maybe (B, B)
forall a. a -> Maybe a
Just (B
ofs,B
ofs')
| Bool
otherwise = B -> Maybe (B, B)
go B
ofs'
where
(Char
c,B
ofs') = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs
!sz :: B
sz = ShortText -> B
toB ShortText
st
{-# INLINE findOfsRev #-}
findOfsRev :: (Char -> Bool) -> ShortText -> B -> Maybe B
findOfsRev :: (Char -> Bool) -> ShortText -> B -> Maybe B
findOfsRev Char -> Bool
p ShortText
st = B -> Maybe B
go
where
go :: B -> Maybe B
go (B Int
0) = Maybe B
forall a. Maybe a
Nothing
go !B
ofs
| Char -> Bool
p (CP -> Char
cp2ch CP
cp) = B -> Maybe B
forall a. a -> Maybe a
Just B
ofs
| Bool
otherwise = B -> Maybe B
go (B
ofsB -> B -> B
forall a. Num a => a -> a -> a
-CP -> B
cpLen CP
cp)
where
!cp :: CP
cp = ShortText -> B -> CP
readCodePointRev ShortText
st B
ofs
span :: (Char -> Bool) -> ShortText -> (ShortText,ShortText)
span :: (Char -> Bool) -> ShortText -> (ShortText, ShortText)
span Char -> Bool
p ShortText
st
| Just B
ofs <- (Char -> Bool) -> ShortText -> B -> Maybe B
findOfs (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) ShortText
st (Int -> B
B Int
0) = B -> ShortText -> (ShortText, ShortText)
splitAtOfs B
ofs ShortText
st
| Bool
otherwise = (ShortText
st,ShortText
forall a. Monoid a => a
mempty)
spanEnd :: (Char -> Bool) -> ShortText -> (ShortText,ShortText)
spanEnd :: (Char -> Bool) -> ShortText -> (ShortText, ShortText)
spanEnd Char -> Bool
p ShortText
st
| Just B
ofs <- (Char -> Bool) -> ShortText -> B -> Maybe B
findOfsRev (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) ShortText
st (ShortText -> B
toB ShortText
st) = B -> ShortText -> (ShortText, ShortText)
splitAtOfs B
ofs ShortText
st
| Bool
otherwise = (ShortText
forall a. Monoid a => a
mempty,ShortText
st)
toCSize :: ShortText -> CSize
toCSize :: ShortText -> CSize
toCSize = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> (ShortText -> Int) -> ShortText -> CSize
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> Int
BSS.length (ShortByteString -> Int)
-> (ShortText -> ShortByteString) -> ShortText -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
toShortByteString
toB :: ShortText -> B
toB :: ShortText -> B
toB = Int -> B
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> B) -> (ShortText -> Int) -> ShortText -> B
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> Int
BSS.length (ShortByteString -> Int)
-> (ShortText -> ShortByteString) -> ShortText -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
toShortByteString
toLength :: ShortText -> Int
toLength :: ShortText -> Int
toLength ShortText
st = Int# -> Int
I# (ShortText -> Int#
toLength# ShortText
st)
toLength# :: ShortText -> Int#
toLength# :: ShortText -> Int#
toLength# ShortText
st = ByteArray# -> Int#
GHC.Exts.sizeofByteArray# (ShortText -> ByteArray#
toByteArray# ShortText
st)
toByteArray# :: ShortText -> ByteArray#
toByteArray# :: ShortText -> ByteArray#
toByteArray# (ShortText (BSSI.SBS ByteArray#
ba#)) = ByteArray#
ba#
toShortByteString :: ShortText -> ShortByteString
toShortByteString :: ShortText -> ShortByteString
toShortByteString (ShortText ShortByteString
b) = ShortByteString
b
toByteString :: ShortText -> BS.ByteString
toByteString :: ShortText -> ByteString
toByteString = ShortByteString -> ByteString
BSS.fromShort (ShortByteString -> ByteString)
-> (ShortText -> ShortByteString) -> ShortText -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
toShortByteString
toBuilder :: ShortText -> BB.Builder
toBuilder :: ShortText -> Builder
toBuilder = ShortByteString -> Builder
BB.shortByteString (ShortByteString -> Builder)
-> (ShortText -> ShortByteString) -> ShortText -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
toShortByteString
toString :: ShortText -> String
toString :: ShortText -> String
toString ShortText
st = B -> String
go B
0
where
go :: B -> String
go !B
ofs
| B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
sz = []
| Bool
otherwise = let (Char
c,B
ofs') = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs
in Char
c Char -> ShowS
forall a b. a -> b -> b
`seq` B
ofs' B -> ShowS
forall a b. a -> b -> b
`seq` (Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: B -> String
go B
ofs')
!sz :: B
sz = ShortText -> B
toB ShortText
st
foldl :: (a -> Char -> a) -> a -> ShortText -> a
foldl :: forall a. (a -> Char -> a) -> a -> ShortText -> a
foldl a -> Char -> a
f a
z ShortText
st = B -> a -> a
go B
0 a
z
where
go :: B -> a -> a
go !B
ofs a
acc
| B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
sz = a
acc
| Bool
otherwise = let (Char
c,B
ofs') = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs
in Char
c Char -> a -> a
forall a b. a -> b -> b
`seq` B
ofs' B -> a -> a
forall a b. a -> b -> b
`seq` B -> a -> a
go B
ofs' (a -> Char -> a
f a
acc Char
c)
!sz :: B
sz = ShortText -> B
toB ShortText
st
foldl1 :: (Char -> Char -> Char) -> ShortText -> Char
foldl1 :: (Char -> Char -> Char) -> ShortText -> Char
foldl1 Char -> Char -> Char
f ShortText
st
| B
sz B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
0 = String -> Char
forall a. (?callStack::CallStack) => String -> a
error String
"foldl1: empty ShortText"
| Bool
otherwise = B -> Char -> Char
go B
c0sz Char
c0
where
go :: B -> Char -> Char
go !B
ofs Char
acc
| B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
sz = Char
acc
| Bool
otherwise = let (Char
c,B
ofs') = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs
in Char
c Char -> Char -> Char
forall a b. a -> b -> b
`seq` B
ofs' B -> Char -> Char
forall a b. a -> b -> b
`seq` B -> Char -> Char
go B
ofs' (Char -> Char -> Char
f Char
acc Char
c)
!sz :: B
sz = ShortText -> B
toB ShortText
st
(Char
c0,B
c0sz) = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st (Int -> B
B Int
0)
foldl' :: (a -> Char -> a) -> a -> ShortText -> a
foldl' :: forall a. (a -> Char -> a) -> a -> ShortText -> a
foldl' a -> Char -> a
f !a
z ShortText
st = B -> a -> a
go B
0 a
z
where
go :: B -> a -> a
go !B
ofs !a
acc
| B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
sz = a
acc
| Bool
otherwise = let (Char
c,B
ofs') = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs
in Char
c Char -> a -> a
forall a b. a -> b -> b
`seq` B
ofs' B -> a -> a
forall a b. a -> b -> b
`seq` B -> a -> a
go B
ofs' (a -> Char -> a
f a
acc Char
c)
!sz :: B
sz = ShortText -> B
toB ShortText
st
foldl1' :: (Char -> Char -> Char) -> ShortText -> Char
foldl1' :: (Char -> Char -> Char) -> ShortText -> Char
foldl1' Char -> Char -> Char
f ShortText
st
| B
sz B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
0 = String -> Char
forall a. (?callStack::CallStack) => String -> a
error String
"foldl1: empty ShortText"
| Bool
otherwise = B -> Char -> Char
go B
c0sz Char
c0
where
go :: B -> Char -> Char
go !B
ofs !Char
acc
| B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
sz = Char
acc
| Bool
otherwise = let (Char
c,B
ofs') = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs
in Char
c Char -> Char -> Char
forall a b. a -> b -> b
`seq` B
ofs' B -> Char -> Char
forall a b. a -> b -> b
`seq` B -> Char -> Char
go B
ofs' (Char -> Char -> Char
f Char
acc Char
c)
!sz :: B
sz = ShortText -> B
toB ShortText
st
(Char
c0,B
c0sz) = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st (Int -> B
B Int
0)
foldr :: (Char -> a -> a) -> a -> ShortText -> a
foldr :: forall a. (Char -> a -> a) -> a -> ShortText -> a
foldr Char -> a -> a
f a
z ShortText
st = B -> a
go B
0
where
go :: B -> a
go !B
ofs
| B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
sz = a
z
| Bool
otherwise = let (Char
c,B
ofs') = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs
in Char
c Char -> a -> a
forall a b. a -> b -> b
`seq` B
ofs' B -> a -> a
forall a b. a -> b -> b
`seq` Char -> a -> a
f Char
c (B -> a
go B
ofs')
!sz :: B
sz = ShortText -> B
toB ShortText
st
foldr1 :: (Char -> Char -> Char) -> ShortText -> Char
foldr1 :: (Char -> Char -> Char) -> ShortText -> Char
foldr1 Char -> Char -> Char
f ShortText
st
| B
sz B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
0 = String -> Char
forall a. (?callStack::CallStack) => String -> a
error String
"foldr1: empty ShortText"
| Bool
otherwise = B -> Char
go B
0
where
go :: B -> Char
go !B
ofs = let (Char
c,B
ofs') = ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs
in Char
c Char -> Char -> Char
forall a b. a -> b -> b
`seq` B
ofs' B -> Char -> Char
forall a b. a -> b -> b
`seq`
(if B
ofs' B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
sz then Char
c else Char -> Char -> Char
f Char
c (B -> Char
go B
ofs'))
!sz :: B
sz = ShortText -> B
toB ShortText
st
toText :: ShortText -> T.Text
#if MIN_VERSION_text(2,0,0)
toText :: ShortText -> Text
toText (ShortText (BSSI.SBS ByteArray#
ba)) = Array -> Int -> Int -> Text
TI.Text (ByteArray# -> Array
TA.ByteArray ByteArray#
ba) Int
0 (Int# -> Int
I# (ByteArray# -> Int#
GHC.Exts.sizeofByteArray# ByteArray#
ba))
#else
toText = T.decodeUtf8 . toByteString
#endif
fromString :: String -> ShortText
fromString :: String -> ShortText
fromString String
s = case String
s of
[] -> ShortText
forall a. Monoid a => a
mempty
[Char
c] -> Char -> ShortText
singleton (Char -> ShortText) -> Char -> ShortText
forall a b. (a -> b) -> a -> b
$ Char -> Char
r Char
c
String
_ -> ShortByteString -> ShortText
ShortText (ShortByteString -> ShortText)
-> (String -> ShortByteString) -> String -> ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextEncoding -> String -> ShortByteString
encodeStringShort TextEncoding
utf8 (String -> ShortByteString) -> ShowS -> String -> ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
r (String -> ShortText) -> String -> ShortText
forall a b. (a -> b) -> a -> b
$ String
s
where
r :: Char -> Char
r Char
c | Int -> Bool
forall i. (Num i, Bits i) => i -> Bool
isSurr (Char -> Int
ord Char
c) = Char
'\xFFFD'
| Bool
otherwise = Char
c
fromText :: T.Text -> ShortText
#if MIN_VERSION_text(2,0,0)
fromText :: Text -> ShortText
fromText (TI.Text (TA.ByteArray ByteArray#
ba) Int
off Int
len) =
ShortByteString -> ShortText
ShortText (ByteArray# -> ShortByteString
BSSI.SBS (case Array -> Int -> Int -> Array
sliceByteArray (ByteArray# -> Array
TA.ByteArray ByteArray#
ba) Int
off Int
len of TA.ByteArray ByteArray#
ba' -> ByteArray#
ba'))
sliceByteArray :: TA.Array -> Int -> Int -> TA.Array
sliceByteArray :: Array -> Int -> Int -> Array
sliceByteArray ta :: Array
ta@(TA.ByteArray ByteArray#
ba) Int
0 Int
len
| Int
len Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int# -> Int
I# (ByteArray# -> Int#
GHC.Exts.sizeofByteArray# ByteArray#
ba)
= Array
ta
sliceByteArray Array
ta Int
off Int
len = (forall s. ST s (MArray s)) -> Array
TA.run ((forall s. ST s (MArray s)) -> Array)
-> (forall s. ST s (MArray s)) -> Array
forall a b. (a -> b) -> a -> b
$ do
MArray s
ma <- Int -> ST s (MArray s)
forall s. Int -> ST s (MArray s)
TA.new Int
len
Int -> MArray s -> Int -> Array -> Int -> ST s ()
forall s. Int -> MArray s -> Int -> Array -> Int -> ST s ()
TA.copyI Int
len MArray s
ma Int
0 Array
ta Int
off
MArray s -> ST s (MArray s)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return MArray s
ma
#else
fromText = fromByteStringUnsafe . T.encodeUtf8
#endif
fromShortByteString :: ShortByteString -> Maybe ShortText
fromShortByteString :: ShortByteString -> Maybe ShortText
fromShortByteString ShortByteString
sbs
| ShortText -> Bool
isValidUtf8 ShortText
st = ShortText -> Maybe ShortText
forall a. a -> Maybe a
Just ShortText
st
| Bool
otherwise = Maybe ShortText
forall a. Maybe a
Nothing
where
st :: ShortText
st = ShortByteString -> ShortText
ShortText ShortByteString
sbs
fromShortByteStringUnsafe :: ShortByteString -> ShortText
fromShortByteStringUnsafe :: ShortByteString -> ShortText
fromShortByteStringUnsafe = ShortByteString -> ShortText
ShortText
fromByteString :: BS.ByteString -> Maybe ShortText
fromByteString :: ByteString -> Maybe ShortText
fromByteString = ShortByteString -> Maybe ShortText
fromShortByteString (ShortByteString -> Maybe ShortText)
-> (ByteString -> ShortByteString) -> ByteString -> Maybe ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ShortByteString
BSS.toShort
fromByteStringUnsafe :: BS.ByteString -> ShortText
fromByteStringUnsafe :: ByteString -> ShortText
fromByteStringUnsafe = ShortByteString -> ShortText
ShortText (ShortByteString -> ShortText)
-> (ByteString -> ShortByteString) -> ByteString -> ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ShortByteString
BSS.toShort
encodeString :: TextEncoding -> String -> BS.ByteString
encodeString :: TextEncoding -> String -> ByteString
encodeString TextEncoding
te String
str = IO ByteString -> ByteString
forall a. IO a -> a
unsafePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ TextEncoding
-> String -> (CStringLen -> IO ByteString) -> IO ByteString
forall a. TextEncoding -> String -> (CStringLen -> IO a) -> IO a
GHC.withCStringLen TextEncoding
te String
str CStringLen -> IO ByteString
BS.packCStringLen
decodeString' :: TextEncoding -> BS.ByteString -> String
decodeString' :: TextEncoding -> ByteString -> String
decodeString' TextEncoding
te ByteString
bs = IO String -> String
forall a. IO a -> a
unsafePerformIO (IO String -> String) -> IO String -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> (CStringLen -> IO String) -> IO String
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
bs (TextEncoding -> CStringLen -> IO String
GHC.peekCStringLen TextEncoding
te)
decodeStringShort' :: TextEncoding -> ShortByteString -> String
decodeStringShort' :: TextEncoding -> ShortByteString -> String
decodeStringShort' TextEncoding
te = TextEncoding -> ByteString -> String
decodeString' TextEncoding
te (ByteString -> String)
-> (ShortByteString -> ByteString) -> ShortByteString -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ByteString
BSS.fromShort
encodeStringShort :: TextEncoding -> String -> BSS.ShortByteString
encodeStringShort :: TextEncoding -> String -> ShortByteString
encodeStringShort TextEncoding
te = ByteString -> ShortByteString
BSS.toShort (ByteString -> ShortByteString)
-> (String -> ByteString) -> String -> ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextEncoding -> String -> ByteString
encodeString TextEncoding
te
isValidUtf8 :: ShortText -> Bool
isValidUtf8 :: ShortText -> Bool
isValidUtf8 ShortText
st = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
==CInt
0) (CInt -> Bool) -> CInt -> Bool
forall a b. (a -> b) -> a -> b
$ IO CInt -> CInt
forall a. IO a -> a
unsafeDupablePerformIO (ByteArray# -> CSize -> IO CInt
c_text_short_is_valid_utf8 (ShortText -> ByteArray#
toByteArray# ShortText
st) (ShortText -> CSize
toCSize ShortText
st))
type CCodePoint = Word
foreign import ccall unsafe "hs_text_short_is_valid_utf8" c_text_short_is_valid_utf8 :: ByteArray# -> CSize -> IO CInt
foreign import ccall unsafe "hs_text_short_index_cp" c_text_short_index :: ByteArray# -> CSize -> CSize -> IO CCodePoint
indexMaybe :: ShortText -> Int -> Maybe Char
indexMaybe :: ShortText -> Int -> Maybe Char
indexMaybe ShortText
st Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = Maybe Char
forall a. Maybe a
Nothing
| Bool
otherwise = CP -> Maybe Char
cp2chSafe CP
cp
where
cp :: CP
cp = Word -> CP
CP (Word -> CP) -> Word -> CP
forall a b. (a -> b) -> a -> b
$ IO Word -> Word
forall a. IO a -> a
unsafeDupablePerformIO (ByteArray# -> CSize -> CSize -> IO Word
c_text_short_index (ShortText -> ByteArray#
toByteArray# ShortText
st) (ShortText -> CSize
toCSize ShortText
st) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i))
indexEndMaybe :: ShortText -> Int -> Maybe Char
indexEndMaybe :: ShortText -> Int -> Maybe Char
indexEndMaybe ShortText
st Int
i
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = Maybe Char
forall a. Maybe a
Nothing
| Bool
otherwise = CP -> Maybe Char
cp2chSafe CP
cp
where
cp :: CP
cp = Word -> CP
CP (Word -> CP) -> Word -> CP
forall a b. (a -> b) -> a -> b
$ IO Word -> Word
forall a. IO a -> a
unsafeDupablePerformIO (ByteArray# -> CSize -> CSize -> IO Word
c_text_short_index_rev (ShortText -> ByteArray#
toByteArray# ShortText
st) (ShortText -> CSize
toCSize ShortText
st) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i))
foreign import ccall unsafe "hs_text_short_index_cp_rev" c_text_short_index_rev :: ByteArray# -> CSize -> CSize -> IO CCodePoint
splitAt :: Int -> ShortText -> (ShortText,ShortText)
splitAt :: Int -> ShortText -> (ShortText, ShortText)
splitAt Int
i ShortText
st
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = (ShortText
forall a. Monoid a => a
mempty,ShortText
st)
| Bool
otherwise = B -> ShortText -> (ShortText, ShortText)
splitAtOfs B
ofs ShortText
st
where
ofs :: B
ofs = CSize -> B
csizeToB (CSize -> B) -> CSize -> B
forall a b. (a -> b) -> a -> b
$
IO CSize -> CSize
forall a. IO a -> a
unsafeDupablePerformIO (ByteArray# -> CSize -> CSize -> IO CSize
c_text_short_index_ofs (ShortText -> ByteArray#
toByteArray# ShortText
st) CSize
stsz (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i))
stsz :: CSize
stsz = ShortText -> CSize
toCSize ShortText
st
splitAtEnd :: Int -> ShortText -> (ShortText,ShortText)
splitAtEnd :: Int -> ShortText -> (ShortText, ShortText)
splitAtEnd Int
i ShortText
st
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = (ShortText
st,ShortText
forall a. Monoid a => a
mempty)
| B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
stsz = (ShortText
forall a. Monoid a => a
mempty,ShortText
st)
| Bool
otherwise = B -> ShortText -> (ShortText, ShortText)
splitAtOfs B
ofs ShortText
st
where
ofs :: B
ofs = CSize -> B
csizeToB (CSize -> B) -> CSize -> B
forall a b. (a -> b) -> a -> b
$
IO CSize -> CSize
forall a. IO a -> a
unsafeDupablePerformIO (ByteArray# -> CSize -> CSize -> IO CSize
c_text_short_index_ofs_rev (ShortText -> ByteArray#
toByteArray# ShortText
st) (ShortText -> CSize
toCSize ShortText
st) (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)))
stsz :: B
stsz = ShortText -> B
toB ShortText
st
{-# INLINE splitAtOfs #-}
splitAtOfs :: B -> ShortText -> (ShortText,ShortText)
splitAtOfs :: B -> ShortText -> (ShortText, ShortText)
splitAtOfs B
ofs ShortText
st
| B
ofs B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
0 = (ShortText
forall a. Monoid a => a
mempty,ShortText
st)
| B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
stsz = (ShortText
st,ShortText
forall a. Monoid a => a
mempty)
| Bool
otherwise = (ShortText -> B -> B -> ShortText
slice ShortText
st B
0 B
ofs, ShortText -> B -> B -> ShortText
slice ShortText
st B
ofs (B
stszB -> B -> B
forall a. Num a => a -> a -> a
-B
ofs))
where
!stsz :: B
stsz = ShortText -> B
toB ShortText
st
foreign import ccall unsafe "hs_text_short_index_ofs" c_text_short_index_ofs :: ByteArray# -> CSize -> CSize -> IO CSize
foreign import ccall unsafe "hs_text_short_index_ofs_rev" c_text_short_index_ofs_rev :: ByteArray# -> CSize -> CSize -> IO CSize
uncons :: ShortText -> Maybe (Char,ShortText)
uncons :: ShortText -> Maybe (Char, ShortText)
uncons ShortText
st
| ShortText -> Bool
null ShortText
st = Maybe (Char, ShortText)
forall a. Maybe a
Nothing
| B
len2 B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
0 = (Char, ShortText) -> Maybe (Char, ShortText)
forall a. a -> Maybe a
Just (Char
c0, ShortText
forall a. Monoid a => a
mempty)
| Bool
otherwise = (Char, ShortText) -> Maybe (Char, ShortText)
forall a. a -> Maybe a
Just (Char
c0, ShortText -> B -> B -> ShortText
slice ShortText
st B
ofs B
len2)
where
c0 :: Char
c0 = CP -> Char
cp2ch CP
cp0
cp0 :: CP
cp0 = ShortText -> B -> CP
readCodePoint ShortText
st B
0
ofs :: B
ofs = CP -> B
cpLen CP
cp0
len2 :: B
len2 = ShortText -> B
toB ShortText
st B -> B -> B
forall a. Num a => a -> a -> a
- B
ofs
unsnoc :: ShortText -> Maybe (ShortText,Char)
unsnoc :: ShortText -> Maybe (ShortText, Char)
unsnoc ShortText
st
| ShortText -> Bool
null ShortText
st = Maybe (ShortText, Char)
forall a. Maybe a
Nothing
| B
len1 B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
0 = (ShortText, Char) -> Maybe (ShortText, Char)
forall a. a -> Maybe a
Just (ShortText
forall a. Monoid a => a
mempty, Char
c0)
| Bool
otherwise = (ShortText, Char) -> Maybe (ShortText, Char)
forall a. a -> Maybe a
Just (ShortText -> B -> B -> ShortText
slice ShortText
st B
0 B
len1, Char
c0)
where
c0 :: Char
c0 = CP -> Char
cp2ch CP
cp0
cp0 :: CP
cp0 = ShortText -> B -> CP
readCodePointRev ShortText
st B
stsz
stsz :: B
stsz = ShortText -> B
toB ShortText
st
len1 :: B
len1 = B
stsz B -> B -> B
forall a. Num a => a -> a -> a
- CP -> B
cpLen CP
cp0
isPrefixOf :: ShortText -> ShortText -> Bool
isPrefixOf :: ShortText -> ShortText -> Bool
isPrefixOf ShortText
x ShortText
y
| Int
lx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
ly = Bool
False
| Int
lx Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Bool
True
| Bool
otherwise = case ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
PrimOps.compareByteArrays# (ShortText -> ByteArray#
toByteArray# ShortText
x) Int#
0# (ShortText -> ByteArray#
toByteArray# ShortText
y) Int#
0# Int#
n# of
Int#
0# -> Bool
True
Int#
_ -> Bool
False
where
!lx :: Int
lx@(I# Int#
n#) = ShortText -> Int
toLength ShortText
x
!ly :: Int
ly = ShortText -> Int
toLength ShortText
y
stripPrefix :: ShortText -> ShortText -> Maybe ShortText
stripPrefix :: ShortText -> ShortText -> Maybe ShortText
stripPrefix ShortText
pfx ShortText
t
| ShortText -> ShortText -> Bool
isPrefixOf ShortText
pfx ShortText
t = ShortText -> Maybe ShortText
forall a. a -> Maybe a
Just (ShortText -> Maybe ShortText) -> ShortText -> Maybe ShortText
forall a b. (a -> b) -> a -> b
$! (ShortText, ShortText) -> ShortText
forall a b. (a, b) -> b
snd (B -> ShortText -> (ShortText, ShortText)
splitAtOfs (ShortText -> B
toB ShortText
pfx) ShortText
t)
| Bool
otherwise = Maybe ShortText
forall a. Maybe a
Nothing
isSuffixOf :: ShortText -> ShortText -> Bool
isSuffixOf :: ShortText -> ShortText -> Bool
isSuffixOf ShortText
x ShortText
y
| Int
lx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
ly = Bool
False
| Int
lx Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Bool
True
| Bool
otherwise = case ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int#
PrimOps.compareByteArrays# (ShortText -> ByteArray#
toByteArray# ShortText
x) Int#
0# (ShortText -> ByteArray#
toByteArray# ShortText
y) Int#
ofs2# Int#
n# of
Int#
0# -> Bool
True
Int#
_ -> Bool
False
where
!(I# Int#
ofs2#) = Int
ly Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lx
!lx :: Int
lx@(I# Int#
n#) = ShortText -> Int
toLength ShortText
x
!ly :: Int
ly = ShortText -> Int
toLength ShortText
y
stripSuffix :: ShortText -> ShortText -> Maybe ShortText
stripSuffix :: ShortText -> ShortText -> Maybe ShortText
stripSuffix ShortText
sfx ShortText
t
| ShortText -> ShortText -> Bool
isSuffixOf ShortText
sfx ShortText
t = ShortText -> Maybe ShortText
forall a. a -> Maybe a
Just (ShortText -> Maybe ShortText) -> ShortText -> Maybe ShortText
forall a b. (a -> b) -> a -> b
$! (ShortText, ShortText) -> ShortText
forall a b. (a, b) -> a
fst (B -> ShortText -> (ShortText, ShortText)
splitAtOfs B
pfxLen ShortText
t)
| Bool
otherwise = Maybe ShortText
forall a. Maybe a
Nothing
where
pfxLen :: B
pfxLen = ShortText -> B
toB ShortText
t B -> B -> B
forall a. Num a => a -> a -> a
- ShortText -> B
toB ShortText
sfx
intersperse :: Char -> ShortText -> ShortText
intersperse :: Char -> ShortText -> ShortText
intersperse Char
c ShortText
st
| ShortText -> Bool
null ShortText
st = ShortText
forall a. Monoid a => a
mempty
| Int
sn Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = ShortText
st
| Bool
otherwise = B -> (forall s. MBA s -> ST s ()) -> ShortText
create B
newsz ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> do
let !cp0 :: CP
cp0 = ShortText -> B -> CP
readCodePoint ShortText
st B
0
!cp0sz :: B
cp0sz = CP -> B
cpLen CP
cp0
B -> MBA s -> B -> CP -> ST s ()
forall s. B -> MBA s -> B -> CP -> ST s ()
writeCodePointN B
cp0sz MBA s
mba B
0 CP
cp0
MBA s -> Int -> B -> B -> ST s ()
forall s. MBA s -> Int -> B -> B -> ST s ()
go MBA s
mba (Int
sn Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) B
cp0sz B
cp0sz
where
newsz :: B
newsz = B
ssz B -> B -> B
forall a. Num a => a -> a -> a
+ ((Int
snInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Int -> B -> B
`mulB` B
csz)
ssz :: B
ssz = ShortText -> B
toB ShortText
st
sn :: Int
sn = ShortText -> Int
length ShortText
st
csz :: B
csz = CP -> B
cpLen CP
cp
cp :: CP
cp = Char -> CP
ch2cp Char
c
go :: MBA s -> Int -> B -> B -> ST s ()
go :: forall s. MBA s -> Int -> B -> B -> ST s ()
go MBA s
_ Int
0 !B
_ !B
_ = () -> ST s ()
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
go MBA s
mba Int
n B
ofs B
ofs2 = do
let !cp1 :: CP
cp1 = ShortText -> B -> CP
readCodePoint ShortText
st B
ofs2
!cp1sz :: B
cp1sz = CP -> B
cpLen CP
cp1
B -> MBA s -> B -> CP -> ST s ()
forall s. B -> MBA s -> B -> CP -> ST s ()
writeCodePointN B
csz MBA s
mba B
ofs CP
cp
B -> MBA s -> B -> CP -> ST s ()
forall s. B -> MBA s -> B -> CP -> ST s ()
writeCodePointN B
cp1sz MBA s
mba (B
ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
csz) CP
cp1
MBA s -> Int -> B -> B -> ST s ()
forall s. MBA s -> Int -> B -> B -> ST s ()
go MBA s
mba (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (B
ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
cszB -> B -> B
forall a. Num a => a -> a -> a
+B
cp1sz) (B
ofs2B -> B -> B
forall a. Num a => a -> a -> a
+B
cp1sz)
intercalate :: ShortText -> [ShortText] -> ShortText
intercalate :: ShortText -> [ShortText] -> ShortText
intercalate ShortText
_ [] = ShortText
forall a. Monoid a => a
mempty
intercalate ShortText
_ [ShortText
t] = ShortText
t
intercalate ShortText
sep [ShortText]
ts
| ShortText -> Bool
null ShortText
sep = [ShortText] -> ShortText
forall a. Monoid a => [a] -> a
mconcat [ShortText]
ts
| Bool
otherwise = [ShortText] -> ShortText
forall a. Monoid a => [a] -> a
mconcat (ShortText -> [ShortText] -> [ShortText]
forall a. a -> [a] -> [a]
List.intersperse ShortText
sep [ShortText]
ts)
replicate :: Int -> ShortText -> ShortText
replicate :: Int -> ShortText -> ShortText
replicate Int
n0 ShortText
t
| Int
n0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1 = ShortText
forall a. Monoid a => a
mempty
| ShortText -> Bool
null ShortText
t = ShortText
forall a. Monoid a => a
mempty
| Bool
otherwise = B -> (forall s. MBA s -> ST s ()) -> ShortText
create (Int
n0 Int -> B -> B
`mulB` B
sz) (Int -> MBA s -> ST s ()
forall s. Int -> MBA s -> ST s ()
go Int
0)
where
go :: Int -> MBA s -> ST s ()
go :: forall s. Int -> MBA s -> ST s ()
go Int
j MBA s
mba
| Int
j Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
n0 = () -> ST s ()
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = do
ShortText -> B -> MBA s -> B -> B -> ST s ()
forall s. ShortText -> B -> MBA s -> B -> B -> ST s ()
copyByteArray ShortText
t B
0 MBA s
mba (Int
j Int -> B -> B
`mulB` B
sz) B
sz
Int -> MBA s -> ST s ()
forall s. Int -> MBA s -> ST s ()
go (Int
jInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) MBA s
mba
sz :: B
sz = ShortText -> B
toB ShortText
t
reverse :: ShortText -> ShortText
reverse :: ShortText -> ShortText
reverse ShortText
st
| ShortText -> Bool
null ShortText
st = ShortText
forall a. Monoid a => a
mempty
| Int
sn Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = ShortText
st
| Bool
otherwise = B -> (forall s. MBA s -> ST s ()) -> ShortText
create B
sz ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ Int -> B -> MBA s -> ST s ()
forall s. Int -> B -> MBA s -> ST s ()
go Int
sn B
0
where
sz :: B
sz = ShortText -> B
toB ShortText
st
sn :: Int
sn = ShortText -> Int
length ShortText
st
go :: Int -> B -> MBA s -> ST s ()
go :: forall s. Int -> B -> MBA s -> ST s ()
go Int
0 !B
_ MBA s
_ = () -> ST s ()
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
go Int
i B
ofs MBA s
mba = do
let !cp :: CP
cp = ShortText -> B -> CP
readCodePoint ShortText
st B
ofs
!cpsz :: B
cpsz = CP -> B
cpLen CP
cp
!ofs' :: B
ofs' = B
ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
cpsz
B -> MBA s -> B -> CP -> ST s ()
forall s. B -> MBA s -> B -> CP -> ST s ()
writeCodePointN B
cpsz MBA s
mba (B
sz B -> B -> B
forall a. Num a => a -> a -> a
- B
ofs') CP
cp
Int -> B -> MBA s -> ST s ()
forall s. Int -> B -> MBA s -> ST s ()
go (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) B
ofs' MBA s
mba
filter :: (Char -> Bool) -> ShortText -> ShortText
filter :: (Char -> Bool) -> ShortText -> ShortText
filter Char -> Bool
p ShortText
t
= case (Maybe B
mofs1,Maybe B
mofs2) of
(Maybe B
Nothing, Maybe B
_) -> ShortText
t
(Just B
0, Maybe B
Nothing) -> ShortText
forall a. Monoid a => a
mempty
(Just B
ofs1, Maybe B
Nothing) -> ShortText -> B -> B -> ShortText
slice ShortText
t B
0 B
ofs1
(Just B
ofs1, Just B
ofs2) -> B -> (forall s. MBA s -> ST s B) -> ShortText
createShrink (B
t0szB -> B -> B
forall a. Num a => a -> a -> a
-(B
ofs2B -> B -> B
forall a. Num a => a -> a -> a
-B
ofs1)) ((forall s. MBA s -> ST s B) -> ShortText)
-> (forall s. MBA s -> ST s B) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> do
ShortText -> B -> MBA s -> B -> B -> ST s ()
forall s. ShortText -> B -> MBA s -> B -> B -> ST s ()
copyByteArray ShortText
t B
0 MBA s
mba B
0 B
ofs1
B
t1sz <- MBA s -> B -> B -> ST s B
forall s. MBA s -> B -> B -> ST s B
go MBA s
mba B
ofs2 B
ofs1
B -> ST s B
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return B
t1sz
where
mofs1 :: Maybe B
mofs1 = (Char -> Bool) -> ShortText -> B -> Maybe B
findOfs (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) ShortText
t (Int -> B
B Int
0)
mofs2 :: Maybe B
mofs2 = (Char -> Bool) -> ShortText -> B -> Maybe B
findOfs Char -> Bool
p ShortText
t (B -> Maybe B -> B
forall a. a -> Maybe a -> a
fromMaybe (Int -> B
B Int
0) Maybe B
mofs1)
t0sz :: B
t0sz = ShortText -> B
toB ShortText
t
go :: MBA s -> B -> B -> ST s B
go :: forall s. MBA s -> B -> B -> ST s B
go MBA s
mba !B
t0ofs !B
t1ofs
| B
t0ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
>= B
t0sz = B -> ST s B
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return B
t1ofs
| Bool
otherwise = let !cp :: CP
cp = ShortText -> B -> CP
readCodePoint ShortText
t B
t0ofs
!cpsz :: B
cpsz = CP -> B
cpLen CP
cp
in if Char -> Bool
p (CP -> Char
cp2ch CP
cp)
then B -> MBA s -> B -> CP -> ST s ()
forall s. B -> MBA s -> B -> CP -> ST s ()
writeCodePointN B
cpsz MBA s
mba B
t1ofs CP
cp ST s () -> ST s B -> ST s B
forall a b. ST s a -> ST s b -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
MBA s -> B -> B -> ST s B
forall s. MBA s -> B -> B -> ST s B
go MBA s
mba (B
t0ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
cpsz) (B
t1ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
cpsz)
else MBA s -> B -> B -> ST s B
forall s. MBA s -> B -> B -> ST s B
go MBA s
mba (B
t0ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
cpsz) B
t1ofs
dropAround :: (Char -> Bool) -> ShortText -> ShortText
dropAround :: (Char -> Bool) -> ShortText -> ShortText
dropAround Char -> Bool
p ShortText
t0 = case (Maybe B
mofs1,Maybe B
mofs2) of
(Maybe B
Nothing,Maybe B
_) -> ShortText
forall a. Monoid a => a
mempty
(Just B
ofs1,Just B
ofs2)
| B
ofs1 B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
0, B
ofs2 B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
t0sz -> ShortText
t0
| B
ofs1 B -> B -> Bool
forall a. Ord a => a -> a -> Bool
< B
ofs2 -> B -> (forall s. MBA s -> ST s ()) -> ShortText
create (B
ofs2B -> B -> B
forall a. Num a => a -> a -> a
-B
ofs1) ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> do
ShortText -> B -> MBA s -> B -> B -> ST s ()
forall s. ShortText -> B -> MBA s -> B -> B -> ST s ()
copyByteArray ShortText
t0 B
ofs1 MBA s
mba (Int -> B
B Int
0) (B
ofs2B -> B -> B
forall a. Num a => a -> a -> a
-B
ofs1)
(Maybe B
_,Maybe B
_) -> String -> ShortText
forall a. (?callStack::CallStack) => String -> a
error String
"dropAround: the impossible happened"
where
mofs1 :: Maybe B
mofs1 = (Char -> Bool) -> ShortText -> B -> Maybe B
findOfs (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) ShortText
t0 (Int -> B
B Int
0)
mofs2 :: Maybe B
mofs2 = (Char -> Bool) -> ShortText -> B -> Maybe B
findOfsRev (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
p) ShortText
t0 B
t0sz
t0sz :: B
t0sz = ShortText -> B
toB ShortText
t0
slice :: ShortText -> B -> B -> ShortText
slice :: ShortText -> B -> B -> ShortText
slice ShortText
st B
ofs B
len
| B
ofs B -> B -> Bool
forall a. Ord a => a -> a -> Bool
< B
0 = String -> ShortText
forall a. (?callStack::CallStack) => String -> a
error String
"invalid offset"
| B
len B -> B -> Bool
forall a. Ord a => a -> a -> Bool
< B
0 = String -> ShortText
forall a. (?callStack::CallStack) => String -> a
error String
"invalid length"
| B
len' B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
0 = ShortText
forall a. Monoid a => a
mempty
| Bool
otherwise = B -> (forall s. MBA s -> ST s ()) -> ShortText
create B
len' ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> ShortText -> B -> MBA s -> B -> B -> ST s ()
forall s. ShortText -> B -> MBA s -> B -> B -> ST s ()
copyByteArray ShortText
st B
ofs' MBA s
mba B
0 B
len'
where
len0 :: B
len0 = ShortText -> B
toB ShortText
st
len' :: B
len' = B -> B -> B
forall a. Ord a => a -> a -> a
max B
0 (B -> B -> B
forall a. Ord a => a -> a -> a
min B
len (B
len0B -> B -> B
forall a. Num a => a -> a -> a
-B
ofs))
ofs' :: B
ofs' = B -> B -> B
forall a. Ord a => a -> a -> a
max B
0 B
ofs
newtype B = B { B -> Int
unB :: Int }
deriving (Eq B
Eq B =>
(B -> B -> Ordering)
-> (B -> B -> Bool)
-> (B -> B -> Bool)
-> (B -> B -> Bool)
-> (B -> B -> Bool)
-> (B -> B -> B)
-> (B -> B -> B)
-> Ord B
B -> B -> Bool
B -> B -> Ordering
B -> B -> B
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
$ccompare :: B -> B -> Ordering
compare :: B -> B -> Ordering
$c< :: B -> B -> Bool
< :: B -> B -> Bool
$c<= :: B -> B -> Bool
<= :: B -> B -> Bool
$c> :: B -> B -> Bool
> :: B -> B -> Bool
$c>= :: B -> B -> Bool
>= :: B -> B -> Bool
$cmax :: B -> B -> B
max :: B -> B -> B
$cmin :: B -> B -> B
min :: B -> B -> B
Ord,B -> B -> Bool
(B -> B -> Bool) -> (B -> B -> Bool) -> Eq B
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: B -> B -> Bool
== :: B -> B -> Bool
$c/= :: B -> B -> Bool
/= :: B -> B -> Bool
Eq,Integer -> B
B -> B
B -> B -> B
(B -> B -> B)
-> (B -> B -> B)
-> (B -> B -> B)
-> (B -> B)
-> (B -> B)
-> (B -> B)
-> (Integer -> B)
-> Num B
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: B -> B -> B
+ :: B -> B -> B
$c- :: B -> B -> B
- :: B -> B -> B
$c* :: B -> B -> B
* :: B -> B -> B
$cnegate :: B -> B
negate :: B -> B
$cabs :: B -> B
abs :: B -> B
$csignum :: B -> B
signum :: B -> B
$cfromInteger :: Integer -> B
fromInteger :: Integer -> B
Num)
mulB :: Int -> B -> B
mulB :: Int -> B -> B
mulB Int
n (B Int
b) = Int -> B
B (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
b)
csizeFromB :: B -> CSize
csizeFromB :: B -> CSize
csizeFromB = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> (B -> Int) -> B -> CSize
forall b c a. (b -> c) -> (a -> b) -> a -> c
. B -> Int
unB
csizeToB :: CSize -> B
csizeToB :: CSize -> B
csizeToB = Int -> B
B (Int -> B) -> (CSize -> Int) -> CSize -> B
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
data MBA s = MBA# { forall s. MBA s -> MutableByteArray# s
unMBA# :: MutableByteArray# s }
{-# INLINE create #-}
create :: B -> (forall s. MBA s -> ST s ()) -> ShortText
create :: B -> (forall s. MBA s -> ST s ()) -> ShortText
create B
n forall s. MBA s -> ST s ()
go = (forall s. ST s ShortText) -> ShortText
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s ShortText) -> ShortText)
-> (forall s. ST s ShortText) -> ShortText
forall a b. (a -> b) -> a -> b
$ do
MBA s
mba <- B -> ST s (MBA s)
forall s. B -> ST s (MBA s)
newByteArray B
n
MBA s -> ST s ()
forall s. MBA s -> ST s ()
go MBA s
mba
MBA s -> ST s ShortText
forall s. MBA s -> ST s ShortText
unsafeFreeze MBA s
mba
{-# INLINE createShrink #-}
createShrink :: B -> (forall s. MBA s -> ST s B) -> ShortText
createShrink :: B -> (forall s. MBA s -> ST s B) -> ShortText
createShrink B
n forall s. MBA s -> ST s B
go = (forall s. ST s ShortText) -> ShortText
forall a. (forall s. ST s a) -> a
runST ((forall s. ST s ShortText) -> ShortText)
-> (forall s. ST s ShortText) -> ShortText
forall a b. (a -> b) -> a -> b
$ do
MBA s
mba <- B -> ST s (MBA s)
forall s. B -> ST s (MBA s)
newByteArray B
n
B
n' <- MBA s -> ST s B
forall s. MBA s -> ST s B
go MBA s
mba
if B
n' B -> B -> Bool
forall a. Ord a => a -> a -> Bool
< B
n
then MBA s -> B -> ST s ShortText
forall s. MBA s -> B -> ST s ShortText
unsafeFreezeShrink MBA s
mba B
n'
else MBA s -> ST s ShortText
forall s. MBA s -> ST s ShortText
unsafeFreeze MBA s
mba
{-# INLINE unsafeFreeze #-}
unsafeFreeze :: MBA s -> ST s ShortText
unsafeFreeze :: forall s. MBA s -> ST s ShortText
unsafeFreeze (MBA# MutableByteArray# s
mba#)
= STRep s ShortText -> ST s ShortText
forall s a. STRep s a -> ST s a
ST (STRep s ShortText -> ST s ShortText)
-> STRep s ShortText -> ST s ShortText
forall a b. (a -> b) -> a -> b
$ \State# s
s -> case MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
forall d.
MutableByteArray# d -> State# d -> (# State# d, ByteArray# #)
GHC.Exts.unsafeFreezeByteArray# MutableByteArray# s
mba# State# s
s of
(# State# s
s', ByteArray#
ba# #) -> (# State# s
s', ShortByteString -> ShortText
ShortText (ByteArray# -> ShortByteString
BSSI.SBS ByteArray#
ba#) #)
{-# INLINE copyByteArray #-}
copyByteArray :: ShortText -> B -> MBA s -> B -> B -> ST s ()
copyByteArray :: forall s. ShortText -> B -> MBA s -> B -> B -> ST s ()
copyByteArray (ShortText (BSSI.SBS ByteArray#
src#)) (B (I# Int#
src_off#)) (MBA# MutableByteArray# s
dst#) (B (I# Int#
dst_off#)) (B (I# Int#
len#))
= STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s -> case ByteArray#
-> Int#
-> MutableByteArray# s
-> Int#
-> Int#
-> State# s
-> State# s
forall d.
ByteArray#
-> Int#
-> MutableByteArray# d
-> Int#
-> Int#
-> State# d
-> State# d
GHC.Exts.copyByteArray# ByteArray#
src# Int#
src_off# MutableByteArray# s
dst# Int#
dst_off# Int#
len# State# s
s of
State# s
s' -> (# State# s
s', () #)
{-# INLINE newByteArray #-}
newByteArray :: B -> ST s (MBA s)
newByteArray :: forall s. B -> ST s (MBA s)
newByteArray (B (I# Int#
n#))
= STRep s (MBA s) -> ST s (MBA s)
forall s a. STRep s a -> ST s a
ST (STRep s (MBA s) -> ST s (MBA s))
-> STRep s (MBA s) -> ST s (MBA s)
forall a b. (a -> b) -> a -> b
$ \State# s
s -> case Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #)
GHC.Exts.newByteArray# Int#
n# State# s
s of
(# State# s
s', MutableByteArray# s
mba# #) -> (# State# s
s', MutableByteArray# s -> MBA s
forall s. MutableByteArray# s -> MBA s
MBA# MutableByteArray# s
mba# #)
{-# INLINE writeWord8Array #-}
writeWord8Array :: MBA s -> B -> Word -> ST s ()
writeWord8Array :: forall s. MBA s -> B -> Word -> ST s ()
writeWord8Array (MBA# MutableByteArray# s
mba#) (B (I# Int#
i#)) (W# Word#
w#)
= STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s ->
#if __GLASGOW_HASKELL__ >= 902
case MutableByteArray# s -> Int# -> Word8# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word8# -> State# d -> State# d
GHC.Exts.writeWord8Array# MutableByteArray# s
mba# Int#
i# (Word# -> Word8#
GHC.Exts.wordToWord8# Word#
w#) State# s
s of
#else
case GHC.Exts.writeWord8Array# mba# i# w# s of
#endif
State# s
s' -> (# State# s
s', () #)
{-# INLINE copyAddrToByteArray #-}
copyAddrToByteArray :: Ptr a -> MBA RealWorld -> B -> B -> ST RealWorld ()
copyAddrToByteArray :: forall a. Ptr a -> MBA RealWorld -> B -> B -> ST RealWorld ()
copyAddrToByteArray (Ptr Addr#
src#) (MBA# MutableByteArray# RealWorld
dst#) (B (I# Int#
dst_off#)) (B (I# Int#
len#))
= STRep RealWorld () -> ST RealWorld ()
forall s a. STRep s a -> ST s a
ST (STRep RealWorld () -> ST RealWorld ())
-> STRep RealWorld () -> ST RealWorld ()
forall a b. (a -> b) -> a -> b
$ \State# RealWorld
s -> case Addr#
-> MutableByteArray# RealWorld
-> Int#
-> Int#
-> State# RealWorld
-> State# RealWorld
forall d.
Addr#
-> MutableByteArray# d -> Int# -> Int# -> State# d -> State# d
GHC.Exts.copyAddrToByteArray# Addr#
src# MutableByteArray# RealWorld
dst# Int#
dst_off# Int#
len# State# RealWorld
s of
State# RealWorld
s' -> (# State# RealWorld
s', () #)
#if __GLASGOW_HASKELL__ >= 710
{-# INLINE unsafeFreezeShrink #-}
unsafeFreezeShrink :: MBA s -> B -> ST s ShortText
unsafeFreezeShrink :: forall s. MBA s -> B -> ST s ShortText
unsafeFreezeShrink MBA s
mba B
n = do
MBA s -> B -> ST s ()
forall s. MBA s -> B -> ST s ()
shrink MBA s
mba B
n
MBA s -> ST s ShortText
forall s. MBA s -> ST s ShortText
unsafeFreeze MBA s
mba
{-# INLINE shrink #-}
shrink :: MBA s -> B -> ST s ()
shrink :: forall s. MBA s -> B -> ST s ()
shrink (MBA# MutableByteArray# s
mba#) (B (I# Int#
i#))
= STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s -> case MutableByteArray# s -> Int# -> State# s -> State# s
forall d. MutableByteArray# d -> Int# -> State# d -> State# d
GHC.Exts.shrinkMutableByteArray# MutableByteArray# s
mba# Int#
i# State# s
s of
State# s
s' -> (# State# s
s', () #)
#else
{-# INLINE unsafeFreezeShrink #-}
unsafeFreezeShrink :: MBA s -> B -> ST s ShortText
unsafeFreezeShrink mba0 n = do
mba' <- newByteArray n
copyByteArray2 mba0 0 mba' 0 n
unsafeFreeze mba'
{-# INLINE copyByteArray2 #-}
copyByteArray2 :: MBA s -> B -> MBA s -> B -> B -> ST s ()
copyByteArray2 (MBA# src#) (B (I# src_off#)) (MBA# dst#) (B (I# dst_off#)) (B( I# len#))
= ST $ \s -> case GHC.Exts.copyMutableByteArray# src# src_off# dst# dst_off# len# s of
s' -> (# s', () #)
#endif
newtype CP = CP Word
{-# INLINE ch2cp #-}
ch2cp :: Char -> CP
ch2cp :: Char -> CP
ch2cp (Char -> Int
ord -> Int
ci)
| Int -> Bool
forall i. (Num i, Bits i) => i -> Bool
isSurr Int
ci = Word -> CP
CP Word
0xFFFD
| Bool
otherwise = Word -> CP
CP (Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ci)
{-# INLINE isSurr #-}
isSurr :: (Num i, Bits i) => i -> Bool
isSurr :: forall i. (Num i, Bits i) => i -> Bool
isSurr i
ci = i
ci i -> i -> i
forall a. Bits a => a -> a -> a
.&. i
0xfff800 i -> i -> Bool
forall a. Eq a => a -> a -> Bool
== i
0xd800
{-# INLINE cp2ch #-}
cp2ch :: CP -> Char
cp2ch :: CP -> Char
cp2ch (CP Word
w) = (Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x110000) Bool -> Char -> Char
forall a. (?callStack::CallStack) => Bool -> a -> a
`assert` Int -> Char
unsafeChr (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
w)
cp2chSafe :: CP -> Maybe Char
cp2chSafe :: CP -> Maybe Char
cp2chSafe CP
cp
| CP -> Bool
cpNull CP
cp = Maybe Char
forall a. Maybe a
Nothing
| Bool
otherwise = Char -> Maybe Char
forall a. a -> Maybe a
Just (Char -> Maybe Char) -> Char -> Maybe Char
forall a b. (a -> b) -> a -> b
$! CP -> Char
cp2ch CP
cp
where
cpNull :: CP -> Bool
cpNull :: CP -> Bool
cpNull (CP Word
w) = Word
w Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
>= Word
0x110000
{-# INLINE cpLen #-}
cpLen :: CP -> B
cpLen :: CP -> B
cpLen (CP Word
cp)
| Word
cp Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x80 = Int -> B
B Int
1
| Word
cp Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x800 = Int -> B
B Int
2
| Word
cp Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x10000 = Int -> B
B Int
3
| Bool
otherwise = Int -> B
B Int
4
{-# INLINE decodeCharAtOfs #-}
decodeCharAtOfs :: ShortText -> B -> (Char,B)
decodeCharAtOfs :: ShortText -> B -> (Char, B)
decodeCharAtOfs ShortText
st B
ofs = (Char
c,B
ofs')
where
c :: Char
c = CP -> Char
cp2ch CP
cp
ofs' :: B
ofs' = B
ofs B -> B -> B
forall a. Num a => a -> a -> a
+ CP -> B
cpLen CP
cp
cp :: CP
cp = ShortText -> B -> CP
readCodePoint ShortText
st B
ofs
singleton :: Char -> ShortText
singleton :: Char -> ShortText
singleton = CP -> ShortText
singleton' (CP -> ShortText) -> (Char -> CP) -> Char -> ShortText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> CP
ch2cp
singleton' :: CP -> ShortText
singleton' :: CP -> ShortText
singleton' cp :: CP
cp@(CP Word
cpw)
| Word
cpw Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x80 = B -> (forall s. MBA s -> ST s ()) -> ShortText
create B
1 ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint1 MBA s
mba B
0 CP
cp
| Word
cpw Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x800 = B -> (forall s. MBA s -> ST s ()) -> ShortText
create B
2 ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint2 MBA s
mba B
0 CP
cp
| Word
cpw Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x10000 = B -> (forall s. MBA s -> ST s ()) -> ShortText
create B
3 ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint3 MBA s
mba B
0 CP
cp
| Bool
otherwise = B -> (forall s. MBA s -> ST s ()) -> ShortText
create B
4 ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint4 MBA s
mba B
0 CP
cp
cons :: Char -> ShortText -> ShortText
cons :: Char -> ShortText -> ShortText
cons (Char -> CP
ch2cp -> cp :: CP
cp@(CP Word
cpw)) ShortText
sfx
| B
n B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
0 = CP -> ShortText
singleton' CP
cp
| Word
cpw Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x80 = B -> (forall s. MBA s -> ST s ()) -> ShortText
create (B
nB -> B -> B
forall a. Num a => a -> a -> a
+B
1) ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint1 MBA s
mba B
0 CP
cp ST s () -> ST s () -> ST s ()
forall a b. ST s a -> ST s b -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> B -> MBA s -> ST s ()
forall s. B -> MBA s -> ST s ()
copySfx B
1 MBA s
mba
| Word
cpw Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x800 = B -> (forall s. MBA s -> ST s ()) -> ShortText
create (B
nB -> B -> B
forall a. Num a => a -> a -> a
+B
2) ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint2 MBA s
mba B
0 CP
cp ST s () -> ST s () -> ST s ()
forall a b. ST s a -> ST s b -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> B -> MBA s -> ST s ()
forall s. B -> MBA s -> ST s ()
copySfx B
2 MBA s
mba
| Word
cpw Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x10000 = B -> (forall s. MBA s -> ST s ()) -> ShortText
create (B
nB -> B -> B
forall a. Num a => a -> a -> a
+B
3) ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint3 MBA s
mba B
0 CP
cp ST s () -> ST s () -> ST s ()
forall a b. ST s a -> ST s b -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> B -> MBA s -> ST s ()
forall s. B -> MBA s -> ST s ()
copySfx B
3 MBA s
mba
| Bool
otherwise = B -> (forall s. MBA s -> ST s ()) -> ShortText
create (B
nB -> B -> B
forall a. Num a => a -> a -> a
+B
4) ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint4 MBA s
mba B
0 CP
cp ST s () -> ST s () -> ST s ()
forall a b. ST s a -> ST s b -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> B -> MBA s -> ST s ()
forall s. B -> MBA s -> ST s ()
copySfx B
4 MBA s
mba
where
!n :: B
n = ShortText -> B
toB ShortText
sfx
copySfx :: B -> MBA s -> ST s ()
copySfx :: forall s. B -> MBA s -> ST s ()
copySfx B
ofs MBA s
mba = ShortText -> B -> MBA s -> B -> B -> ST s ()
forall s. ShortText -> B -> MBA s -> B -> B -> ST s ()
copyByteArray ShortText
sfx B
0 MBA s
mba B
ofs B
n
snoc :: ShortText -> Char -> ShortText
snoc :: ShortText -> Char -> ShortText
snoc ShortText
pfx (Char -> CP
ch2cp -> cp :: CP
cp@(CP Word
cpw))
| B
n B -> B -> Bool
forall a. Eq a => a -> a -> Bool
== B
0 = CP -> ShortText
singleton' CP
cp
| Word
cpw Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x80 = B -> (forall s. MBA s -> ST s ()) -> ShortText
create (B
nB -> B -> B
forall a. Num a => a -> a -> a
+B
1) ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> ST s ()
forall s. MBA s -> ST s ()
copyPfx MBA s
mba ST s () -> ST s () -> ST s ()
forall a b. ST s a -> ST s b -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint1 MBA s
mba B
n CP
cp
| Word
cpw Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x800 = B -> (forall s. MBA s -> ST s ()) -> ShortText
create (B
nB -> B -> B
forall a. Num a => a -> a -> a
+B
2) ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> ST s ()
forall s. MBA s -> ST s ()
copyPfx MBA s
mba ST s () -> ST s () -> ST s ()
forall a b. ST s a -> ST s b -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint2 MBA s
mba B
n CP
cp
| Word
cpw Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
0x10000 = B -> (forall s. MBA s -> ST s ()) -> ShortText
create (B
nB -> B -> B
forall a. Num a => a -> a -> a
+B
3) ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> ST s ()
forall s. MBA s -> ST s ()
copyPfx MBA s
mba ST s () -> ST s () -> ST s ()
forall a b. ST s a -> ST s b -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint3 MBA s
mba B
n CP
cp
| Bool
otherwise = B -> (forall s. MBA s -> ST s ()) -> ShortText
create (B
nB -> B -> B
forall a. Num a => a -> a -> a
+B
4) ((forall s. MBA s -> ST s ()) -> ShortText)
-> (forall s. MBA s -> ST s ()) -> ShortText
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> MBA s -> ST s ()
forall s. MBA s -> ST s ()
copyPfx MBA s
mba ST s () -> ST s () -> ST s ()
forall a b. ST s a -> ST s b -> ST s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint4 MBA s
mba B
n CP
cp
where
!n :: B
n = ShortText -> B
toB ShortText
pfx
copyPfx :: MBA s -> ST s ()
copyPfx :: forall s. MBA s -> ST s ()
copyPfx MBA s
mba = ShortText -> B -> MBA s -> B -> B -> ST s ()
forall s. ShortText -> B -> MBA s -> B -> B -> ST s ()
copyByteArray ShortText
pfx B
0 MBA s
mba B
0 B
n
writeCodePointN :: B -> MBA s -> B -> CP -> ST s ()
writeCodePointN :: forall s. B -> MBA s -> B -> CP -> ST s ()
writeCodePointN B
1 = MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint1
writeCodePointN B
2 = MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint2
writeCodePointN B
3 = MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint3
writeCodePointN B
4 = MBA s -> B -> CP -> ST s ()
forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint4
writeCodePointN B
_ = MBA s -> B -> CP -> ST s ()
forall a. (?callStack::CallStack) => a
undefined
writeCodePoint1 :: MBA s -> B -> CP -> ST s ()
writeCodePoint1 :: forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint1 MBA s
mba B
ofs (CP Word
cp) =
MBA s -> B -> Word -> ST s ()
forall s. MBA s -> B -> Word -> ST s ()
writeWord8Array MBA s
mba B
ofs Word
cp
writeCodePoint2 :: MBA s -> B -> CP -> ST s ()
writeCodePoint2 :: forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint2 MBA s
mba B
ofs (CP Word
cp) = do
MBA s -> B -> Word -> ST s ()
forall s. MBA s -> B -> Word -> ST s ()
writeWord8Array MBA s
mba B
ofs (Word
0xc0 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. (Word
cp Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
6))
MBA s -> B -> Word -> ST s ()
forall s. MBA s -> B -> Word -> ST s ()
writeWord8Array MBA s
mba (B
ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
1) (Word
0x80 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. (Word
cp Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
0x3f))
writeCodePoint3 :: MBA s -> B -> CP -> ST s ()
writeCodePoint3 :: forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint3 MBA s
mba B
ofs (CP Word
cp) = do
MBA s -> B -> Word -> ST s ()
forall s. MBA s -> B -> Word -> ST s ()
writeWord8Array MBA s
mba B
ofs (Word
0xe0 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. (Word
cp Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
12))
MBA s -> B -> Word -> ST s ()
forall s. MBA s -> B -> Word -> ST s ()
writeWord8Array MBA s
mba (B
ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
1) (Word
0x80 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. ((Word
cp Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
6) Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
0x3f))
MBA s -> B -> Word -> ST s ()
forall s. MBA s -> B -> Word -> ST s ()
writeWord8Array MBA s
mba (B
ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
2) (Word
0x80 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. (Word
cp Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
0x3f))
writeCodePoint4 :: MBA s -> B -> CP -> ST s ()
writeCodePoint4 :: forall s. MBA s -> B -> CP -> ST s ()
writeCodePoint4 MBA s
mba B
ofs (CP Word
cp) = do
MBA s -> B -> Word -> ST s ()
forall s. MBA s -> B -> Word -> ST s ()
writeWord8Array MBA s
mba B
ofs (Word
0xf0 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. (Word
cp Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
18))
MBA s -> B -> Word -> ST s ()
forall s. MBA s -> B -> Word -> ST s ()
writeWord8Array MBA s
mba (B
ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
1) (Word
0x80 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. ((Word
cp Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
12) Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
0x3f))
MBA s -> B -> Word -> ST s ()
forall s. MBA s -> B -> Word -> ST s ()
writeWord8Array MBA s
mba (B
ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
2) (Word
0x80 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. ((Word
cp Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
6) Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
0x3f))
MBA s -> B -> Word -> ST s ()
forall s. MBA s -> B -> Word -> ST s ()
writeWord8Array MBA s
mba (B
ofsB -> B -> B
forall a. Num a => a -> a -> a
+B
3) (Word
0x80 Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. (Word
cp Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
0x3f))
readCodePoint :: ShortText -> B -> CP
readCodePoint :: ShortText -> B -> CP
readCodePoint ShortText
st (B -> CSize
csizeFromB -> CSize
ofs)
= Word -> CP
CP (Word -> CP) -> Word -> CP
forall a b. (a -> b) -> a -> b
$ IO Word -> Word
forall a. IO a -> a
unsafeDupablePerformIO (ByteArray# -> CSize -> IO Word
c_text_short_ofs_cp (ShortText -> ByteArray#
toByteArray# ShortText
st) CSize
ofs)
foreign import ccall unsafe "hs_text_short_ofs_cp" c_text_short_ofs_cp :: ByteArray# -> CSize -> IO CCodePoint
readCodePointRev :: ShortText -> B -> CP
readCodePointRev :: ShortText -> B -> CP
readCodePointRev ShortText
st (B -> CSize
csizeFromB -> CSize
ofs)
= Word -> CP
CP (Word -> CP) -> Word -> CP
forall a b. (a -> b) -> a -> b
$ IO Word -> Word
forall a. IO a -> a
unsafeDupablePerformIO (ByteArray# -> CSize -> IO Word
c_text_short_ofs_cp_rev (ShortText -> ByteArray#
toByteArray# ShortText
st) CSize
ofs)
foreign import ccall unsafe "hs_text_short_ofs_cp_rev" c_text_short_ofs_cp_rev :: ByteArray# -> CSize -> IO CCodePoint
instance GHC.Exts.IsList ShortText where
type (Item ShortText) = Char
fromList :: [Item ShortText] -> ShortText
fromList = String -> ShortText
[Item ShortText] -> ShortText
fromString
toList :: ShortText -> [Item ShortText]
toList = ShortText -> String
ShortText -> [Item ShortText]
toString
instance S.IsString ShortText where
fromString :: String -> ShortText
fromString = String -> ShortText
fromStringLit
{-# INLINE [0] fromStringLit #-}
fromStringLit :: String -> ShortText
fromStringLit :: String -> ShortText
fromStringLit = String -> ShortText
fromString
{-# RULES "ShortText empty literal" fromStringLit "" = mempty #-}
{-# RULES "ShortText singleton literal" forall c . fromStringLit [c] = singleton c #-}
{-# RULES "ShortText literal ASCII" forall s . fromStringLit (GHC.unpackCString# s) = fromLitAsciiAddr# s #-}
{-# RULES "ShortText literal UTF-8" forall s . fromStringLit (GHC.unpackCStringUtf8# s) = fromLitMUtf8Addr# s #-}
{-# NOINLINE fromLitAsciiAddr# #-}
fromLitAsciiAddr# :: Addr# -> ShortText
fromLitAsciiAddr# :: Addr# -> ShortText
fromLitAsciiAddr# (Addr# -> Ptr CChar
forall a. Addr# -> Ptr a
Ptr -> Ptr CChar
ptr) = IO ShortText -> ShortText
forall a. IO a -> a
unsafeDupablePerformIO (IO ShortText -> ShortText) -> IO ShortText -> ShortText
forall a b. (a -> b) -> a -> b
$ do
B
sz <- CSize -> B
csizeToB (CSize -> B) -> IO CSize -> IO B
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Ptr CChar -> IO CSize
c_strlen Ptr CChar
ptr
case B
sz B -> B -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` B
0 of
Ordering
EQ -> ShortText -> IO ShortText
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ShortText
forall a. Monoid a => a
mempty
Ordering
GT -> ST RealWorld ShortText -> IO ShortText
forall a. ST RealWorld a -> IO a
stToIO (ST RealWorld ShortText -> IO ShortText)
-> ST RealWorld ShortText -> IO ShortText
forall a b. (a -> b) -> a -> b
$ do
MBA RealWorld
mba <- B -> ST RealWorld (MBA RealWorld)
forall s. B -> ST s (MBA s)
newByteArray B
sz
Ptr CChar -> MBA RealWorld -> B -> B -> ST RealWorld ()
forall a. Ptr a -> MBA RealWorld -> B -> B -> ST RealWorld ()
copyAddrToByteArray Ptr CChar
ptr MBA RealWorld
mba B
0 B
sz
MBA RealWorld -> ST RealWorld ShortText
forall s. MBA s -> ST s ShortText
unsafeFreeze MBA RealWorld
mba
Ordering
LT -> ShortText -> IO ShortText
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> ShortText
forall a. (?callStack::CallStack) => String -> a
error String
"fromLitAsciiAddr#")
foreign import ccall unsafe "strlen" c_strlen :: CString -> IO CSize
{-# NOINLINE fromLitMUtf8Addr# #-}
fromLitMUtf8Addr# :: Addr# -> ShortText
fromLitMUtf8Addr# :: Addr# -> ShortText
fromLitMUtf8Addr# (Addr# -> Ptr CChar
forall a. Addr# -> Ptr a
Ptr -> Ptr CChar
ptr) = IO ShortText -> ShortText
forall a. IO a -> a
unsafeDupablePerformIO (IO ShortText -> ShortText) -> IO ShortText -> ShortText
forall a b. (a -> b) -> a -> b
$ do
B
sz <- Int -> B
B (Int -> B) -> IO Int -> IO B
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Ptr CChar -> IO Int
c_text_short_mutf8_strlen Ptr CChar
ptr
case B
sz B -> B -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` B
0 of
Ordering
EQ -> ShortText -> IO ShortText
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ShortText
forall a. Monoid a => a
mempty
Ordering
GT -> ST RealWorld ShortText -> IO ShortText
forall a. ST RealWorld a -> IO a
stToIO (ST RealWorld ShortText -> IO ShortText)
-> ST RealWorld ShortText -> IO ShortText
forall a b. (a -> b) -> a -> b
$ do
MBA RealWorld
mba <- B -> ST RealWorld (MBA RealWorld)
forall s. B -> ST s (MBA s)
newByteArray B
sz
Ptr CChar -> MBA RealWorld -> B -> B -> ST RealWorld ()
forall a. Ptr a -> MBA RealWorld -> B -> B -> ST RealWorld ()
copyAddrToByteArray Ptr CChar
ptr MBA RealWorld
mba B
0 B
sz
MBA RealWorld -> ST RealWorld ShortText
forall s. MBA s -> ST s ShortText
unsafeFreeze MBA RealWorld
mba
Ordering
LT -> do
MBA RealWorld
mba <- ST RealWorld (MBA RealWorld) -> IO (MBA RealWorld)
forall a. ST RealWorld a -> IO a
stToIO (B -> ST RealWorld (MBA RealWorld)
forall s. B -> ST s (MBA s)
newByteArray (B -> B
forall a. Num a => a -> a
abs B
sz))
Ptr CChar -> MutableByteArray# RealWorld -> IO ()
c_text_short_mutf8_trans Ptr CChar
ptr (MBA RealWorld -> MutableByteArray# RealWorld
forall s. MBA s -> MutableByteArray# s
unMBA# MBA RealWorld
mba)
ST RealWorld ShortText -> IO ShortText
forall a. ST RealWorld a -> IO a
stToIO (MBA RealWorld -> ST RealWorld ShortText
forall s. MBA s -> ST s ShortText
unsafeFreeze MBA RealWorld
mba)
foreign import ccall unsafe "hs_text_short_mutf8_strlen" c_text_short_mutf8_strlen :: CString -> IO Int
foreign import ccall unsafe "hs_text_short_mutf8_trans" c_text_short_mutf8_trans :: CString -> MutableByteArray# RealWorld -> IO ()