Skip to content

Commit fb7b0c6

Browse files
committed
Add some rewrite rules for empty strings.
1 parent 434600a commit fb7b0c6

File tree

1 file changed

+37
-9
lines changed

1 file changed

+37
-9
lines changed

src/Proto3/Wire/Reverse.hs

+37-9
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@
2626

2727
{-# LANGUAGE BangPatterns #-}
2828
{-# LANGUAGE CPP #-}
29+
{-# LANGUAGE MagicHash #-}
2930

3031
module Proto3.Wire.Reverse
3132
( -- * `BuildR` type
@@ -86,6 +87,7 @@ module Proto3.Wire.Reverse
8687

8788
import Data.Bits ( (.&.) )
8889
import qualified Data.ByteString as B
90+
import qualified Data.ByteString.Internal as BI
8991
import qualified Data.ByteString.Lazy as BL
9092
import qualified Data.ByteString.Lazy.Internal as BLI
9193
import qualified Data.ByteString.Short as BS
@@ -99,6 +101,11 @@ import qualified Data.Text.Lazy as TL
99101
import qualified Data.Text.Short as TS
100102
import Data.Vector.Generic ( Vector )
101103
import Data.Word ( Word8, Word16, Word32, Word64 )
104+
import GHC.Exts ( Addr#, Int(..), Int#, lazy )
105+
#if !MIN_VERSION_bytestring(0,11,0)
106+
import GHC.Exts ( plusAddr# )
107+
#endif
108+
import GHC.ForeignPtr ( ForeignPtr(..), ForeignPtrContents )
102109
import Foreign ( castPtr, copyBytes )
103110
import Proto3.Wire.Reverse.Internal
104111
import qualified Proto3.Wire.Reverse.Prim as Prim
@@ -134,15 +141,32 @@ toLazyByteString = snd . runBuildR
134141
-- >>> byteString "ABC"
135142
-- Proto3.Wire.Reverse.lazyByteString "ABC"
136143
byteString :: B.ByteString -> BuildR
137-
byteString bs = withUnused $ \unused ->
138-
let len = B.length bs in
139-
if len <= unused
140-
then
141-
unsafeConsume len $ \dst ->
142-
BU.unsafeUseAsCString bs $ \src ->
143-
copyBytes dst (castPtr src) len
144-
else
145-
prependChunk bs
144+
#if MIN_VERSION_bytestring(0,11,0)
145+
byteString (BI.BS (ForeignPtr ad ct) (I# len)) = byteStringImpl ad ct len
146+
#else
147+
byteString (BI.PS (ForeignPtr ad ct) (I# off) (I# len)) = byteStringImpl (plusAddr# ad off) ct len
148+
#endif
149+
{-# INLINE byteString #-}
150+
151+
byteStringImpl :: Addr# -> ForeignPtrContents -> Int# -> BuildR
152+
byteStringImpl ad ct len =
153+
#if MIN_VERSION_bytestring(0,11,0)
154+
let bs = BI.BS (ForeignPtr ad ct) (I# len) in
155+
#else
156+
let bs = BI.PS (ForeignPtr ad ct) 0 (I# len) in
157+
#endif
158+
withUnused $ \unused ->
159+
if I# len <= unused
160+
then
161+
unsafeConsume (I# len) $ \dst ->
162+
BU.unsafeUseAsCString bs $ \src ->
163+
copyBytes dst (castPtr src) (I# len)
164+
else
165+
prependChunk bs
166+
{-# NOINLINE [1] byteStringImpl #-}
167+
{-# RULES
168+
"byteStringImpl/empty" forall ad ct . byteStringImpl ad ct 0# = mempty
169+
#-}
146170

147171
-- | Convert a lazy `BL.ByteString` to a `BuildR`
148172
--
@@ -179,6 +203,10 @@ lazyByteString = etaBuildR $ scan (ReverseChunks BL.empty)
179203
copyBytes dst (castPtr src) len
180204
else
181205
prependReverseChunks (ReverseChunks(BLI.Chunk c cs))
206+
{-# NOINLINE [1] lazyByteString #-}
207+
{-# RULES
208+
"lazyByteString/empty" lazyByteString BLI.Empty = mempty
209+
#-}
182210

183211
-- | Convert a `BS.ShortByteString` to a `BuildR`
184212
--

0 commit comments

Comments
 (0)