@@ -58,6 +58,7 @@ module Data.Vector.Generic.Mutable (
58
58
ifoldr , ifoldr' , ifoldrM , ifoldrM' ,
59
59
60
60
-- * Modifying vectors
61
+ mapInPlace , imapInPlace , mapInPlaceM , imapInPlaceM ,
61
62
nextPermutation , nextPermutationBy ,
62
63
prevPermutation , prevPermutationBy ,
63
64
@@ -77,6 +78,7 @@ module Data.Vector.Generic.Mutable (
77
78
PrimMonad , PrimState , RealWorld
78
79
) where
79
80
81
+ import Control.Monad ((<=<) )
80
82
import Data.Vector.Generic.Mutable.Base
81
83
import qualified Data.Vector.Generic.Base as V
82
84
@@ -1215,6 +1217,37 @@ partitionWithUnknown f s
1215
1217
-- Modifying vectors
1216
1218
-- -----------------
1217
1219
1220
+ -- | Modify vector in place by applying function to each element.
1221
+ --
1222
+ -- @since NEXT_VERSION
1223
+ mapInPlace :: (PrimMonad m , MVector v a ) => (a -> a ) -> v (PrimState m ) a -> m ()
1224
+ {-# INLINE mapInPlace #-}
1225
+ mapInPlace f = imapInPlace (\ _ -> f)
1226
+
1227
+ -- | Modify vector in place by applying function to each element and its index.
1228
+ --
1229
+ -- @since NEXT_VERSION
1230
+ imapInPlace :: (PrimMonad m , MVector v a ) => (Int -> a -> a ) -> v (PrimState m ) a -> m ()
1231
+ {-# INLINE imapInPlace #-}
1232
+ imapInPlace f v
1233
+ = stToPrim $ iforM_ v $ \ i -> unsafeWrite v i . f i
1234
+
1235
+ -- | Modify vector in place by applying monadic function to each element in order.
1236
+ --
1237
+ -- @since NEXT_VERSION
1238
+ mapInPlaceM :: (PrimMonad m , MVector v a ) => (a -> m a ) -> v (PrimState m ) a -> m ()
1239
+ {-# INLINE mapInPlaceM #-}
1240
+ mapInPlaceM f
1241
+ = imapInPlaceM (\ _ -> f)
1242
+
1243
+ -- | Modify vector in place by applying monadic function to each element and its index in order.
1244
+ --
1245
+ -- @since NEXT_VERSION
1246
+ imapInPlaceM :: (PrimMonad m , MVector v a ) => (Int -> a -> m a ) -> v (PrimState m ) a -> m ()
1247
+ {-# INLINE imapInPlaceM #-}
1248
+ imapInPlaceM f v
1249
+ = iforM_ v $ \ i -> unsafeWrite v i <=< f i
1250
+
1218
1251
1219
1252
-- | Compute the (lexicographically) next permutation of the given vector in-place.
1220
1253
-- Returns False when the input is the last item in the enumeration, i.e., if it is in
0 commit comments