{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP          #-}
module Data.Aeson.Internal.Text (
    unsafeDecodeASCII,
) where
import           Data.ByteString                (ByteString)
import qualified Data.Text                      as T
#if MIN_VERSION_text(2,0,0)
import           Data.Text.Array                (Array (..))
import qualified Data.Text.Internal             as T (Text (..))
import qualified Data.ByteString.Short.Internal as SBS
import           Data.Aeson.Internal.ByteString
#else
import qualified Data.Text.Encoding             as TE
#endif
unsafeDecodeASCII :: ByteString -> T.Text
#if MIN_VERSION_text(2,0,0)
unsafeDecodeASCII :: ByteString -> Text
unsafeDecodeASCII ByteString
bs = forall r. ByteString -> (ForeignPtr Word8 -> Int -> r) -> r
withBS ByteString
bs forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
_fp Int
len -> if Int
len forall a. Eq a => a -> a -> Bool
== Int
0 then Text
T.empty else
  let !(SBS.SBS ByteArray#
arr) = ByteString -> ShortByteString
SBS.toShort ByteString
bs in Array -> Int -> Int -> Text
T.Text (ByteArray# -> Array
ByteArray ByteArray#
arr) Int
0 Int
len
#else
unsafeDecodeASCII = TE.decodeLatin1
#endif