Skip to content

Commit

Permalink
#33 Implement iterateWithIndex
Browse files Browse the repository at this point in the history
  • Loading branch information
Bodigrim committed Jul 30, 2023
1 parent 4218f93 commit 88ef487
Show file tree
Hide file tree
Showing 3 changed files with 57 additions and 0 deletions.
1 change: 1 addition & 0 deletions changelog.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
# 0.4.0.0

* Add `foldr` catamorphism and `fromInfinite` / `toInfinite` conversions.
* Add `iterateWithIndex` and `iterateWithIndexM`.
* Remove instances `Foldable` and `Traversable`, they are too dangerous to diverge.

# 0.3.3.0
Expand Down
40 changes: 40 additions & 0 deletions src/Data/Chimera.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ module Data.Chimera (
tabulateFix,
tabulateFix',
iterate,
iterateWithIndex,
unfoldr,
cycle,
fromListWithDef,
Expand All @@ -53,6 +54,7 @@ module Data.Chimera (
tabulateFixM,
tabulateFixM',
iterateM,
iterateWithIndexM,
unfoldrM,

-- * Subvectors
Expand Down Expand Up @@ -359,6 +361,8 @@ tabulateFixM_ strat f = result
-- | 'iterate' @f@ @x@ returns an infinite stream, generated by
-- repeated applications of @f@ to @x@.
--
-- It holds that 'index' ('iterate' @f@ @x@) 0 is equal to @x@.
--
-- >>> ch = iterate (+ 1) 0 :: UChimera Int
-- >>> take 10 (toList ch)
-- [0,1,2,3,4,5,6,7,8,9]
Expand Down Expand Up @@ -432,6 +436,42 @@ unfoldrM f seed = do
(z, seed') <- unfoldrExactVecNM 1 f seed
zs <- go 0 seed'
pure $ Chimera $ A.fromListN (bits + 1) (z : zs)
{-# SPECIALIZE unfoldrM :: G.Vector v b => (a -> Identity (b, a)) -> a -> Identity (Chimera v b) #-}

-- | 'iterateWithIndex' @f@ @x@ returns an infinite stream, generated by
-- applications of @f@ to a current index and previous value, starting from @x@.
--
-- It holds that 'index' ('iterateWithIndex' @f@ @x@) 0 is equal to @x@.
--
-- >>> ch = iterateWithIndex (+) 100 :: UChimera Word
-- >>> take 10 (toList ch)
-- [100,101,103,106,110,115,121,128,136,145]
--
-- @since 0.4.0.0
iterateWithIndex :: G.Vector v a => (Word -> a -> a) -> a -> Chimera v a
iterateWithIndex f = runIdentity . iterateWithIndexM ((pure .) . f)

iterateWithIndexExactVecNM :: forall m a v. (Monad m, G.Vector v a) => Int -> (Word -> a -> m a) -> a -> m (v a)
iterateWithIndexExactVecNM n f s = G.unfoldrExactNM n go (int2word n, s)
where
go :: (Word, a) -> m (a, (Word, a))
go (i, x) = do
x' <- f i x
pure (x', (i + 1, x'))

-- | Monadic version of 'iterateWithIndex'.
--
-- @since 0.4.0.0
iterateWithIndexM :: (Monad m, G.Vector v a) => (Word -> a -> m a) -> a -> m (Chimera v a)
iterateWithIndexM f seed = do
nextSeed <- f 1 seed
let z = G.singleton seed
zs <- iterateListNM bits go (G.singleton nextSeed)
pure $ Chimera $ A.fromListN (bits + 1) (z : zs)
where
go vec =
iterateWithIndexExactVecNM (G.length vec `shiftL` 1) f (G.unsafeLast vec)
{-# SPECIALIZE iterateWithIndexM :: G.Vector v a => (Word -> a -> Identity a) -> a -> Identity (Chimera v a) #-}

interleaveVec :: G.Vector v a => v a -> v a -> v a
interleaveVec as bs =
Expand Down
16 changes: 16 additions & 0 deletions test/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -103,6 +103,19 @@ chimeraTests = testGroup "Chimera"
let jx = ix `mod` 65536 in
iterate f seed !! fromIntegral jx === Ch.index (Ch.iterate f seed :: UChimera Word) jx

, QC.testProperty "head . iterate" $
\(Fun _ (f :: Word -> Word)) seed ->
seed === Ch.index (Ch.iterate f seed :: UChimera Word) 0

, QC.testProperty "iterateWithIndex" $
\(Fun _ (f :: (Word, Int) -> Int)) seed ix ->
let jx = ix `mod` 65536 in
iterateWithIndex (curry f) seed !! fromIntegral jx === Ch.index (Ch.iterateWithIndex (curry f) seed :: UChimera Int) jx

, QC.testProperty "head . iterateWithIndex" $
\(Fun _ (f :: (Word, Int) -> Int)) seed ->
seed === Ch.index (Ch.iterateWithIndex (curry f) seed :: UChimera Int) 0

, QC.testProperty "unfoldr" $
\(Fun _ (f :: Word -> (Int, Word))) seed ix ->
let jx = ix `mod` 65536 in
Expand Down Expand Up @@ -171,3 +184,6 @@ mkUnfix splt f x
$ map f
$ takeWhile (\y -> 0 <= y && y < x)
$ splt x

iterateWithIndex :: (Word -> a -> a) -> a -> [a]
iterateWithIndex f seed = L.unfoldr (\(ix, a) -> let a' = f (ix + 1) a in Just (a, (ix + 1, a'))) (0, seed)

0 comments on commit 88ef487

Please sign in to comment.