
+1 from me. We probably also want foldMapAlt:
foldMapAlt :: (Foldable t, Alternative f) => (a -> f b) -> t a -> f b
On Tue, Nov 28, 2017 at 11:12 PM, Fumiaki Kinoshita
We found this quite useful, but we are not 100% about the name and documentation.
-- | Try—in the 'Alternative' sense—to return all the values in a 'Foldable' -- container. -- -- @ -- foldAlt ≡ 'listToMaybe' :: [a] -> 'Maybe' a -- foldAlt ≡ 'maybeToList' :: 'Maybe' a -> [a] -- foldAlt ≡ 'MaybeT' . 'return' :: ('Monad' m) => 'Maybe' a -> 'MaybeT' m a -- foldAlt ≡ 'Pipes.ListT' . 'Pipes.each' :: ('Monad' m) => [a] -> 'Pipes.ListT' m a -- foldAlt ≡ id :: 'Maybe' a -> 'Maybe' a -- @ foldAlt :: (Foldable t, Alternative f) => t a -> f a foldAlt = getAlt . foldMap (Alt . pure) {-# INLINE foldAlt #-}
I propose adding this to either `Data.Foldable` or `Control.Applicative`. Any thoughts?
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-- -Andrew Thaddeus Martin