{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
module Data.Bytes.Text.Utf8
( fromShortText
, toShortText
#if MIN_VERSION_text(2,0,0)
, fromText
#endif
#if MIN_VERSION_text(2,1,0)
, toText
#endif
) where
import Data.Bytes.Types (Bytes (Bytes))
import Data.Primitive (ByteArray (ByteArray))
import Data.Text (Text)
import Data.Text.Short (ShortText)
import qualified Data.Bytes as Bytes
import qualified Data.Text.Array as A
import qualified Data.Text.Internal as I
import qualified Data.Text.Short as TS
#if MIN_VERSION_text(2,1,0)
import qualified Data.Text.Internal.Validate
#endif
fromShortText :: ShortText -> Bytes
{-# INLINE fromShortText #-}
fromShortText :: ShortText -> Bytes
fromShortText = ShortByteString -> Bytes
Bytes.fromShortByteString (ShortByteString -> Bytes)
-> (ShortText -> ShortByteString) -> ShortText -> Bytes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortText -> ShortByteString
TS.toShortByteString
toShortText :: Bytes -> Maybe ShortText
{-# INLINE toShortText #-}
toShortText :: Bytes -> Maybe ShortText
toShortText !Bytes
b = ShortByteString -> Maybe ShortText
TS.fromShortByteString (Bytes -> ShortByteString
Bytes.toShortByteString Bytes
b)
#if MIN_VERSION_text(2,0,0)
fromText :: Text -> Bytes
{-# inline fromText #-}
fromText :: Text -> Bytes
fromText (I.Text (A.ByteArray ByteArray#
b) Int
off Int
len) = ByteArray -> Int -> Int -> Bytes
Bytes (ByteArray# -> ByteArray
ByteArray ByteArray#
b) Int
off Int
len
#endif
#if MIN_VERSION_text(2,1,0)
toText :: Bytes -> Maybe Text
{-# inline toText #-}
toText :: Bytes -> Maybe Text
toText (Bytes b :: ByteArray
b@(ByteArray ByteArray#
b0) Int
off Int
len) =
if ByteArray -> Int -> Int -> Bool
Data.Text.Internal.Validate.isValidUtf8ByteArray ByteArray
b Int
off Int
len
then Text -> Maybe Text
forall a. a -> Maybe a
Just (ByteArray -> Int -> Int -> Text
I.Text (ByteArray# -> ByteArray
A.ByteArray ByteArray#
b0) Int
off Int
len)
else Maybe Text
forall a. Maybe a
Nothing
#endif