Skip to content

Commit

Permalink
Add readMaybe to API for mutable vectors
Browse files Browse the repository at this point in the history
Fixes #341

Co-authored-by: konsumlamm <[email protected]>
Co-authored-by: Alexey Kuleshevich <[email protected]>
  • Loading branch information
3 people committed Dec 5, 2021
1 parent 7ce76a5 commit 70199ef
Show file tree
Hide file tree
Showing 5 changed files with 97 additions and 20 deletions.
22 changes: 19 additions & 3 deletions vector/src/Data/Vector/Generic/Mutable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module Data.Vector.Generic.Mutable (
clear,

-- * Accessing individual elements
read, write, modify, modifyM, swap, exchange,
read, readMaybe, write, modify, modifyM, swap, exchange,
unsafeRead, unsafeWrite, unsafeModify, unsafeModifyM, unsafeSwap, unsafeExchange,

-- * Folds
Expand Down Expand Up @@ -635,8 +635,8 @@ clear = stToPrim . basicClear
-- Accessing individual elements
-- -----------------------------

-- | Yield the element at the given position. Will throw exception if
-- index is out of range.
-- | Yield the element at the given position. Will throw an exception if
-- the index is out of range.
--
-- ==== __Examples__
--
Expand All @@ -649,6 +649,22 @@ read :: (HasCallStack, PrimMonad m, MVector v a) => v (PrimState m) a -> Int ->
read v i = checkIndex Bounds i (length v)
$ unsafeRead v i

-- | Yield the element at the given position. Returns 'Nothing' if
-- the index is out of range.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector.Mutable as MV
-- >>> v <- MV.generate 10 (\x -> x*x)
-- >>> MV.readMaybe v 3
-- Just 9
-- >>> MV.readMaybe v 13
-- Nothing
readMaybe :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> m (Maybe a)
{-# INLINE readMaybe #-}
readMaybe v i | i `inRange` (length v) = Just <$> unsafeRead v i
| otherwise = pure Nothing

-- | Replace the element at the given position.
write :: (HasCallStack, PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> a -> m ()
{-# INLINE write #-}
Expand Down
21 changes: 18 additions & 3 deletions vector/src/Data/Vector/Mutable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module Data.Vector.Mutable (
clear,

-- * Accessing individual elements
read, write, modify, modifyM, swap, exchange,
read, readMaybe, write, modify, modifyM, swap, exchange,
unsafeRead, unsafeWrite, unsafeModify, unsafeModifyM, unsafeSwap, unsafeExchange,

-- * Folds
Expand Down Expand Up @@ -424,8 +424,8 @@ clear = G.clear
-- Accessing individual elements
-- -----------------------------

-- | Yield the element at the given position. Will throw exception if
-- index is out of range.
-- | Yield the element at the given position. Will throw an exception if
-- the index is out of range.
--
-- ==== __Examples__
--
Expand All @@ -437,6 +437,21 @@ read :: PrimMonad m => MVector (PrimState m) a -> Int -> m a
{-# INLINE read #-}
read = G.read

-- | Yield the element at the given position. Returns 'Nothing' if
-- the index is out of range.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector.Mutable as MV
-- >>> v <- MV.generate 10 (\x -> x*x)
-- >>> MV.readMaybe v 3
-- Just 9
-- >>> MV.readMaybe v 13
-- Nothing
readMaybe :: (PrimMonad m) => MVector (PrimState m) a -> Int -> m (Maybe a)
{-# INLINE readMaybe #-}
readMaybe = G.readMaybe

-- | Replace the element at the given position.
write :: PrimMonad m => MVector (PrimState m) a -> Int -> a -> m ()
{-# INLINE write #-}
Expand Down
26 changes: 21 additions & 5 deletions vector/src/Data/Vector/Primitive/Mutable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ module Data.Vector.Primitive.Mutable (
clear,

-- * Accessing individual elements
read, write, modify, modifyM, swap, exchange,
read, readMaybe, write, modify, modifyM, swap, exchange,
unsafeRead, unsafeWrite, unsafeModify, unsafeModifyM, unsafeSwap, unsafeExchange,

-- * Folds
Expand Down Expand Up @@ -386,19 +386,35 @@ clear = G.clear
-- Accessing individual elements
-- -----------------------------

-- | Yield the element at the given position. Will throw exception if
-- index is out of range.
-- | Yield the element at the given position. Will throw an exception if
-- the index is out of range.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector.Primitive.Mutable as MVP
-- >>> v <- MV.generate 10 (\x -> x*x)
-- >>> MV.read v 3
-- >>> v <- MVP.generate 10 (\x -> x*x)
-- >>> MVP.read v 3
-- 9
read :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> Int -> m a
{-# INLINE read #-}
read = G.read

-- | Yield the element at the given position. Returns 'Nothing' if
-- the index is out of range.

--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector.Primitive.Mutable as MVP
-- >>> v <- MVP.generate 10 (\x -> x*x)
-- >>> MVP.readMaybe v 3
-- Just 9
-- >>> MVP.readMaybe v 13
-- Nothing
readMaybe :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> Int -> m (Maybe a)
{-# INLINE readMaybe #-}
readMaybe = G.readMaybe

-- | Replace the element at the given position.
write :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> Int -> a -> m ()
{-# INLINE write #-}
Expand Down
25 changes: 20 additions & 5 deletions vector/src/Data/Vector/Storable/Mutable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module Data.Vector.Storable.Mutable(
clear,

-- * Accessing individual elements
read, write, modify, modifyM, swap, exchange,
read, readMaybe, write, modify, modifyM, swap, exchange,
unsafeRead, unsafeWrite, unsafeModify, unsafeModifyM, unsafeSwap, unsafeExchange,

-- * Folds
Expand Down Expand Up @@ -485,19 +485,34 @@ clear = G.clear
-- Accessing individual elements
-- -----------------------------

-- | Yield the element at the given position. Will throw exception if
-- index is out of range.
-- | Yield the element at the given position. Will throw an exception if
-- the index is out of range.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector.Storable.Mutable as MVS
-- >>> v <- MV.generate 10 (\x -> x*x)
-- >>> MV.read v 3
-- >>> v <- MVS.generate 10 (\x -> x*x)
-- >>> MVS.read v 3
-- 9
read :: (PrimMonad m, Storable a) => MVector (PrimState m) a -> Int -> m a
{-# INLINE read #-}
read = G.read

-- | Yield the element at the given position. Returns 'Nothing' if
-- the index is out of range.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector.Storable.Mutable as MVS
-- >>> v <- MVS.generate 10 (\x -> x*x)
-- >>> MVS.readMaybe v 3
-- Just 9
-- >>> MVS.readMaybe v 13
-- Nothing
readMaybe :: (PrimMonad m, Storable a) => MVector (PrimState m) a -> Int -> m (Maybe a)
{-# INLINE readMaybe #-}
readMaybe = G.readMaybe

-- | Replace the element at the given position.
write
:: (PrimMonad m, Storable a) => MVector (PrimState m) a -> Int -> a -> m ()
Expand Down
23 changes: 19 additions & 4 deletions vector/src/Data/Vector/Unboxed/Mutable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ module Data.Vector.Unboxed.Mutable (
unzip, unzip3, unzip4, unzip5, unzip6,

-- * Accessing individual elements
read, write, modify, modifyM, swap, exchange,
read, readMaybe, write, modify, modifyM, swap, exchange,
unsafeRead, unsafeWrite, unsafeModify, unsafeModifyM, unsafeSwap, unsafeExchange,

-- * Folds
Expand Down Expand Up @@ -293,19 +293,34 @@ clear = G.clear
-- Accessing individual elements
-- -----------------------------

-- | Yield the element at the given position. Will throw exception if
-- index is out of range.
-- | Yield the element at the given position. Will throw an exception if
-- the index is out of range.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector.Unboxed.Mutable as MVU
-- >>> v <- MV.generate 10 (\x -> x*x)
-- >>> v <- MVU.generate 10 (\x -> x*x)
-- >>> MV.read v 3
-- 9
read :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m a
{-# INLINE read #-}
read = G.read

-- | Yield the element at the given position. Returns 'Nothing' if
-- the index is out of range.
--
-- ==== __Examples__
--
-- >>> import qualified Data.Vector.Unboxed.Mutable as MVU
-- >>> v <- MVU.generate 10 (\x -> x*x)
-- >>> MVU.readMaybe v 3
-- Just 9
-- >>> MVU.readMaybe v 13
-- Nothing
readMaybe :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m (Maybe a)
{-# INLINE readMaybe #-}
readMaybe = G.readMaybe

-- | Replace the element at the given position.
write :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> a -> m ()
{-# INLINE write #-}
Expand Down

0 comments on commit 70199ef

Please sign in to comment.