26
26
27
27
{-# LANGUAGE BangPatterns #-}
28
28
{-# LANGUAGE CPP #-}
29
+ {-# LANGUAGE MagicHash #-}
29
30
30
31
module Proto3.Wire.Reverse
31
32
( -- * `BuildR` type
@@ -86,6 +87,7 @@ module Proto3.Wire.Reverse
86
87
87
88
import Data.Bits ( (.&.) )
88
89
import qualified Data.ByteString as B
90
+ import qualified Data.ByteString.Internal as BI
89
91
import qualified Data.ByteString.Lazy as BL
90
92
import qualified Data.ByteString.Lazy.Internal as BLI
91
93
import qualified Data.ByteString.Short as BS
@@ -99,6 +101,11 @@ import qualified Data.Text.Lazy as TL
99
101
import qualified Data.Text.Short as TS
100
102
import Data.Vector.Generic ( Vector )
101
103
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 )
102
109
import Foreign ( castPtr , copyBytes )
103
110
import Proto3.Wire.Reverse.Internal
104
111
import qualified Proto3.Wire.Reverse.Prim as Prim
@@ -134,15 +141,32 @@ toLazyByteString = snd . runBuildR
134
141
-- >>> byteString "ABC"
135
142
-- Proto3.Wire.Reverse.lazyByteString "ABC"
136
143
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
+ #-}
146
170
147
171
-- | Convert a lazy `BL.ByteString` to a `BuildR`
148
172
--
@@ -179,6 +203,10 @@ lazyByteString = etaBuildR $ scan (ReverseChunks BL.empty)
179
203
copyBytes dst (castPtr src) len
180
204
else
181
205
prependReverseChunks (ReverseChunks (BLI. Chunk c cs))
206
+ {-# NOINLINE [1] lazyByteString #-}
207
+ {-# RULES
208
+ "lazyByteString/empty" lazyByteString BLI.Empty = mempty
209
+ #-}
182
210
183
211
-- | Convert a `BS.ShortByteString` to a `BuildR`
184
212
--
0 commit comments