Skip to content

Commit 503eb77

Browse files
LysxiaBodigrim
authored andcommitted
Shave off redundant field of Text.Internal.Buffer
1 parent 86b5590 commit 503eb77

File tree

1 file changed

+18
-15
lines changed

1 file changed

+18
-15
lines changed

src/Data/Text/Internal/Builder.hs

Lines changed: 18 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -196,20 +196,23 @@ fromText t@(Text arr off l)
196196
--
197197
-- @since 1.2.0.0
198198
fromString :: String -> Builder
199-
fromString str = Builder $ \k (Buffer p0 o0 u0 l0) ->
200-
let loop !marr !o !u !l [] = k (Buffer marr o u l)
201-
loop marr o u l s@(c:cs)
202-
| l <= 3 = do
199+
fromString str = Builder $ \k (Buffer p0 o0 u0) -> do
200+
len <- A.getSizeofMArray p0
201+
-- `end` is 3 bytes before the actual end of `marr`
202+
-- to make sure there's room for a 4-byte UTF-8 code point.
203+
let loop !marr !o !u !_ [] = k (Buffer marr o u)
204+
loop marr o u end s@(c:cs)
205+
| u >= end = do
203206
A.shrinkM marr (o + u)
204207
arr <- A.unsafeFreeze marr
205208
let !t = Text arr o u
206209
marr' <- A.new chunkSize
207-
ts <- inlineInterleaveST (loop marr' 0 0 chunkSize s)
210+
ts <- inlineInterleaveST (loop marr' 0 0 (chunkSize - 3) s)
208211
return $ t : ts
209212
| otherwise = do
210213
n <- unsafeWrite marr (o+u) (safe c)
211-
loop marr o (u+n) (l-n) cs
212-
in loop p0 o0 u0 l0 str
214+
loop marr o (u+n) end cs
215+
loop p0 o0 u0 (len - o0 - 3) str
213216
where
214217
chunkSize = smallChunkSize
215218
{-# INLINEABLE fromString #-}
@@ -228,7 +231,6 @@ fromLazyText ts = flush `append` mapBuilder (L.toChunks ts ++)
228231
data Buffer s = Buffer {-# UNPACK #-} !(A.MArray s)
229232
{-# UNPACK #-} !Int -- offset
230233
{-# UNPACK #-} !Int -- used units
231-
{-# UNPACK #-} !Int -- length left
232234

233235
------------------------------------------------------------------------
234236

@@ -251,11 +253,11 @@ toLazyTextWith chunkSize m = L.fromChunks (runST $
251253
-- | /O(1)./ Pop the strict @Text@ we have constructed so far, if any,
252254
-- yielding a new chunk in the result lazy @Text@.
253255
flush :: Builder
254-
flush = Builder $ \ k buf@(Buffer p o u l) ->
256+
flush = Builder $ \ k buf@(Buffer p o u) ->
255257
if u == 0
256258
then k buf
257259
else do arr <- A.unsafeFreeze p
258-
let !b = Buffer p (o+u) 0 l
260+
let !b = Buffer p (o+u) 0
259261
!t = Text arr o u
260262
ts <- inlineInterleaveST (k b)
261263
return $! t : ts
@@ -271,8 +273,9 @@ withBuffer f = Builder $ \k buf -> f buf >>= k
271273

272274
-- | Get the size of the buffer
273275
withSize :: (Int -> Builder) -> Builder
274-
withSize f = Builder $ \ k buf@(Buffer _ _ _ l) ->
275-
runBuilder (f l) k buf
276+
withSize f = Builder $ \ k buf@(Buffer arr offset used) -> do
277+
len <- A.getSizeofMArray arr
278+
runBuilder (f (len - offset - used)) k buf
276279
{-# INLINE withSize #-}
277280

278281
-- | Map the resulting list of texts.
@@ -300,15 +303,15 @@ writeN n f = writeAtMost n (\ p o -> f p o >> return n)
300303
{-# INLINE writeN #-}
301304

302305
writeBuffer :: (A.MArray s -> Int -> ST s Int) -> Buffer s -> ST s (Buffer s)
303-
writeBuffer f (Buffer p o u l) = do
306+
writeBuffer f (Buffer p o u) = do
304307
n <- f p (o+u)
305-
return $! Buffer p o (u+n) (l-n)
308+
return $! Buffer p o (u+n)
306309
{-# INLINE writeBuffer #-}
307310

308311
newBuffer :: Int -> ST s (Buffer s)
309312
newBuffer size = do
310313
arr <- A.new size
311-
return $! Buffer arr 0 0 size
314+
return $! Buffer arr 0 0
312315
{-# INLINE newBuffer #-}
313316

314317
------------------------------------------------------------------------

0 commit comments

Comments
 (0)