Skip to content
Open
63 changes: 63 additions & 0 deletions Data/Primitive/PrimArray.hs
Original file line number Diff line number Diff line change
Expand Up @@ -66,6 +66,10 @@ module Data.Primitive.PrimArray
, foldlPrimArray
, foldlPrimArray'
, foldlPrimArrayM'
, foldMapRPrimArray
, foldMapLPrimArray
, foldMapRPrimArray'
, foldMapLPrimArray'
-- * Effectful Folding
, traversePrimArray_
, itraversePrimArray_
Expand Down Expand Up @@ -467,6 +471,65 @@ sizeofPrimArray :: forall a. Prim a => PrimArray a -> Int
{-# INLINE sizeofPrimArray #-}
sizeofPrimArray (PrimArray arr#) = I# (quotInt# (sizeofByteArray# arr#) (sizeOf# (undefined :: a)))

-- | Map each element of the primitive array to a monoid, and combine the results.
-- The combination is right-associated, and the accumulation is lazy.
-- An example:
--
-- @mySum = 'Data.Monoid.getSum' '$' 'foldMapRPrimArray' 'Data.Monoid.Sum' ('fromList' [1,2,3,4])@
--
-- Because the accumulation of 'foldMapRPrimArray' is /right-associative/, accumulation starts from the right. The first accumulation looks like this:
--
-- @mySum = 'Data.Monoid.getSum' '$' ('foldMapRPrimArray' 'Data.Monoid.Sum' ('fromList' [1,2,3])) '<>' ('Data.Monoid.Sum' 4 '<>' 'mempty')@
--
-- At each step, we don't force the value of the /accumulator/, in this case 'mempty' (and in the next case the result of @'Data.Monoid.Sum' 4 '<>' 'mempty'@).
-- This is what it means for accumulation to be lazy. Continuing:
--
-- @mySum = 'Data.Monoid.getSum' '$' ('foldMapRPrimArray' 'Data.Monoid.Sum' ('fromList' [1,2])) '<>' ('Data.Monoid.Sum' 3 '<>' ('Data.Monoid.Sum' 4 '<>' 'mempty'))@
--
-- As you can see, we are accumulating thunks because we never force the value of the accumulator, so @'Data.Monoid.Sum' 4 '<>' 'mempty'@ is not calculated until the end.
-- Fully 'built-up', the thunks look like this:
--
-- @mySum = 'Data.Monoid.getSum' '$' ('Data.Monoid.Sum' 1 '<>' ('Data.Monoid.Sum' 2 '<>' ('Data.Monoid.Sum' 3 '<>' ('Data.Monoid.Sum' 4 '<>' 'mempty'))))@
--
-- And now that we've built up the thunks, we need to actually accumulate them to get our answer:
--
-- @mySum = 'Data.Monoid.getSum' '$' ('Data.Monoid.Sum' 1 '<>' ('Data.Monoid.Sum' 2 '<>' ('Data.Monoid.Sum' 3 '<>' 'Data.Monoid.Sum' 4)))@
--
-- @mySum = 'Data.Monoid.getSum' '$' ('Data.Monoid.Sum' 1 '<>' ('Data.Monoid.Sum' 2 '<>' ('Data.Monoid.Sum' 7)))@
--
-- @mySum = 'Data.Monoid.getSum' '$' ('Data.Monoid.Sum' 1 '<>' ('Data.Monoid.Sum' 9)@
--
-- @mySum = 'Data.Monoid.getSum' '$' 'Data.Monoid.Sum' 10@
--
-- @mySum = 10@
foldMapRPrimArray :: forall a m. (Prim a, Monoid m) => (a -> m) -> PrimArray a -> m
{-# INLINE foldMapRPrimArray #-}
foldMapRPrimArray f = foldrPrimArray (\a acc -> f a `mappend` acc) mempty

-- | Map each element of the primitive array to a monoid, and combine the results.
-- The combination is left-associated, and the accumulation is lazy.
foldMapLPrimArray :: forall a m. (Prim a, Monoid m) => (a -> m) -> PrimArray a -> m
{-# INLINE foldMapLPrimArray #-}
foldMapLPrimArray f = foldlPrimArray (\acc a -> acc `mappend` f a) mempty

-- | Map each element of the primitive array to a monoid, and combine the results.
-- The combination is right-associated, and the accumulation is strict. This means
-- that at each step, we force the accumulator value to WHNF, but we /don't/ force the value
-- of the result of the function argument at each point, meaning that if 'mappend' is lazy in its first argument, that result will
-- not be evaluated.
foldMapRPrimArray' :: forall a m. (Prim a, Monoid m) => (a -> m) -> PrimArray a -> m
{-# INLINE foldMapRPrimArray' #-}
foldMapRPrimArray' f = foldrPrimArray (\a !acc -> f a `mappend` acc) mempty

-- | Map each element of the primitive array to a monoid, and combine the results.
-- The combination is left-associated, and the accumulation is strict. This means
-- that at each step, we force the accumulator value to WHNF, but we /don't/ force the value
--
-- of the result of the function argument at each point, meaning that if 'mappend' is lazy in its second argument, that result will not be evaluated.
foldMapLPrimArray' :: forall a m. (Prim a, Monoid m) => (a -> m) -> PrimArray a -> m
{-# INLINE foldMapLPrimArray' #-}
foldMapLPrimArray' f = foldlPrimArray (\ !acc a -> acc `mappend` f a) mempty

-- | Lazy right-associated fold over the elements of a 'PrimArray'.
{-# INLINE foldrPrimArray #-}
foldrPrimArray :: forall a b. Prim a => (a -> b -> b) -> b -> PrimArray a -> b
Expand Down
5 changes: 4 additions & 1 deletion changelog.md
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,10 @@

## Changes in version 0.6.4.1

* Add instances for the following newtypes from `base`:
* Add `foldMapRPrimArray` , `foldMapLPrimArray`, `foldMapRPrimArray'`, and
`foldMapLPrimArray'`

* Add `Prim` instances for the following newtypes from `base`:
`Const`, `Identity`, `Down`, `Dual`, `Sum`, `Product`,
`First`, `Last`, `Min`, `Max`

Expand Down
2 changes: 1 addition & 1 deletion test/primitive-tests.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ test-suite test
, tasty-quickcheck
, tagged
, transformers >= 0.3
, quickcheck-classes >= 0.4.11.1
, quickcheck-classes >= 0.4.14.2
ghc-options: -O2

source-repository head
Expand Down