Skip to content

Commit 7b39212

Browse files
authored
Merge pull request #545 from Shimuuar/mutable_mapM
Add map for mutable vector which modify it in place.
2 parents f7d2d4f + b2e00f2 commit 7b39212

File tree

9 files changed

+214
-3
lines changed

9 files changed

+214
-3
lines changed

vector/changelog.md

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,9 @@
22

33
* [#522](https://github.com/haskell/vector/pull/522) API using Applicatives
44
added: `traverse` & friends.
5-
* [#518](https://github.com/haskell/vector/pull/518) `UnboxViaStorable` added.
5+
* [#545](https://github.com/haskell/vector/pull/545) `mapInPlace`,
6+
`imapInPlace`, `mapInPlaceM`, `imapInPlaceM` added to mutable vectors API.
7+
* [#518](https://github.com/haskell/vector/pull/518) `UnboxViaStorable` added.
68
Vector constructors are reexported for `DoNotUnbox*`.
79
* [#531](https://github.com/haskell/vector/pull/531) `iconcatMap` added.
810

vector/src/Data/Vector/Generic/Mutable.hs

Lines changed: 33 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,7 @@ module Data.Vector.Generic.Mutable (
5858
ifoldr, ifoldr', ifoldrM, ifoldrM',
5959

6060
-- * Modifying vectors
61+
mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM,
6162
nextPermutation, nextPermutationBy,
6263
prevPermutation, prevPermutationBy,
6364

@@ -77,6 +78,7 @@ module Data.Vector.Generic.Mutable (
7778
PrimMonad, PrimState, RealWorld
7879
) where
7980

81+
import Control.Monad ((<=<))
8082
import Data.Vector.Generic.Mutable.Base
8183
import qualified Data.Vector.Generic.Base as V
8284

@@ -1215,6 +1217,37 @@ partitionWithUnknown f s
12151217
-- Modifying vectors
12161218
-- -----------------
12171219

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+
12181251

12191252
-- | Compute the (lexicographically) next permutation of the given vector in-place.
12201253
-- Returns False when the input is the last item in the enumeration, i.e., if it is in

vector/src/Data/Vector/Mutable.hs

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -57,6 +57,7 @@ module Data.Vector.Mutable (
5757
ifoldr, ifoldr', ifoldrM, ifoldrM',
5858

5959
-- * Modifying vectors
60+
mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM,
6061
nextPermutation, nextPermutationBy,
6162
prevPermutation, prevPermutationBy,
6263

@@ -571,6 +572,34 @@ unsafeMove = G.unsafeMove
571572
-- Modifying vectors
572573
-- -----------------
573574

575+
-- | Modify vector in place by applying function to each element.
576+
--
577+
-- @since NEXT_VERSION
578+
mapInPlace :: (PrimMonad m) => (a -> a) -> MVector (PrimState m) a -> m ()
579+
{-# INLINE mapInPlace #-}
580+
mapInPlace = G.mapInPlace
581+
582+
-- | Modify vector in place by applying function to each element and its index.
583+
--
584+
-- @since NEXT_VERSION
585+
imapInPlace :: (PrimMonad m) => (Int -> a -> a) -> MVector (PrimState m) a -> m ()
586+
{-# INLINE imapInPlace #-}
587+
imapInPlace = G.imapInPlace
588+
589+
-- | Modify vector in place by applying monadic function to each element in order.
590+
--
591+
-- @since NEXT_VERSION
592+
mapInPlaceM :: (PrimMonad m) => (a -> m a) -> MVector (PrimState m) a -> m ()
593+
{-# INLINE mapInPlaceM #-}
594+
mapInPlaceM = G.mapInPlaceM
595+
596+
-- | Modify vector in place by applying monadic function to each element and its index in order.
597+
--
598+
-- @since NEXT_VERSION
599+
imapInPlaceM :: (PrimMonad m) => (Int -> a -> m a) -> MVector (PrimState m) a -> m ()
600+
{-# INLINE imapInPlaceM #-}
601+
imapInPlaceM = G.imapInPlaceM
602+
574603
-- | Compute the (lexicographically) next permutation of the given vector in-place.
575604
-- Returns False when the input is the last item in the enumeration, i.e., if it is in
576605
-- weakly descending order. In this case the vector will not get updated,

vector/src/Data/Vector/Primitive/Mutable.hs

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,7 @@ module Data.Vector.Primitive.Mutable (
5656
ifoldr, ifoldr', ifoldrM, ifoldrM',
5757

5858
-- * Modifying vectors
59+
mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM,
5960
nextPermutation, nextPermutationBy,
6061
prevPermutation, prevPermutationBy,
6162

@@ -535,6 +536,34 @@ unsafeMove = G.unsafeMove
535536
-- Modifying vectors
536537
-- -----------------
537538

539+
-- | Modify vector in place by applying function to each element.
540+
--
541+
-- @since NEXT_VERSION
542+
mapInPlace :: (PrimMonad m, Prim a) => (a -> a) -> MVector (PrimState m) a -> m ()
543+
{-# INLINE mapInPlace #-}
544+
mapInPlace = G.mapInPlace
545+
546+
-- | Modify vector in place by applying function to each element and its index.
547+
--
548+
-- @since NEXT_VERSION
549+
imapInPlace :: (PrimMonad m, Prim a) => (Int -> a -> a) -> MVector (PrimState m) a -> m ()
550+
{-# INLINE imapInPlace #-}
551+
imapInPlace = G.imapInPlace
552+
553+
-- | Modify vector in place by applying monadic function to each element in order.
554+
--
555+
-- @since NEXT_VERSION
556+
mapInPlaceM :: (PrimMonad m, Prim a) => (a -> m a) -> MVector (PrimState m) a -> m ()
557+
{-# INLINE mapInPlaceM #-}
558+
mapInPlaceM = G.mapInPlaceM
559+
560+
-- | Modify vector in place by applying monadic function to each element and its index in order.
561+
--
562+
-- @since NEXT_VERSION
563+
imapInPlaceM :: (PrimMonad m, Prim a) => (Int -> a -> m a) -> MVector (PrimState m) a -> m ()
564+
{-# INLINE imapInPlaceM #-}
565+
imapInPlaceM = G.imapInPlaceM
566+
538567
-- | Compute the (lexicographically) next permutation of the given vector in-place.
539568
-- Returns False when the input is the last item in the enumeration, i.e., if it is in
540569
-- weakly descending order. In this case the vector will not get updated,

vector/src/Data/Vector/Storable/Mutable.hs

Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -57,6 +57,7 @@ module Data.Vector.Storable.Mutable(
5757
ifoldr, ifoldr', ifoldrM, ifoldrM',
5858

5959
-- * Modifying vectors
60+
mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM,
6061
nextPermutation, nextPermutationBy,
6162
prevPermutation, prevPermutationBy,
6263

@@ -635,6 +636,35 @@ unsafeMove = G.unsafeMove
635636
-- Modifying vectors
636637
-- -----------------
637638

639+
640+
-- | Modify vector in place by applying function to each element.
641+
--
642+
-- @since NEXT_VERSION
643+
mapInPlace :: (PrimMonad m, Storable a) => (a -> a) -> MVector (PrimState m) a -> m ()
644+
{-# INLINE mapInPlace #-}
645+
mapInPlace = G.mapInPlace
646+
647+
-- | Modify vector in place by applying function to each element and its index.
648+
--
649+
-- @since NEXT_VERSION
650+
imapInPlace :: (PrimMonad m, Storable a) => (Int -> a -> a) -> MVector (PrimState m) a -> m ()
651+
{-# INLINE imapInPlace #-}
652+
imapInPlace = G.imapInPlace
653+
654+
-- | Modify vector in place by applying monadic function to each element in order.
655+
--
656+
-- @since NEXT_VERSION
657+
mapInPlaceM :: (PrimMonad m, Storable a) => (a -> m a) -> MVector (PrimState m) a -> m ()
658+
{-# INLINE mapInPlaceM #-}
659+
mapInPlaceM = G.mapInPlaceM
660+
661+
-- | Modify vector in place by applying monadic function to each element and its index in order.
662+
--
663+
-- @since NEXT_VERSION
664+
imapInPlaceM :: (PrimMonad m, Storable a) => (Int -> a -> m a) -> MVector (PrimState m) a -> m ()
665+
{-# INLINE imapInPlaceM #-}
666+
imapInPlaceM = G.imapInPlaceM
667+
638668
-- | Compute the (lexicographically) next permutation of the given vector in-place.
639669
-- Returns False when the input is the last item in the enumeration, i.e., if it is in
640670
-- weakly descending order. In this case the vector will not get updated,

vector/src/Data/Vector/Strict/Mutable.hs

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -61,6 +61,7 @@ module Data.Vector.Strict.Mutable (
6161
ifoldr, ifoldr', ifoldrM, ifoldrM',
6262

6363
-- * Modifying vectors
64+
mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM,
6465
nextPermutation, nextPermutationBy,
6566
prevPermutation, prevPermutationBy,
6667

@@ -550,6 +551,34 @@ unsafeMove = G.unsafeMove
550551
-- Modifying vectors
551552
-- -----------------
552553

554+
-- | Modify vector in place by applying function to each element.
555+
--
556+
-- @since NEXT_VERSION
557+
mapInPlace :: (PrimMonad m) => (a -> a) -> MVector (PrimState m) a -> m ()
558+
{-# INLINE mapInPlace #-}
559+
mapInPlace = G.mapInPlace
560+
561+
-- | Modify vector in place by applying function to each element and its index.
562+
--
563+
-- @since NEXT_VERSION
564+
imapInPlace :: (PrimMonad m) => (Int -> a -> a) -> MVector (PrimState m) a -> m ()
565+
{-# INLINE imapInPlace #-}
566+
imapInPlace = G.imapInPlace
567+
568+
-- | Modify vector in place by applying monadic function to each element in order.
569+
--
570+
-- @since NEXT_VERSION
571+
mapInPlaceM :: (PrimMonad m) => (a -> m a) -> MVector (PrimState m) a -> m ()
572+
{-# INLINE mapInPlaceM #-}
573+
mapInPlaceM = G.mapInPlaceM
574+
575+
-- | Modify vector in place by applying monadic function to each element and its index in order.
576+
--
577+
-- @since NEXT_VERSION
578+
imapInPlaceM :: (PrimMonad m) => (Int -> a -> m a) -> MVector (PrimState m) a -> m ()
579+
{-# INLINE imapInPlaceM #-}
580+
imapInPlaceM = G.imapInPlaceM
581+
553582
-- | Compute the (lexicographically) next permutation of the given vector in-place.
554583
-- Returns False when the input is the last item in the enumeration, i.e., if it is in
555584
-- weakly descending order. In this case the vector will not get updated,

vector/src/Data/Vector/Unboxed/Mutable.hs

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,7 @@ module Data.Vector.Unboxed.Mutable (
5858
ifoldr, ifoldr', ifoldrM, ifoldrM',
5959

6060
-- * Modifying vectors
61+
mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM,
6162
nextPermutation, nextPermutationBy,
6263
prevPermutation, prevPermutationBy,
6364

@@ -442,6 +443,34 @@ unsafeMove = G.unsafeMove
442443
-- Modifying vectors
443444
-- -----------------
444445

446+
-- | Modify vector in place by applying function to each element.
447+
--
448+
-- @since NEXT_VERSION
449+
mapInPlace :: (PrimMonad m, Unbox a) => (a -> a) -> MVector (PrimState m) a -> m ()
450+
{-# INLINE mapInPlace #-}
451+
mapInPlace = G.mapInPlace
452+
453+
-- | Modify vector in place by applying function to each element and its index.
454+
--
455+
-- @since NEXT_VERSION
456+
imapInPlace :: (PrimMonad m, Unbox a) => (Int -> a -> a) -> MVector (PrimState m) a -> m ()
457+
{-# INLINE imapInPlace #-}
458+
imapInPlace = G.imapInPlace
459+
460+
-- | Modify vector in place by applying monadic function to each element in order.
461+
--
462+
-- @since NEXT_VERSION
463+
mapInPlaceM :: (PrimMonad m, Unbox a) => (a -> m a) -> MVector (PrimState m) a -> m ()
464+
{-# INLINE mapInPlaceM #-}
465+
mapInPlaceM = G.mapInPlaceM
466+
467+
-- | Modify vector in place by applying monadic function to each element and its index in order.
468+
--
469+
-- @since NEXT_VERSION
470+
imapInPlaceM :: (PrimMonad m, Unbox a) => (Int -> a -> m a) -> MVector (PrimState m) a -> m ()
471+
{-# INLINE imapInPlaceM #-}
472+
imapInPlaceM = G.imapInPlaceM
473+
445474
-- | Compute the (lexicographically) next permutation of the given vector in-place.
446475
-- Returns False when the input is the last item in the enumeration, i.e., if it is in
447476
-- weakly descending order. In this case the vector will not get updated,

vector/tests/Tests/Vector/Property.hs

Lines changed: 29 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -208,7 +208,8 @@ testPolymorphicFunctions _ = $(testProperties [
208208
'prop_mut_foldr, 'prop_mut_foldr', 'prop_mut_foldl, 'prop_mut_foldl',
209209
'prop_mut_ifoldr, 'prop_mut_ifoldr', 'prop_mut_ifoldl, 'prop_mut_ifoldl',
210210
'prop_mut_foldM, 'prop_mut_foldM', 'prop_mut_foldrM, 'prop_mut_foldrM',
211-
'prop_mut_ifoldM, 'prop_mut_ifoldM', 'prop_mut_ifoldrM, 'prop_mut_ifoldrM'
211+
'prop_mut_ifoldM, 'prop_mut_ifoldM', 'prop_mut_ifoldrM, 'prop_mut_ifoldrM',
212+
'prop_mut_mapInPlace, 'prop_mut_imapInPlace, 'prop_mut_mapInPlaceM, 'prop_mut_imapInPlaceM
212213
])
213214
where
214215
-- Prelude
@@ -591,6 +592,33 @@ testPolymorphicFunctions _ = $(testProperties [
591592
prop_mut_imapM_ :: P ((Int -> a -> Writer [a] ()) -> v a -> Writer [a] ())
592593
= (\f v -> liftRunST $ MV.imapM_ (\i x -> hoistST $ f i x) =<< V.thaw v) `eq` imapM_
593594

595+
prop_mut_mapInPlace :: P ((a -> a) -> v a -> v a)
596+
prop_mut_mapInPlace
597+
= (\f v -> runST $ do mv <- V.thaw v
598+
MV.mapInPlace f mv
599+
V.freeze mv
600+
) `eq` map
601+
prop_mut_imapInPlace :: P ((Int -> a -> a) -> v a -> v a)
602+
prop_mut_imapInPlace
603+
= (\f v -> runST $ do mv <- V.thaw v
604+
MV.imapInPlace f mv
605+
V.freeze mv
606+
) `eq` imap
607+
prop_mut_mapInPlaceM :: P ((a -> Writer [a] a) -> v a -> Writer [a] (v a))
608+
prop_mut_mapInPlaceM
609+
= (\f v -> liftRunST $ do mv <- V.thaw v
610+
MV.mapInPlaceM (\a -> hoistST $ f a) mv
611+
V.freeze mv
612+
) `eq` mapM
613+
prop_mut_imapInPlaceM :: P ((Int -> a -> Writer [a] a) -> v a -> Writer [a] (v a))
614+
prop_mut_imapInPlaceM
615+
= (\f v -> liftRunST $ do mv <- V.thaw v
616+
MV.imapInPlaceM (\i a -> hoistST (f i a)) mv
617+
V.freeze mv
618+
) `eq` imapM
619+
620+
621+
594622

595623
liftRunST :: (forall s. WriterT w (ST s) a) -> Writer w a
596624
liftRunST m = WriterT $ Identity $ runST $ runWriterT m

vector/vector.cabal

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -101,7 +101,6 @@ common flag-Wall
101101
if impl(ghc >= 8.0) && impl(ghc < 8.1)
102102
Ghc-Options: -Wno-redundant-constraints
103103

104-
105104
Library
106105
import: flag-Wall
107106
Default-Language: Haskell2010
@@ -184,6 +183,9 @@ Library
184183
-- rewrite rules
185184
common tests-common
186185
Default-Language: Haskell2010
186+
-- Disable pointless warning about partial functions
187+
if impl(ghc >= 9.8)
188+
Ghc-Options: -Wno-x-partial
187189
Ghc-Options: -fno-warn-missing-signatures
188190
hs-source-dirs: tests
189191
Build-Depends: base >= 4.5 && < 5

0 commit comments

Comments
 (0)