Change the argument order of put/modifyIndex

This commit is contained in:
Harendra Kumar 2022-12-27 10:43:30 +05:30
parent af00deb8c4
commit 94f3134643
5 changed files with 23 additions and 23 deletions

View File

@ -266,7 +266,7 @@ o_1_space_serial_marray value ~(array, indices) =
, benchIO' "strip (> 0)" (const (return array))
$ MArray.strip (> 0)
, benchIO' "modifyIndices (+ 1)" (const (return indices))
$ Stream.fold (MArray.modifyIndices (\_idx val -> val + 1) array)
$ Stream.fold (MArray.modifyIndices array (\_idx val -> val + 1))
. Stream.unfold Array.reader
]

View File

@ -477,8 +477,8 @@ withNewArrayUnsafe count f = do
-- /Pre-release/
{-# INLINE putIndexUnsafe #-}
putIndexUnsafe :: forall m a. (MonadIO m, Unbox a)
=> Int -> a -> Array a -> m ()
putIndexUnsafe i x Array{..} = do
=> Int -> Array a -> a -> m ()
putIndexUnsafe i Array{..} x = do
let index = INDEX_OF(arrStart, i, a)
assert (i >= 0 && INDEX_VALID(index, arrEnd, a)) (return ())
liftIO $ pokeWith arrContents index x
@ -490,13 +490,13 @@ invalidIndex label i =
-- | /O(1)/ Write the given element at the given index in the array.
-- Performs in-place mutation of the array.
--
-- >>> putIndex arr ix val = Array.modifyIndex ix (const (val, ())) arr
-- >>> putIndex ix arr val = Array.modifyIndex ix arr (const (val, ()))
-- >>> f = Array.putIndices
-- >>> putIndex ix val arr = Stream.fold (f arr) (Stream.fromPure (ix, val))
-- >>> putIndex ix arr val = Stream.fold (f arr) (Stream.fromPure (ix, val))
--
{-# INLINE putIndex #-}
putIndex :: forall m a. (MonadIO m, Unbox a) => Int -> a -> Array a -> m ()
putIndex i x Array{..} = do
putIndex :: forall m a. (MonadIO m, Unbox a) => Int -> Array a -> a -> m ()
putIndex i Array{..} x = do
let index = INDEX_OF(arrStart,i,a)
if i >= 0 && INDEX_VALID(index,arrEnd,a)
then liftIO $ pokeWith arrContents index x
@ -513,14 +513,14 @@ putIndices arr = FL.foldlM' step (return ())
where
step () (i, x) = liftIO (putIndex i x arr)
step () (i, x) = liftIO (putIndex i arr x)
-- | Modify a given index of an array using a modifier function.
--
-- /Pre-release/
modifyIndexUnsafe :: forall m a b. (MonadIO m, Unbox a) =>
Int -> (a -> (a, b)) -> Array a -> m b
modifyIndexUnsafe i f Array{..} = liftIO $ do
Int -> Array a -> (a -> (a, b)) -> m b
modifyIndexUnsafe i Array{..} f = liftIO $ do
let index = INDEX_OF(arrStart,i,a)
assert (i >= 0 && INDEX_NEXT(index,a) <= arrEnd) (return ())
r <- peekWith arrContents index
@ -532,8 +532,8 @@ modifyIndexUnsafe i f Array{..} = liftIO $ do
--
-- /Pre-release/
modifyIndex :: forall m a b. (MonadIO m, Unbox a) =>
Int -> (a -> (a, b)) -> Array a -> m b
modifyIndex i f Array{..} = do
Int -> Array a -> (a -> (a, b)) -> m b
modifyIndex i Array{..} f = do
let index = INDEX_OF(arrStart,i,a)
if i >= 0 && INDEX_VALID(index,arrEnd,a)
then liftIO $ do
@ -549,8 +549,8 @@ modifyIndex i f Array{..} = do
-- /Pre-release/
{-# INLINE modifyIndices #-}
modifyIndices :: forall m a . (MonadIO m, Unbox a)
=> (Int -> a -> a) -> Array a -> Fold m Int ()
modifyIndices f arr = FL.foldlM' step initial
=> Array a -> (Int -> a -> a) -> Fold m Int ()
modifyIndices arr f = FL.foldlM' step initial
where
@ -558,14 +558,14 @@ modifyIndices f arr = FL.foldlM' step initial
step () i =
let f1 x = (f i x, ())
in modifyIndex i f1 arr
in modifyIndex i arr f1
-- | Modify each element of an array using the supplied modifier function.
--
-- /Pre-release/
modify :: forall m a. (MonadIO m, Unbox a)
=> (a -> a) -> Array a -> m ()
modify f Array{..} = liftIO $
=> Array a -> (a -> a) -> m ()
modify Array{..} f = liftIO $
go arrStart
where
@ -2341,7 +2341,7 @@ bubble cmp0 arr =
x1 <- getIndexUnsafe i arr
case x `cmp0` x1 of
LT -> do
putIndexUnsafe (i + 1) x1 arr
putIndexUnsafe (i + 1) arr x1
go x (i - 1)
_ -> putIndexUnsafe (i + 1) x arr
else putIndexUnsafe (i + 1) x arr
_ -> putIndexUnsafe (i + 1) arr x
else putIndexUnsafe (i + 1) arr x

View File

@ -2462,7 +2462,7 @@ bottomBy cmp n = Fold step initial extract
x1 <- MA.getIndexUnsafe (i - 1) arr
case x `cmp` x1 of
LT -> do
MA.putIndexUnsafe (i - 1) x arr
MA.putIndexUnsafe (i - 1) arr x
MA.bubble cmp arr
return $ Partial (arr, i)
_ -> return $ Partial (arr, i)

View File

@ -245,7 +245,7 @@ joinOuterGeneric eq s1 s =
if a `eq` b1
then do
CrossStream (Stream.fromEffect $ put True)
MA.putIndex i True foundArr
MA.putIndex i foundArr True
return (Just a, Just b1)
else CrossStream Stream.nil
Nothing -> return (Just a, Nothing)

View File

@ -59,7 +59,7 @@ testLengthFromStream = genericTestFrom (const A.fromStream)
unsafeWriteIndex :: [Int] -> Int -> Int -> IO Bool
unsafeWriteIndex xs i x = do
arr <- MA.fromList xs
MA.putIndexUnsafe i x arr
MA.putIndexUnsafe i arr x
x1 <- MA.getIndexUnsafe i arr
return $ x1 == x