{-# LANGUAGE GADTSyntax #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnliftedNewtypes #-} module Data.Text.Short.Unlifted ( ShortText# (..) , pattern Empty# , lift , unlift ) where import GHC.Exts (Int#) import Data.ByteString.Short.Internal as TS import Data.Text.Short (ShortText) import Data.Unlifted (ShortText# (ShortText#)) import GHC.Exts ((==#)) import qualified Data.Text.Short as TS import qualified Data.Text.Short.Unsafe as TS import qualified GHC.Exts as Exts pattern Empty# :: ShortText# pattern $mEmpty# :: forall {r}. ShortText# -> ((# #) -> r) -> ((# #) -> r) -> r $bEmpty# :: (# #) -> ShortText# Empty# <- (null# -> 1#) where Empty# = (# #) -> ShortText# empty# (# #) empty# :: (# #) -> ShortText# empty# :: (# #) -> ShortText# empty# (# #) _ = ByteArray# -> ShortText# ShortText# ((State# RealWorld -> ByteArray#) -> ByteArray# forall o. (State# RealWorld -> o) -> o Exts.runRW# (\State# RealWorld s0 -> case Int# -> State# RealWorld -> (# State# RealWorld, MutableByteArray# RealWorld #) forall d. Int# -> State# d -> (# State# d, MutableByteArray# d #) Exts.newByteArray# Int# 0# State# RealWorld s0 of { (# State# RealWorld s1, MutableByteArray# RealWorld b #) -> case MutableByteArray# RealWorld -> State# RealWorld -> (# State# RealWorld, ByteArray# #) forall d. MutableByteArray# d -> State# d -> (# State# d, ByteArray# #) Exts.unsafeFreezeByteArray# MutableByteArray# RealWorld b State# RealWorld s1 of { (# State# RealWorld _, ByteArray# y #) -> ByteArray# y}})) null# :: ShortText# -> Int# null# :: ShortText# -> Int# null# (ShortText# ByteArray# x) = ByteArray# -> Int# Exts.sizeofByteArray# ByteArray# x Int# -> Int# -> Int# ==# Int# 0# lift :: ShortText# -> ShortText lift :: ShortText# -> ShortText lift (ShortText# ByteArray# x) = ShortByteString -> ShortText TS.fromShortByteStringUnsafe (ByteArray# -> ShortByteString SBS ByteArray# x) unlift :: ShortText -> ShortText# unlift :: ShortText -> ShortText# unlift ShortText t = case ShortText -> ShortByteString TS.toShortByteString ShortText t of SBS ByteArray# x -> ByteArray# -> ShortText# ShortText# ByteArray# x