Skip to content

Commit dae9d17

Browse files
authored
Merge pull request #425 from Shimuuar/safe-read
Add safe read variant for mutable vectors
2 parents 08e128d + 03b71a5 commit dae9d17

File tree

6 files changed

+137
-11
lines changed

6 files changed

+137
-11
lines changed

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

Lines changed: 28 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ module Data.Vector.Generic.Mutable (
4444
clear,
4545

4646
-- * Accessing individual elements
47-
read, write, modify, modifyM, swap, exchange,
47+
read, readMaybe, write, modify, modifyM, swap, exchange,
4848
unsafeRead, unsafeWrite, unsafeModify, unsafeModifyM, unsafeSwap, unsafeExchange,
4949

5050
-- * Folds
@@ -635,12 +635,38 @@ clear = stToPrim . basicClear
635635
-- Accessing individual elements
636636
-- -----------------------------
637637

638-
-- | Yield the element at the given position.
638+
-- | Yield the element at the given position. Will throw an exception if
639+
-- the index is out of range.
640+
--
641+
-- ==== __Examples__
642+
--
643+
-- >>> import qualified Data.Vector.Mutable as MV
644+
-- >>> v <- MV.generate 10 (\x -> x*x)
645+
-- >>> MV.read v 3
646+
-- 9
639647
read :: (HasCallStack, PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> m a
640648
{-# INLINE read #-}
641649
read v i = checkIndex Bounds i (length v)
642650
$ unsafeRead v i
643651

652+
-- | Yield the element at the given position. Returns 'Nothing' if
653+
-- the index is out of range.
654+
--
655+
-- @since 0.13
656+
--
657+
-- ==== __Examples__
658+
--
659+
-- >>> import qualified Data.Vector.Mutable as MV
660+
-- >>> v <- MV.generate 10 (\x -> x*x)
661+
-- >>> MV.readMaybe v 3
662+
-- Just 9
663+
-- >>> MV.readMaybe v 13
664+
-- Nothing
665+
readMaybe :: (PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> m (Maybe a)
666+
{-# INLINE readMaybe #-}
667+
readMaybe v i | i `inRange` (length v) = Just <$> unsafeRead v i
668+
| otherwise = pure Nothing
669+
644670
-- | Replace the element at the given position.
645671
write :: (HasCallStack, PrimMonad m, MVector v a) => v (PrimState m) a -> Int -> a -> m ()
646672
{-# INLINE write #-}

vector/src/Data/Vector/Mutable.hs

Lines changed: 27 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ module Data.Vector.Mutable (
4444
clear,
4545

4646
-- * Accessing individual elements
47-
read, write, modify, modifyM, swap, exchange,
47+
read, readMaybe, write, modify, modifyM, swap, exchange,
4848
unsafeRead, unsafeWrite, unsafeModify, unsafeModifyM, unsafeSwap, unsafeExchange,
4949

5050
-- * Folds
@@ -424,11 +424,36 @@ clear = G.clear
424424
-- Accessing individual elements
425425
-- -----------------------------
426426

427-
-- | Yield the element at the given position.
427+
-- | Yield the element at the given position. Will throw an exception if
428+
-- the index is out of range.
429+
--
430+
-- ==== __Examples__
431+
--
432+
-- >>> import qualified Data.Vector.Mutable as MV
433+
-- >>> v <- MV.generate 10 (\x -> x*x)
434+
-- >>> MV.read v 3
435+
-- 9
428436
read :: PrimMonad m => MVector (PrimState m) a -> Int -> m a
429437
{-# INLINE read #-}
430438
read = G.read
431439

440+
-- | Yield the element at the given position. Returns 'Nothing' if
441+
-- the index is out of range.
442+
--
443+
-- @since 0.13
444+
--
445+
-- ==== __Examples__
446+
--
447+
-- >>> import qualified Data.Vector.Mutable as MV
448+
-- >>> v <- MV.generate 10 (\x -> x*x)
449+
-- >>> MV.readMaybe v 3
450+
-- Just 9
451+
-- >>> MV.readMaybe v 13
452+
-- Nothing
453+
readMaybe :: (PrimMonad m) => MVector (PrimState m) a -> Int -> m (Maybe a)
454+
{-# INLINE readMaybe #-}
455+
readMaybe = G.readMaybe
456+
432457
-- | Replace the element at the given position.
433458
write :: PrimMonad m => MVector (PrimState m) a -> Int -> a -> m ()
434459
{-# INLINE write #-}

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

Lines changed: 27 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ module Data.Vector.Primitive.Mutable (
4343
clear,
4444

4545
-- * Accessing individual elements
46-
read, write, modify, modifyM, swap, exchange,
46+
read, readMaybe, write, modify, modifyM, swap, exchange,
4747
unsafeRead, unsafeWrite, unsafeModify, unsafeModifyM, unsafeSwap, unsafeExchange,
4848

4949
-- * Folds
@@ -386,11 +386,36 @@ clear = G.clear
386386
-- Accessing individual elements
387387
-- -----------------------------
388388

389-
-- | Yield the element at the given position.
389+
-- | Yield the element at the given position. Will throw an exception if
390+
-- the index is out of range.
391+
--
392+
-- ==== __Examples__
393+
--
394+
-- >>> import qualified Data.Vector.Primitive.Mutable as MVP
395+
-- >>> v <- MVP.generate 10 (\x -> x*x)
396+
-- >>> MVP.read v 3
397+
-- 9
390398
read :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> Int -> m a
391399
{-# INLINE read #-}
392400
read = G.read
393401

402+
-- | Yield the element at the given position. Returns 'Nothing' if
403+
-- the index is out of range.
404+
--
405+
-- @since 0.13
406+
--
407+
-- ==== __Examples__
408+
--
409+
-- >>> import qualified Data.Vector.Primitive.Mutable as MVP
410+
-- >>> v <- MVP.generate 10 (\x -> x*x)
411+
-- >>> MVP.readMaybe v 3
412+
-- Just 9
413+
-- >>> MVP.readMaybe v 13
414+
-- Nothing
415+
readMaybe :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> Int -> m (Maybe a)
416+
{-# INLINE readMaybe #-}
417+
readMaybe = G.readMaybe
418+
394419
-- | Replace the element at the given position.
395420
write :: (PrimMonad m, Prim a) => MVector (PrimState m) a -> Int -> a -> m ()
396421
{-# INLINE write #-}

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

Lines changed: 27 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ module Data.Vector.Storable.Mutable(
4444
clear,
4545

4646
-- * Accessing individual elements
47-
read, write, modify, modifyM, swap, exchange,
47+
read, readMaybe, write, modify, modifyM, swap, exchange,
4848
unsafeRead, unsafeWrite, unsafeModify, unsafeModifyM, unsafeSwap, unsafeExchange,
4949

5050
-- * Folds
@@ -485,11 +485,36 @@ clear = G.clear
485485
-- Accessing individual elements
486486
-- -----------------------------
487487

488-
-- | Yield the element at the given position.
488+
-- | Yield the element at the given position. Will throw an exception if
489+
-- the index is out of range.
490+
--
491+
-- ==== __Examples__
492+
--
493+
-- >>> import qualified Data.Vector.Storable.Mutable as MVS
494+
-- >>> v <- MVS.generate 10 (\x -> x*x)
495+
-- >>> MVS.read v 3
496+
-- 9
489497
read :: (PrimMonad m, Storable a) => MVector (PrimState m) a -> Int -> m a
490498
{-# INLINE read #-}
491499
read = G.read
492500

501+
-- | Yield the element at the given position. Returns 'Nothing' if
502+
-- the index is out of range.
503+
--
504+
-- @since 0.13
505+
--
506+
-- ==== __Examples__
507+
--
508+
-- >>> import qualified Data.Vector.Storable.Mutable as MVS
509+
-- >>> v <- MVS.generate 10 (\x -> x*x)
510+
-- >>> MVS.readMaybe v 3
511+
-- Just 9
512+
-- >>> MVS.readMaybe v 13
513+
-- Nothing
514+
readMaybe :: (PrimMonad m, Storable a) => MVector (PrimState m) a -> Int -> m (Maybe a)
515+
{-# INLINE readMaybe #-}
516+
readMaybe = G.readMaybe
517+
493518
-- | Replace the element at the given position.
494519
write
495520
:: (PrimMonad m, Storable a) => MVector (PrimState m) a -> Int -> a -> m ()

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

Lines changed: 27 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ module Data.Vector.Unboxed.Mutable (
4343
unzip, unzip3, unzip4, unzip5, unzip6,
4444

4545
-- * Accessing individual elements
46-
read, write, modify, modifyM, swap, exchange,
46+
read, readMaybe, write, modify, modifyM, swap, exchange,
4747
unsafeRead, unsafeWrite, unsafeModify, unsafeModifyM, unsafeSwap, unsafeExchange,
4848

4949
-- * Folds
@@ -293,11 +293,36 @@ clear = G.clear
293293
-- Accessing individual elements
294294
-- -----------------------------
295295

296-
-- | Yield the element at the given position.
296+
-- | Yield the element at the given position. Will throw an exception if
297+
-- the index is out of range.
298+
--
299+
-- ==== __Examples__
300+
--
301+
-- >>> import qualified Data.Vector.Unboxed.Mutable as MVU
302+
-- >>> v <- MVU.generate 10 (\x -> x*x)
303+
-- >>> MVU.read v 3
304+
-- 9
297305
read :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m a
298306
{-# INLINE read #-}
299307
read = G.read
300308

309+
-- | Yield the element at the given position. Returns 'Nothing' if
310+
-- the index is out of range.
311+
--
312+
-- @since 0.13
313+
--
314+
-- ==== __Examples__
315+
--
316+
-- >>> import qualified Data.Vector.Unboxed.Mutable as MVU
317+
-- >>> v <- MVU.generate 10 (\x -> x*x)
318+
-- >>> MVU.readMaybe v 3
319+
-- Just 9
320+
-- >>> MVU.readMaybe v 13
321+
-- Nothing
322+
readMaybe :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> m (Maybe a)
323+
{-# INLINE readMaybe #-}
324+
readMaybe = G.readMaybe
325+
301326
-- | Replace the element at the given position.
302327
write :: (PrimMonad m, Unbox a) => MVector (PrimState m) a -> Int -> a -> m ()
303328
{-# INLINE write #-}

vector/vector.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -266,7 +266,7 @@ test-suite vector-doctest
266266
buildable: False
267267
build-depends:
268268
base -any
269-
, doctest >=0.15 && <0.20
269+
, doctest >=0.15 && <0.21
270270
, primitive >= 0.6.4.0 && < 0.8
271271
, vector -any
272272

0 commit comments

Comments
 (0)