diff --git a/vector/changelog.md b/vector/changelog.md index 2259a7ff..ed7e85c2 100644 --- a/vector/changelog.md +++ b/vector/changelog.md @@ -2,7 +2,9 @@ * [#522](https://github.com/haskell/vector/pull/522) API using Applicatives added: `traverse` & friends. - * [#518](https://github.com/haskell/vector/pull/518) `UnboxViaStorable` added. + * [#545](https://github.com/haskell/vector/pull/545) `mapInPlace`, + `imapInPlace`, `mapInPlaceM`, `imapInPlaceM` added to mutable vectors API. + * [#518](https://github.com/haskell/vector/pull/518) `UnboxViaStorable` added. Vector constructors are reexported for `DoNotUnbox*`. * [#531](https://github.com/haskell/vector/pull/531) `iconcatMap` added. diff --git a/vector/src/Data/Vector/Generic/Mutable.hs b/vector/src/Data/Vector/Generic/Mutable.hs index 0f55e6f1..7ccf21dc 100644 --- a/vector/src/Data/Vector/Generic/Mutable.hs +++ b/vector/src/Data/Vector/Generic/Mutable.hs @@ -58,6 +58,7 @@ module Data.Vector.Generic.Mutable ( ifoldr, ifoldr', ifoldrM, ifoldrM', -- * Modifying vectors + mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM, nextPermutation, nextPermutationBy, prevPermutation, prevPermutationBy, @@ -77,6 +78,7 @@ module Data.Vector.Generic.Mutable ( PrimMonad, PrimState, RealWorld ) where +import Control.Monad ((<=<)) import Data.Vector.Generic.Mutable.Base import qualified Data.Vector.Generic.Base as V @@ -1215,6 +1217,37 @@ partitionWithUnknown f s -- Modifying vectors -- ----------------- +-- | Modify vector in place by applying function to each element. +-- +-- @since NEXT_VERSION +mapInPlace :: (PrimMonad m, MVector v a) => (a -> a) -> v (PrimState m) a -> m () +{-# INLINE mapInPlace #-} +mapInPlace f = imapInPlace (\_ -> f) + +-- | Modify vector in place by applying function to each element and its index. +-- +-- @since NEXT_VERSION +imapInPlace :: (PrimMonad m, MVector v a) => (Int -> a -> a) -> v (PrimState m) a -> m () +{-# INLINE imapInPlace #-} +imapInPlace f v + = stToPrim $ iforM_ v $ \i -> unsafeWrite v i . f i + +-- | Modify vector in place by applying monadic function to each element in order. +-- +-- @since NEXT_VERSION +mapInPlaceM :: (PrimMonad m, MVector v a) => (a -> m a) -> v (PrimState m) a -> m () +{-# INLINE mapInPlaceM #-} +mapInPlaceM f + = imapInPlaceM (\_ -> f) + +-- | Modify vector in place by applying monadic function to each element and its index in order. +-- +-- @since NEXT_VERSION +imapInPlaceM :: (PrimMonad m, MVector v a) => (Int -> a -> m a) -> v (PrimState m) a -> m () +{-# INLINE imapInPlaceM #-} +imapInPlaceM f v + = iforM_ v $ \i -> unsafeWrite v i <=< f i + -- | Compute the (lexicographically) next permutation of the given vector in-place. -- Returns False when the input is the last item in the enumeration, i.e., if it is in diff --git a/vector/src/Data/Vector/Mutable.hs b/vector/src/Data/Vector/Mutable.hs index b84f242c..82a60c67 100644 --- a/vector/src/Data/Vector/Mutable.hs +++ b/vector/src/Data/Vector/Mutable.hs @@ -57,6 +57,7 @@ module Data.Vector.Mutable ( ifoldr, ifoldr', ifoldrM, ifoldrM', -- * Modifying vectors + mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM, nextPermutation, nextPermutationBy, prevPermutation, prevPermutationBy, @@ -571,6 +572,34 @@ unsafeMove = G.unsafeMove -- Modifying vectors -- ----------------- +-- | Modify vector in place by applying function to each element. +-- +-- @since NEXT_VERSION +mapInPlace :: (PrimMonad m) => (a -> a) -> MVector (PrimState m) a -> m () +{-# INLINE mapInPlace #-} +mapInPlace = G.mapInPlace + +-- | Modify vector in place by applying function to each element and its index. +-- +-- @since NEXT_VERSION +imapInPlace :: (PrimMonad m) => (Int -> a -> a) -> MVector (PrimState m) a -> m () +{-# INLINE imapInPlace #-} +imapInPlace = G.imapInPlace + +-- | Modify vector in place by applying monadic function to each element in order. +-- +-- @since NEXT_VERSION +mapInPlaceM :: (PrimMonad m) => (a -> m a) -> MVector (PrimState m) a -> m () +{-# INLINE mapInPlaceM #-} +mapInPlaceM = G.mapInPlaceM + +-- | Modify vector in place by applying monadic function to each element and its index in order. +-- +-- @since NEXT_VERSION +imapInPlaceM :: (PrimMonad m) => (Int -> a -> m a) -> MVector (PrimState m) a -> m () +{-# INLINE imapInPlaceM #-} +imapInPlaceM = G.imapInPlaceM + -- | Compute the (lexicographically) next permutation of the given vector in-place. -- Returns False when the input is the last item in the enumeration, i.e., if it is in -- weakly descending order. In this case the vector will not get updated, diff --git a/vector/src/Data/Vector/Primitive/Mutable.hs b/vector/src/Data/Vector/Primitive/Mutable.hs index 15710ff9..627a2350 100644 --- a/vector/src/Data/Vector/Primitive/Mutable.hs +++ b/vector/src/Data/Vector/Primitive/Mutable.hs @@ -56,6 +56,7 @@ module Data.Vector.Primitive.Mutable ( ifoldr, ifoldr', ifoldrM, ifoldrM', -- * Modifying vectors + mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM, nextPermutation, nextPermutationBy, prevPermutation, prevPermutationBy, @@ -535,6 +536,34 @@ unsafeMove = G.unsafeMove -- Modifying vectors -- ----------------- +-- | Modify vector in place by applying function to each element. +-- +-- @since NEXT_VERSION +mapInPlace :: (PrimMonad m, Prim a) => (a -> a) -> MVector (PrimState m) a -> m () +{-# INLINE mapInPlace #-} +mapInPlace = G.mapInPlace + +-- | Modify vector in place by applying function to each element and its index. +-- +-- @since NEXT_VERSION +imapInPlace :: (PrimMonad m, Prim a) => (Int -> a -> a) -> MVector (PrimState m) a -> m () +{-# INLINE imapInPlace #-} +imapInPlace = G.imapInPlace + +-- | Modify vector in place by applying monadic function to each element in order. +-- +-- @since NEXT_VERSION +mapInPlaceM :: (PrimMonad m, Prim a) => (a -> m a) -> MVector (PrimState m) a -> m () +{-# INLINE mapInPlaceM #-} +mapInPlaceM = G.mapInPlaceM + +-- | Modify vector in place by applying monadic function to each element and its index in order. +-- +-- @since NEXT_VERSION +imapInPlaceM :: (PrimMonad m, Prim a) => (Int -> a -> m a) -> MVector (PrimState m) a -> m () +{-# INLINE imapInPlaceM #-} +imapInPlaceM = G.imapInPlaceM + -- | Compute the (lexicographically) next permutation of the given vector in-place. -- Returns False when the input is the last item in the enumeration, i.e., if it is in -- weakly descending order. In this case the vector will not get updated, diff --git a/vector/src/Data/Vector/Storable/Mutable.hs b/vector/src/Data/Vector/Storable/Mutable.hs index ccde3c2e..524bd691 100644 --- a/vector/src/Data/Vector/Storable/Mutable.hs +++ b/vector/src/Data/Vector/Storable/Mutable.hs @@ -57,6 +57,7 @@ module Data.Vector.Storable.Mutable( ifoldr, ifoldr', ifoldrM, ifoldrM', -- * Modifying vectors + mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM, nextPermutation, nextPermutationBy, prevPermutation, prevPermutationBy, @@ -635,6 +636,35 @@ unsafeMove = G.unsafeMove -- Modifying vectors -- ----------------- + +-- | Modify vector in place by applying function to each element. +-- +-- @since NEXT_VERSION +mapInPlace :: (PrimMonad m, Storable a) => (a -> a) -> MVector (PrimState m) a -> m () +{-# INLINE mapInPlace #-} +mapInPlace = G.mapInPlace + +-- | Modify vector in place by applying function to each element and its index. +-- +-- @since NEXT_VERSION +imapInPlace :: (PrimMonad m, Storable a) => (Int -> a -> a) -> MVector (PrimState m) a -> m () +{-# INLINE imapInPlace #-} +imapInPlace = G.imapInPlace + +-- | Modify vector in place by applying monadic function to each element in order. +-- +-- @since NEXT_VERSION +mapInPlaceM :: (PrimMonad m, Storable a) => (a -> m a) -> MVector (PrimState m) a -> m () +{-# INLINE mapInPlaceM #-} +mapInPlaceM = G.mapInPlaceM + +-- | Modify vector in place by applying monadic function to each element and its index in order. +-- +-- @since NEXT_VERSION +imapInPlaceM :: (PrimMonad m, Storable a) => (Int -> a -> m a) -> MVector (PrimState m) a -> m () +{-# INLINE imapInPlaceM #-} +imapInPlaceM = G.imapInPlaceM + -- | Compute the (lexicographically) next permutation of the given vector in-place. -- Returns False when the input is the last item in the enumeration, i.e., if it is in -- weakly descending order. In this case the vector will not get updated, diff --git a/vector/src/Data/Vector/Strict/Mutable.hs b/vector/src/Data/Vector/Strict/Mutable.hs index 4a2fdd6f..7af79a75 100644 --- a/vector/src/Data/Vector/Strict/Mutable.hs +++ b/vector/src/Data/Vector/Strict/Mutable.hs @@ -61,6 +61,7 @@ module Data.Vector.Strict.Mutable ( ifoldr, ifoldr', ifoldrM, ifoldrM', -- * Modifying vectors + mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM, nextPermutation, nextPermutationBy, prevPermutation, prevPermutationBy, @@ -550,6 +551,34 @@ unsafeMove = G.unsafeMove -- Modifying vectors -- ----------------- +-- | Modify vector in place by applying function to each element. +-- +-- @since NEXT_VERSION +mapInPlace :: (PrimMonad m) => (a -> a) -> MVector (PrimState m) a -> m () +{-# INLINE mapInPlace #-} +mapInPlace = G.mapInPlace + +-- | Modify vector in place by applying function to each element and its index. +-- +-- @since NEXT_VERSION +imapInPlace :: (PrimMonad m) => (Int -> a -> a) -> MVector (PrimState m) a -> m () +{-# INLINE imapInPlace #-} +imapInPlace = G.imapInPlace + +-- | Modify vector in place by applying monadic function to each element in order. +-- +-- @since NEXT_VERSION +mapInPlaceM :: (PrimMonad m) => (a -> m a) -> MVector (PrimState m) a -> m () +{-# INLINE mapInPlaceM #-} +mapInPlaceM = G.mapInPlaceM + +-- | Modify vector in place by applying monadic function to each element and its index in order. +-- +-- @since NEXT_VERSION +imapInPlaceM :: (PrimMonad m) => (Int -> a -> m a) -> MVector (PrimState m) a -> m () +{-# INLINE imapInPlaceM #-} +imapInPlaceM = G.imapInPlaceM + -- | Compute the (lexicographically) next permutation of the given vector in-place. -- Returns False when the input is the last item in the enumeration, i.e., if it is in -- weakly descending order. In this case the vector will not get updated, diff --git a/vector/src/Data/Vector/Unboxed/Mutable.hs b/vector/src/Data/Vector/Unboxed/Mutable.hs index 0b0c9ec9..e7bcaed2 100644 --- a/vector/src/Data/Vector/Unboxed/Mutable.hs +++ b/vector/src/Data/Vector/Unboxed/Mutable.hs @@ -58,6 +58,7 @@ module Data.Vector.Unboxed.Mutable ( ifoldr, ifoldr', ifoldrM, ifoldrM', -- * Modifying vectors + mapInPlace, imapInPlace, mapInPlaceM, imapInPlaceM, nextPermutation, nextPermutationBy, prevPermutation, prevPermutationBy, @@ -442,6 +443,34 @@ unsafeMove = G.unsafeMove -- Modifying vectors -- ----------------- +-- | Modify vector in place by applying function to each element. +-- +-- @since NEXT_VERSION +mapInPlace :: (PrimMonad m, Unbox a) => (a -> a) -> MVector (PrimState m) a -> m () +{-# INLINE mapInPlace #-} +mapInPlace = G.mapInPlace + +-- | Modify vector in place by applying function to each element and its index. +-- +-- @since NEXT_VERSION +imapInPlace :: (PrimMonad m, Unbox a) => (Int -> a -> a) -> MVector (PrimState m) a -> m () +{-# INLINE imapInPlace #-} +imapInPlace = G.imapInPlace + +-- | Modify vector in place by applying monadic function to each element in order. +-- +-- @since NEXT_VERSION +mapInPlaceM :: (PrimMonad m, Unbox a) => (a -> m a) -> MVector (PrimState m) a -> m () +{-# INLINE mapInPlaceM #-} +mapInPlaceM = G.mapInPlaceM + +-- | Modify vector in place by applying monadic function to each element and its index in order. +-- +-- @since NEXT_VERSION +imapInPlaceM :: (PrimMonad m, Unbox a) => (Int -> a -> m a) -> MVector (PrimState m) a -> m () +{-# INLINE imapInPlaceM #-} +imapInPlaceM = G.imapInPlaceM + -- | Compute the (lexicographically) next permutation of the given vector in-place. -- Returns False when the input is the last item in the enumeration, i.e., if it is in -- weakly descending order. In this case the vector will not get updated, diff --git a/vector/tests/Tests/Vector/Property.hs b/vector/tests/Tests/Vector/Property.hs index f1326850..e5df9ab6 100644 --- a/vector/tests/Tests/Vector/Property.hs +++ b/vector/tests/Tests/Vector/Property.hs @@ -208,7 +208,8 @@ testPolymorphicFunctions _ = $(testProperties [ 'prop_mut_foldr, 'prop_mut_foldr', 'prop_mut_foldl, 'prop_mut_foldl', 'prop_mut_ifoldr, 'prop_mut_ifoldr', 'prop_mut_ifoldl, 'prop_mut_ifoldl', 'prop_mut_foldM, 'prop_mut_foldM', 'prop_mut_foldrM, 'prop_mut_foldrM', - 'prop_mut_ifoldM, 'prop_mut_ifoldM', 'prop_mut_ifoldrM, 'prop_mut_ifoldrM' + 'prop_mut_ifoldM, 'prop_mut_ifoldM', 'prop_mut_ifoldrM, 'prop_mut_ifoldrM', + 'prop_mut_mapInPlace, 'prop_mut_imapInPlace, 'prop_mut_mapInPlaceM, 'prop_mut_imapInPlaceM ]) where -- Prelude @@ -591,6 +592,33 @@ testPolymorphicFunctions _ = $(testProperties [ prop_mut_imapM_ :: P ((Int -> a -> Writer [a] ()) -> v a -> Writer [a] ()) = (\f v -> liftRunST $ MV.imapM_ (\i x -> hoistST $ f i x) =<< V.thaw v) `eq` imapM_ + prop_mut_mapInPlace :: P ((a -> a) -> v a -> v a) + prop_mut_mapInPlace + = (\f v -> runST $ do mv <- V.thaw v + MV.mapInPlace f mv + V.freeze mv + ) `eq` map + prop_mut_imapInPlace :: P ((Int -> a -> a) -> v a -> v a) + prop_mut_imapInPlace + = (\f v -> runST $ do mv <- V.thaw v + MV.imapInPlace f mv + V.freeze mv + ) `eq` imap + prop_mut_mapInPlaceM :: P ((a -> Writer [a] a) -> v a -> Writer [a] (v a)) + prop_mut_mapInPlaceM + = (\f v -> liftRunST $ do mv <- V.thaw v + MV.mapInPlaceM (\a -> hoistST $ f a) mv + V.freeze mv + ) `eq` mapM + prop_mut_imapInPlaceM :: P ((Int -> a -> Writer [a] a) -> v a -> Writer [a] (v a)) + prop_mut_imapInPlaceM + = (\f v -> liftRunST $ do mv <- V.thaw v + MV.imapInPlaceM (\i a -> hoistST (f i a)) mv + V.freeze mv + ) `eq` imapM + + + liftRunST :: (forall s. WriterT w (ST s) a) -> Writer w a liftRunST m = WriterT $ Identity $ runST $ runWriterT m diff --git a/vector/vector.cabal b/vector/vector.cabal index 177dac34..f4f38417 100644 --- a/vector/vector.cabal +++ b/vector/vector.cabal @@ -101,7 +101,6 @@ common flag-Wall if impl(ghc >= 8.0) && impl(ghc < 8.1) Ghc-Options: -Wno-redundant-constraints - Library import: flag-Wall Default-Language: Haskell2010 @@ -184,6 +183,9 @@ Library -- rewrite rules common tests-common Default-Language: Haskell2010 + -- Disable pointless warning about partial functions + if impl(ghc >= 9.8) + Ghc-Options: -Wno-x-partial Ghc-Options: -fno-warn-missing-signatures hs-source-dirs: tests Build-Depends: base >= 4.5 && < 5