Skip to content

Commit 5f44b58

Browse files
committed
Merge pull request #35 from nanonaren/master
Modify at a given position for mutable vectors
2 parents 947aa93 + 3bc592f commit 5f44b58

File tree

5 files changed

+63
-10
lines changed

5 files changed

+63
-10
lines changed

Data/Vector/Generic/Mutable.hs

Lines changed: 15 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,8 @@ module Data.Vector.Generic.Mutable (
4040
clear,
4141

4242
-- * Accessing individual elements
43-
read, write, swap, exchange,
44-
unsafeRead, unsafeWrite, unsafeSwap, unsafeExchange,
43+
read, write, modify, swap, exchange,
44+
unsafeRead, unsafeWrite, unsafeModify, unsafeSwap, unsafeExchange,
4545

4646
-- * Modifying vectors
4747

@@ -687,6 +687,12 @@ write :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> a -> m ()
687687
write v i x = BOUNDS_CHECK(checkIndex) "write" i (length v)
688688
$ unsafeWrite v i x
689689

690+
-- | Modify the element at the given position.
691+
modify :: (PrimMonad m, MVector v a) => v (PrimState m) a -> (a -> a) -> Int -> m ()
692+
{-# INLINE modify #-}
693+
modify v f i = BOUNDS_CHECK(checkIndex) "modify" i (length v)
694+
$ unsafeModify v f i
695+
690696
-- | Swap the elements at the given positions.
691697
swap :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> Int -> m ()
692698
{-# INLINE swap #-}
@@ -713,6 +719,13 @@ unsafeWrite :: (PrimMonad m, MVector v a)
713719
unsafeWrite v i x = UNSAFE_CHECK(checkIndex) "unsafeWrite" i (length v)
714720
$ basicUnsafeWrite v i x
715721

722+
-- | Modify the element at the given position. No bounds checks are performed.
723+
unsafeModify :: (PrimMonad m, MVector v a) => v (PrimState m) a -> (a -> a) -> Int -> m ()
724+
{-# INLINE unsafeModify #-}
725+
unsafeModify v f i = UNSAFE_CHECK(checkIndex) "unsafeModify" i (length v)
726+
$ basicUnsafeRead v i >>= \x ->
727+
basicUnsafeWrite v i (f x)
728+
716729
-- | Swap the elements at the given positions. No bounds checks are performed.
717730
unsafeSwap :: (PrimMonad m, MVector v a)
718731
=> v (PrimState m) a -> Int -> Int -> m ()

Data/Vector/Mutable.hs

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,8 @@ module Data.Vector.Mutable (
4040
clear,
4141

4242
-- * Accessing individual elements
43-
read, write, swap,
44-
unsafeRead, unsafeWrite, unsafeSwap,
43+
read, write, modify, swap,
44+
unsafeRead, unsafeWrite, unsafeModify, unsafeSwap,
4545

4646
-- * Modifying vectors
4747

@@ -325,6 +325,11 @@ write :: PrimMonad m => MVector (PrimState m) a -> Int -> a -> m ()
325325
{-# INLINE write #-}
326326
write = G.write
327327

328+
-- | Modify the element at the given position.
329+
modify :: PrimMonad m => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
330+
{-# INLINE modify #-}
331+
modify = G.modify
332+
328333
-- | Swap the elements at the given positions.
329334
swap :: PrimMonad m => MVector (PrimState m) a -> Int -> Int -> m ()
330335
{-# INLINE swap #-}
@@ -341,6 +346,11 @@ unsafeWrite :: PrimMonad m => MVector (PrimState m) a -> Int -> a -> m ()
341346
{-# INLINE unsafeWrite #-}
342347
unsafeWrite = G.unsafeWrite
343348

349+
-- | Modify the element at the given position. No bounds checks are performed.
350+
unsafeModify :: PrimMonad m => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
351+
{-# INLINE unsafeModify #-}
352+
unsafeModify = G.unsafeModify
353+
344354
-- | Swap the elements at the given positions. No bounds checks are performed.
345355
unsafeSwap :: PrimMonad m => MVector (PrimState m) a -> Int -> Int -> m ()
346356
{-# INLINE unsafeSwap #-}

Data/Vector/Primitive/Mutable.hs

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,8 @@ module Data.Vector.Primitive.Mutable (
4040
clear,
4141

4242
-- * Accessing individual elements
43-
read, write, swap,
44-
unsafeRead, unsafeWrite, unsafeSwap,
43+
read, write, modify, swap,
44+
unsafeRead, unsafeWrite, unsafeModify, unsafeSwap,
4545

4646
-- * Modifying vectors
4747

@@ -264,6 +264,11 @@ write :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> Int -> a -> m ()
264264
{-# INLINE write #-}
265265
write = G.write
266266

267+
-- | Modify the element at the given position.
268+
modify :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
269+
{-# INLINE modify #-}
270+
modify = G.modify
271+
267272
-- | Swap the elements at the given positions.
268273
swap :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> Int -> Int -> m ()
269274
{-# INLINE swap #-}
@@ -281,6 +286,11 @@ unsafeWrite
281286
{-# INLINE unsafeWrite #-}
282287
unsafeWrite = G.unsafeWrite
283288

289+
-- | Modify the element at the given position. No bounds checks are performed.
290+
unsafeModify :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
291+
{-# INLINE unsafeModify #-}
292+
unsafeModify = G.unsafeModify
293+
284294
-- | Swap the elements at the given positions. No bounds checks are performed.
285295
unsafeSwap
286296
:: (PrimMonad m, Prim a) => MVector (PrimState m) a -> Int -> Int -> m ()

Data/Vector/Storable/Mutable.hs

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,8 @@ module Data.Vector.Storable.Mutable(
4040
clear,
4141

4242
-- * Accessing individual elements
43-
read, write, swap,
44-
unsafeRead, unsafeWrite, unsafeSwap,
43+
read, write, modify, swap,
44+
unsafeRead, unsafeWrite, unsafeModify, unsafeSwap,
4545

4646
-- * Modifying vectors
4747

@@ -336,6 +336,11 @@ write
336336
{-# INLINE write #-}
337337
write = G.write
338338

339+
-- | Modify the element at the given position.
340+
modify :: (PrimMonad m, Storable a) => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
341+
{-# INLINE modify #-}
342+
modify = G.modify
343+
339344
-- | Swap the elements at the given positions.
340345
swap
341346
:: (PrimMonad m, Storable a) => MVector (PrimState m) a -> Int -> Int -> m ()
@@ -354,6 +359,11 @@ unsafeWrite
354359
{-# INLINE unsafeWrite #-}
355360
unsafeWrite = G.unsafeWrite
356361

362+
-- | Modify the element at the given position. No bounds checks are performed.
363+
unsafeModify :: (PrimMonad m, Storable a) => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
364+
{-# INLINE unsafeModify #-}
365+
unsafeModify = G.unsafeModify
366+
357367
-- | Swap the elements at the given positions. No bounds checks are performed.
358368
unsafeSwap
359369
:: (PrimMonad m, Storable a) => MVector (PrimState m) a -> Int -> Int -> m ()

Data/Vector/Unboxed/Mutable.hs

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -44,8 +44,8 @@ module Data.Vector.Unboxed.Mutable (
4444
unzip, unzip3, unzip4, unzip5, unzip6,
4545

4646
-- * Accessing individual elements
47-
read, write, swap,
48-
unsafeRead, unsafeWrite, unsafeSwap,
47+
read, write, modify, swap,
48+
unsafeRead, unsafeWrite, unsafeModify, unsafeSwap,
4949

5050
-- * Modifying vectors
5151

@@ -211,6 +211,11 @@ write :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> a -> m ()
211211
{-# INLINE write #-}
212212
write = G.write
213213

214+
-- | Modify the element at the given position.
215+
modify :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
216+
{-# INLINE modify #-}
217+
modify = G.modify
218+
214219
-- | Swap the elements at the given positions.
215220
swap :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> Int -> m ()
216221
{-# INLINE swap #-}
@@ -228,6 +233,11 @@ unsafeWrite
228233
{-# INLINE unsafeWrite #-}
229234
unsafeWrite = G.unsafeWrite
230235

236+
-- | Modify the element at the given position. No bounds checks are performed.
237+
unsafeModify :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> (a -> a) -> Int -> m ()
238+
{-# INLINE unsafeModify #-}
239+
unsafeModify = G.unsafeModify
240+
231241
-- | Swap the elements at the given positions. No bounds checks are performed.
232242
unsafeSwap
233243
:: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> Int -> m ()

0 commit comments

Comments
 (0)