Skip to content
Snippets Groups Projects

Add fold functions for arrays

Merged meooow requested to merge meooow/array:folds into master
1 unresolved thread

At the moment it is quite difficult to perform some folds on some arrays.

  • In general, arrays can be folded over by folding over the range of indices and then indexing into the array. This is a little cumbersome, and also inefficient when folding right-to-left because Ix does not offer reversed range generation.
  • Alternately, Array has a Foldable instance which works great, but UArray cannot be Foldable. Folds on UArray can instead be done via elems. Due to list fusion, this works out well for some folds (foldr, foldl'), but not others (foldr').
  • For mutable arrays, there are no alternate ways to fold.

This commit adds some commonly used folds for arrays and mutable arrays to improve this situation.

Fixes #16 (closed).

Edited by meooow

Merge request reports

Loading
Loading

Activity

Filter activity
  • Approvals
  • Assignees & reviewers
  • Comments (from bots)
  • Comments (from users)
  • Commits & branches
  • Edits
  • Labels
  • Lock status
  • Mentions
  • Merge request status
  • Tracking
1141 foldrMArrayM' :: (MArray a e m, Ix i) => (e -> b -> m b) -> b -> a i e -> m b
1142 foldrMArrayM' f z0 = \a -> do
1143 !n <- getNumElements a
1144 let go i !z | i < 0 = pure z
1145 | otherwise = do
1146 x <- unsafeRead a i
1147 z' <- f x z
1148 go (i-1) z'
1149 go (n-1) z0
1150 {-# INLINE foldrMArrayM' #-}
1151
1152 -- | Map elements to monadic actions, sequence them left-to-right, and discard
1153 -- the results.
1154 --
1155 -- @since FIXME
1156 mapMArrayM_ :: (MArray a e m, Ix i) => (e -> m b) -> a i e -> m ()
  • Thanks for your outstanding work!

  • Lei Zhu approved this merge request

    approved this merge request

  • Lei Zhu added 3 commits

    added 3 commits

    Compare with previous version

  • merged

  • Please register or sign in to reply
    Loading