Rename newByteArray to new

To keep it consistent with naming in other Array modules.
This commit is contained in:
Harendra Kumar 2023-11-25 09:39:51 +05:30
parent 6705ec00b9
commit 56fd008519
8 changed files with 35 additions and 32 deletions

View File

@ -25,6 +25,7 @@ import Test.QuickCheck (Arbitrary, arbitrary)
#endif
import Streamly.Internal.Data.MutByteArray hiding (encode)
import qualified Streamly.Internal.Data.MutByteArray as MBA
#ifdef USE_UNBOX
import Data.Proxy (Proxy(..))
#else
@ -335,7 +336,7 @@ pokeWithSize arr val = do
pokeTimesWithSize :: SERIALIZE_CLASS a => a -> Int -> IO ()
pokeTimesWithSize val times = do
let n = getSize val
arr <- newByteArray n
arr <- MBA.new n
loopWith times pokeWithSize arr val
-}
@ -347,14 +348,14 @@ poke arr val = SERIALIZE_OP 0 arr val >> return ()
pokeTimes :: SERIALIZE_CLASS a => a -> Int -> IO ()
pokeTimes val times = do
let n = getSize val
arr <- newByteArray n
arr <- MBA.new n
loopWith times poke arr val
{-# INLINE encode #-}
encode :: SERIALIZE_CLASS a => a -> IO ()
encode val = do
let n = getSize val
arr <- newByteArray n
arr <- MBA.new n
SERIALIZE_OP 0 arr val >> return ()
{-# INLINE encodeTimes #-}
@ -390,7 +391,7 @@ peek (_val, n) arr = do
{-# INLINE peekTimes #-}
peekTimes :: (NFData a, SERIALIZE_CLASS a) => Int -> a -> Int -> IO ()
peekTimes n val times = do
arr <- newByteArray n
arr <- MBA.new n
_ <- SERIALIZE_OP 0 arr val
loopWith times peek (val, n) arr
@ -398,7 +399,7 @@ peekTimes n val times = do
trip :: forall a. (NFData a, SERIALIZE_CLASS a) => a -> IO ()
trip val = do
let n = getSize val
arr <- newByteArray n
arr <- MBA.new n
_ <- SERIALIZE_OP 0 arr val
#ifdef USE_UNBOX
(val1 :: a) <- DESERIALIZE_OP 0 arr

View File

@ -52,8 +52,8 @@ module Streamly.Data.MutByteArray
, isPinned
, pin
, unpin
, newByteArray
, pinnedNewByteArray
, new
, pinnedNew
-- * Unbox
, Unbox(..)

View File

@ -40,10 +40,10 @@ where
import Control.Monad.IO.Class (MonadIO(..))
import Data.Proxy (Proxy(..))
import Streamly.Internal.Data.MutByteArray.Type
(MutByteArray(..), newByteArray)
import Streamly.Internal.Data.MutByteArray.Type (MutByteArray)
import Streamly.Internal.Data.Unbox (Unbox(..), sizeOf)
import qualified Streamly.Internal.Data.MutByteArray.Type as MBA
import qualified Streamly.Internal.Data.Stream.Type as D
-- | An 'IORef' holds a single 'Unbox'-able value.
@ -55,7 +55,7 @@ newtype IORef a = IORef MutByteArray
{-# INLINE newIORef #-}
newIORef :: forall a. Unbox a => a -> IO (IORef a)
newIORef x = do
var <- newByteArray (sizeOf (Proxy :: Proxy a))
var <- MBA.new (sizeOf (Proxy :: Proxy a))
pokeByteIndex 0 var x
return $ IORef var

View File

@ -744,8 +744,8 @@ reallocExplicit elemSize newCapacityInBytes MutArray{..} = do
let newCapMaxInBytes = roundUpLargeArray newCapacityInBytes
contents <-
if Unboxed.isPinned arrContents
then Unboxed.pinnedNewByteArray newCapMaxInBytes
else Unboxed.newByteArray newCapMaxInBytes
then Unboxed.pinnedNew newCapMaxInBytes
else Unboxed.new newCapMaxInBytes
let !(MutByteArray mbarrFrom#) = arrContents
!(MutByteArray mbarrTo#) = contents
@ -2134,8 +2134,8 @@ spliceCopy arr1 arr2 = liftIO $ do
let newLen = len1 + len2
newArrContents <-
if Unboxed.isPinned (arrContents arr1)
then Unboxed.pinnedNewByteArray newLen
else Unboxed.newByteArray newLen
then Unboxed.pinnedNew newLen
else Unboxed.new newLen
let len = len1 + len2
putSliceUnsafe (arrContents arr1) start1 newArrContents 0 len1
putSliceUnsafe (arrContents arr2) start2 newArrContents len1 len2

View File

@ -24,8 +24,8 @@ module Streamly.Internal.Data.MutByteArray.Type
-- ** Allocation
, nil
, newBytesAs
, newByteArray
, pinnedNewByteArray
, new
, pinnedNew
, pinnedNewAlignedBytes
-- ** Access
@ -122,23 +122,23 @@ asPtrUnsafe arr f = do
{-# NOINLINE nil #-}
nil :: MutByteArray
nil = unsafePerformIO $ newByteArray 0
nil = unsafePerformIO $ new 0
{-# INLINE newByteArray #-}
newByteArray :: Int -> IO MutByteArray
newByteArray nbytes | nbytes < 0 =
{-# INLINE new #-}
new :: Int -> IO MutByteArray
new nbytes | nbytes < 0 =
errorWithoutStackTrace "newByteArray: size must be >= 0"
newByteArray (I# nbytes) = IO $ \s ->
new (I# nbytes) = IO $ \s ->
case newByteArray# nbytes s of
(# s', mbarr# #) ->
let c = MutByteArray mbarr#
in (# s', c #)
{-# INLINE pinnedNewByteArray #-}
pinnedNewByteArray :: Int -> IO MutByteArray
pinnedNewByteArray nbytes | nbytes < 0 =
{-# INLINE pinnedNew #-}
pinnedNew :: Int -> IO MutByteArray
pinnedNew nbytes | nbytes < 0 =
errorWithoutStackTrace "pinnedNewByteArray: size must be >= 0"
pinnedNewByteArray (I# nbytes) = IO $ \s ->
pinnedNew (I# nbytes) = IO $ \s ->
case newPinnedByteArray# nbytes s of
(# s', mbarr# #) ->
let c = MutByteArray mbarr#
@ -156,8 +156,8 @@ pinnedNewAlignedBytes (I# nbytes) (I# align) = IO $ \s ->
{-# INLINE newBytesAs #-}
newBytesAs :: PinnedState -> Int -> IO MutByteArray
newBytesAs Unpinned = newByteArray
newBytesAs Pinned = pinnedNewByteArray
newBytesAs Unpinned = new
newBytesAs Pinned = pinnedNew
-------------------------------------------------------------------------------
-- Copying

View File

@ -22,7 +22,7 @@ module Streamly.Test.Data.Serialize (main) where
--------------------------------------------------------------------------------
import System.Random (randomRIO)
import Streamly.Internal.Data.MutByteArray (MutByteArray, newByteArray)
import Streamly.Internal.Data.MutByteArray (MutByteArray)
import GHC.Generics (Generic)
import Streamly.Data.MutByteArray (Serialize)
import Streamly.Test.Data.Serialize.TH (genDatatype)
@ -169,7 +169,7 @@ poke val = do
let arrSize = sz + excessSize
serStartOff = randomOff
serEndOff = randomOff + sz
arr <- newByteArray arrSize
arr <- Serialize.new arrSize
off1 <- Serialize.serialize serStartOff arr val
off1 `shouldBe` serEndOff

View File

@ -28,6 +28,7 @@ import GHC.Generics (Generic, Rep(..))
import GHC.Real (Ratio(..))
import Streamly.Internal.Data.MutByteArray
import qualified Streamly.Internal.Data.MutByteArray as MBA
import Test.Hspec as H
@ -198,7 +199,7 @@ testSerialization val = do
#else
(sizeOf (Proxy :: Proxy a))
#endif
arr <- newByteArray len
arr <- MBA.new len
nextOff <- POKE(0, arr, val)
(nextOff1, val1) <- PEEK(0, arr, len)
val1 `shouldBe` val
@ -232,7 +233,7 @@ testGenericConsistency val = do
len `shouldBe` genericSizeOf (Proxy :: Proxy a)
-- Test the serialization and deserialization
arr <- newByteArray (sizeOf (Proxy :: Proxy a))
arr <- MBA.new (sizeOf (Proxy :: Proxy a))
nextOff <- POKE(0, arr, val)
genericPeekByteIndex arr 0 `shouldReturn` val

View File

@ -16,6 +16,7 @@ module Streamly.Test.Data.Unbox.TH (main) where
import Data.Proxy (Proxy(..))
import Streamly.Internal.Data.MutByteArray
import qualified Streamly.Internal.Data.MutByteArray as MBA
import Test.Hspec as H
@ -28,7 +29,7 @@ testSerialization ::
=> a
-> IO ()
testSerialization val = do
arr <- newByteArray (sizeOf (Proxy :: Proxy a))
arr <- MBA.new (sizeOf (Proxy :: Proxy a))
pokeByteIndex 0 arr val
peekByteIndex 0 arr `shouldReturn` val