@@ -162,7 +162,7 @@ import Data.ByteString.Internal.Type
162162 )
163163
164164import Data.Array.Byte
165- ( ByteArray (.. ) )
165+ ( ByteArray (.. ), MutableByteArray ( .. ) )
166166import Data.Bits
167167 ( FiniteBits (finiteBitSize )
168168 , shiftL
@@ -392,7 +392,7 @@ asBA (ShortByteString ba) = ba
392392unSBS :: ShortByteString -> ByteArray #
393393unSBS (ShortByteString (ByteArray ba# )) = ba#
394394
395- create :: Int -> (forall s . MBA s -> ST s () ) -> ShortByteString
395+ create :: Int -> (forall s . MutableByteArray s -> ST s () ) -> ShortByteString
396396create len fill =
397397 assert (len >= 0 ) $ runST $ do
398398 mba <- newByteArray len
@@ -405,7 +405,7 @@ create len fill =
405405-- The generating function is required to return the actual final size
406406-- (<= the maximum size) and the result value. The resulting byte array
407407-- is realloced to this size.
408- createAndTrim :: Int -> (forall s . MBA s -> ST s (Int , a )) -> (ShortByteString , a )
408+ createAndTrim :: Int -> (forall s . MutableByteArray s -> ST s (Int , a )) -> (ShortByteString , a )
409409createAndTrim maxLen fill =
410410 assert (maxLen >= 0 ) $ runST $ do
411411 mba <- newByteArray maxLen
@@ -421,7 +421,7 @@ createAndTrim maxLen fill =
421421 return (ShortByteString ba, res)
422422{-# INLINE createAndTrim #-}
423423
424- createAndTrim' :: Int -> (forall s . MBA s -> ST s Int ) -> ShortByteString
424+ createAndTrim' :: Int -> (forall s . MutableByteArray s -> ST s Int ) -> ShortByteString
425425createAndTrim' maxLen fill =
426426 assert (maxLen >= 0 ) $ runST $ do
427427 mba <- newByteArray maxLen
@@ -436,7 +436,7 @@ createAndTrim' maxLen fill =
436436{-# INLINE createAndTrim' #-}
437437
438438-- | Like createAndTrim, but with two buffers at once
439- createAndTrim2 :: Int -> Int -> (forall s . MBA s -> MBA s -> ST s (Int , Int )) -> (ShortByteString , ShortByteString )
439+ createAndTrim2 :: Int -> Int -> (forall s . MutableByteArray s -> MutableByteArray s -> ST s (Int , Int )) -> (ShortByteString , ShortByteString )
440440createAndTrim2 maxLen1 maxLen2 fill =
441441 runST $ do
442442 mba1 <- newByteArray maxLen1
@@ -446,7 +446,7 @@ createAndTrim2 maxLen1 maxLen2 fill =
446446 sbs2 <- freeze' len2 maxLen2 mba2
447447 pure (sbs1, sbs2)
448448 where
449- freeze' :: Int -> Int -> MBA s -> ST s ShortByteString
449+ freeze' :: Int -> Int -> MutableByteArray s -> ST s ShortByteString
450450 freeze' len maxLen mba =
451451 if assert (0 <= len && len <= maxLen) $ len >= maxLen
452452 then do
@@ -496,7 +496,7 @@ fromShort !sbs = unsafeDupablePerformIO (fromShortIO sbs)
496496fromShortIO :: ShortByteString -> IO ByteString
497497fromShortIO sbs = do
498498 let len = length sbs
499- mba@ (MBA # mba# ) <- stToIO (newPinnedByteArray len)
499+ mba@ (MutableByteArray mba# ) <- stToIO (newPinnedByteArray len)
500500 stToIO (copyByteArray (asBA sbs) 0 mba 0 len)
501501 let fp = ForeignPtr (byteArrayContents# (unsafeCoerce# mba# ))
502502 (PlainPtr mba# )
@@ -542,7 +542,7 @@ packLenBytes :: Int -> [Word8] -> ShortByteString
542542packLenBytes len ws0 =
543543 create len (\ mba -> go mba 0 ws0)
544544 where
545- go :: MBA s -> Int -> [Word8 ] -> ST s ()
545+ go :: MutableByteArray s -> Int -> [Word8 ] -> ST s ()
546546 go ! _ ! _ [] = return ()
547547 go ! mba ! i (w: ws) = do
548548 writeWord8Array mba i w
@@ -646,7 +646,7 @@ concat = \sbss ->
646646 totalLen ! acc (curr : rest)
647647 = totalLen (checkedAdd " Short.concat" acc $ length curr) rest
648648
649- copy :: MBA s -> Int -> [ShortByteString ] -> ST s ()
649+ copy :: MutableByteArray s -> Int -> [ShortByteString ] -> ST s ()
650650 copy ! _ ! _ [] = return ()
651651 copy ! dst ! off (src : sbss) = do
652652 let ! len = length src
@@ -777,7 +777,7 @@ map f = \sbs ->
777777 ba = asBA sbs
778778 in create l (\ mba -> go ba mba 0 l)
779779 where
780- go :: ByteArray -> MBA s -> Int -> Int -> ST s ()
780+ go :: ByteArray -> MutableByteArray s -> Int -> Int -> ST s ()
781781 go ! ba ! mba ! i ! l
782782 | i >= l = return ()
783783 | otherwise = do
@@ -796,7 +796,7 @@ reverse = \sbs ->
796796#if HS_UNALIGNED_ByteArray_OPS_OK
797797 in create l (\ mba -> go ba mba l)
798798 where
799- go :: forall s . ByteArray -> MBA s -> Int -> ST s ()
799+ go :: forall s . ByteArray -> MutableByteArray s -> Int -> ST s ()
800800 go ! ba ! mba ! l = do
801801 -- this is equivalent to: (q, r) = l `quotRem` 8
802802 let q = l `shiftR` 3
@@ -829,7 +829,7 @@ reverse = \sbs ->
829829#else
830830 in create l (\ mba -> go ba mba 0 l)
831831 where
832- go :: ByteArray -> MBA s -> Int -> Int -> ST s ()
832+ go :: ByteArray -> MutableByteArray s -> Int -> Int -> ST s ()
833833 go ! ba ! mba ! i ! l
834834 | i >= l = return ()
835835 | otherwise = do
@@ -856,7 +856,7 @@ intercalate sep = \case
856856 ba = asBA sep
857857 lba = length sep
858858
859- go :: MBA s -> Int -> [ShortByteString ] -> ST s ()
859+ go :: MutableByteArray s -> Int -> [ShortByteString ] -> ST s ()
860860 go _ _ [] = pure ()
861861 go mba ! off (chunk: chunks) = do
862862 let lc = length chunk
@@ -1278,7 +1278,7 @@ unfoldrN i f = \x0 ->
12781278 | otherwise -> createAndTrim i $ \ mba -> go mba x0 0
12791279
12801280 where
1281- go :: forall s . MBA s -> a -> Int -> ST s (Int , Maybe a )
1281+ go :: forall s . MutableByteArray s -> a -> Int -> ST s (Int , Maybe a )
12821282 go ! mba ! x ! n = go' x n
12831283 where
12841284 go' :: a -> Int -> ST s (Int , Maybe a )
@@ -1430,7 +1430,7 @@ filter k = \sbs -> let l = length sbs
14301430 in if | l <= 0 -> sbs
14311431 | otherwise -> createAndTrim' l $ \ mba -> go mba (asBA sbs) l
14321432 where
1433- go :: forall s . MBA s -- mutable output bytestring
1433+ go :: forall s . MutableByteArray s -- mutable output bytestring
14341434 -> ByteArray -- input bytestring
14351435 -> Int -- length of input bytestring
14361436 -> ST s Int
@@ -1477,8 +1477,8 @@ partition k = \sbs -> let len = length sbs
14771477 | otherwise -> createAndTrim2 len len $ \ mba1 mba2 -> go mba1 mba2 (asBA sbs) len
14781478 where
14791479 go :: forall s .
1480- MBA s -- mutable output bytestring1
1481- -> MBA s -- mutable output bytestring2
1480+ MutableByteArray s -- mutable output bytestring1
1481+ -> MutableByteArray s -- mutable output bytestring2
14821482 -> ByteArray -- input bytestring
14831483 -> Int -- length of input bytestring
14841484 -> ST s (Int , Int ) -- (length mba1, length mba2)
@@ -1586,8 +1586,6 @@ createFromPtr !ptr len =
15861586------------------------------------------------------------------------
15871587-- Primop wrappers
15881588
1589- data MBA s = MBA # (MutableByteArray # s )
1590-
15911589indexCharArray :: ByteArray -> Int -> Char
15921590indexCharArray (ByteArray ba# ) (I # i# ) = C # (indexCharArray# ba# i# )
15931591
@@ -1599,37 +1597,37 @@ indexWord8ArrayAsWord64 :: ByteArray -> Int -> Word64
15991597indexWord8ArrayAsWord64 (ByteArray ba# ) (I # i# ) = W64 # (indexWord8ArrayAsWord64# ba# i# )
16001598#endif
16011599
1602- newByteArray :: Int -> ST s (MBA s )
1600+ newByteArray :: Int -> ST s (MutableByteArray s )
16031601newByteArray len@ (I # len# ) =
16041602 assert (len >= 0 ) $
16051603 ST $ \ s -> case newByteArray# len# s of
1606- (# s', mba# # ) -> (# s', MBA # mba# # )
1604+ (# s', mba# # ) -> (# s', MutableByteArray mba# # )
16071605
1608- newPinnedByteArray :: Int -> ST s (MBA s )
1606+ newPinnedByteArray :: Int -> ST s (MutableByteArray s )
16091607newPinnedByteArray len@ (I # len# ) =
16101608 assert (len >= 0 ) $
16111609 ST $ \ s -> case newPinnedByteArray# len# s of
1612- (# s', mba# # ) -> (# s', MBA # mba# # )
1610+ (# s', mba# # ) -> (# s', MutableByteArray mba# # )
16131611
1614- unsafeFreezeByteArray :: MBA s -> ST s ByteArray
1615- unsafeFreezeByteArray (MBA # mba# ) =
1612+ unsafeFreezeByteArray :: MutableByteArray s -> ST s ByteArray
1613+ unsafeFreezeByteArray (MutableByteArray mba# ) =
16161614 ST $ \ s -> case unsafeFreezeByteArray# mba# s of
16171615 (# s', ba# # ) -> (# s', ByteArray ba# # )
16181616
1619- writeWord8Array :: MBA s -> Int -> Word8 -> ST s ()
1620- writeWord8Array (MBA # mba# ) (I # i# ) (W8 # w# ) =
1617+ writeWord8Array :: MutableByteArray s -> Int -> Word8 -> ST s ()
1618+ writeWord8Array (MutableByteArray mba# ) (I # i# ) (W8 # w# ) =
16211619 ST $ \ s -> case writeWord8Array# mba# i# w# s of
16221620 s' -> (# s', () # )
16231621
16241622#if HS_UNALIGNED_ByteArray_OPS_OK
1625- writeWord64Array :: MBA s -> Int -> Word64 -> ST s ()
1626- writeWord64Array (MBA # mba# ) (I # i# ) (W64 # w# ) =
1623+ writeWord64Array :: MutableByteArray s -> Int -> Word64 -> ST s ()
1624+ writeWord64Array (MutableByteArray mba# ) (I # i# ) (W64 # w# ) =
16271625 ST $ \ s -> case writeWord64Array# mba# i# w# s of
16281626 s' -> (# s', () # )
16291627#endif
16301628
1631- copyAddrToByteArray :: Ptr a -> MBA RealWorld -> Int -> Int -> ST RealWorld ()
1632- copyAddrToByteArray (Ptr src# ) (MBA # dst# ) (I # dst_off# ) (I # len# ) =
1629+ copyAddrToByteArray :: Ptr a -> MutableByteArray RealWorld -> Int -> Int -> ST RealWorld ()
1630+ copyAddrToByteArray (Ptr src# ) (MutableByteArray dst# ) (I # dst_off# ) (I # len# ) =
16331631 ST $ \ s -> case copyAddrToByteArray# src# dst# dst_off# len# s of
16341632 s' -> (# s', () # )
16351633
@@ -1638,18 +1636,18 @@ copyByteArrayToAddr (ByteArray src#) (I# src_off#) (Ptr dst#) (I# len#) =
16381636 ST $ \ s -> case copyByteArrayToAddr# src# src_off# dst# len# s of
16391637 s' -> (# s', () # )
16401638
1641- copyByteArray :: ByteArray -> Int -> MBA s -> Int -> Int -> ST s ()
1642- copyByteArray (ByteArray src# ) (I # src_off# ) (MBA # dst# ) (I # dst_off# ) (I # len# ) =
1639+ copyByteArray :: ByteArray -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
1640+ copyByteArray (ByteArray src# ) (I # src_off# ) (MutableByteArray dst# ) (I # dst_off# ) (I # len# ) =
16431641 ST $ \ s -> case copyByteArray# src# src_off# dst# dst_off# len# s of
16441642 s' -> (# s', () # )
16451643
1646- setByteArray :: MBA s -> Int -> Int -> Int -> ST s ()
1647- setByteArray (MBA # dst# ) (I # off# ) (I # len# ) (I # c# ) =
1644+ setByteArray :: MutableByteArray s -> Int -> Int -> Int -> ST s ()
1645+ setByteArray (MutableByteArray dst# ) (I # off# ) (I # len# ) (I # c# ) =
16481646 ST $ \ s -> case setByteArray# dst# off# len# c# s of
16491647 s' -> (# s', () # )
16501648
1651- copyMutableByteArray :: MBA s -> Int -> MBA s -> Int -> Int -> ST s ()
1652- copyMutableByteArray (MBA # src# ) (I # src_off# ) (MBA # dst# ) (I # dst_off# ) (I # len# ) =
1649+ copyMutableByteArray :: MutableByteArray s -> Int -> MutableByteArray s -> Int -> Int -> ST s ()
1650+ copyMutableByteArray (MutableByteArray src# ) (I # src_off# ) (MutableByteArray dst# ) (I # dst_off# ) (I # len# ) =
16531651 ST $ \ s -> case copyMutableByteArray# src# src_off# dst# dst_off# len# s of
16541652 s' -> (# s', () # )
16551653
@@ -1834,7 +1832,7 @@ packLenBytesRev :: Int -> [Word8] -> ShortByteString
18341832packLenBytesRev len ws0 =
18351833 create len (\ mba -> go mba len ws0)
18361834 where
1837- go :: MBA s -> Int -> [Word8 ] -> ST s ()
1835+ go :: MutableByteArray s -> Int -> [Word8 ] -> ST s ()
18381836 go ! _ ! _ [] = return ()
18391837 go ! mba ! i (w: ws) = do
18401838 writeWord8Array mba (i - 1 ) w
0 commit comments