add concatMapM to base in control.monad

friend asked me to raise this previously https://ghc.haskell.org/trac/ghc/ticket/2042 seems like it iddn't happen last time because base lived outside of ghc? -- | The 'concatMapM' function generalizes 'concatMap' to arbitrary monads. concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b] concatMapM f xs = liftM concat (mapM f xs)

it should be noted that this can be viewed as a special case of the
witherable packages lovely interfaces
http://hackage.haskell.org/package/witherable-0.3 , which has related
things like
witherM :: Monad
http://hackage.haskell.org/package/base-4.12.0.0/docs/Control-Monad.html#t:M...
m
=> (a -> m (Maybe
http://hackage.haskell.org/package/base-4.12.0.0/docs/GHC-Maybe.html#t:Maybe
b))
-> t a -> m (t b)
On Fri, Feb 8, 2019 at 12:04 PM Carter Schonwald
friend asked me to raise this
previously https://ghc.haskell.org/trac/ghc/ticket/2042 seems like it iddn't happen last time because base lived outside of ghc?
-- | The 'concatMapM' function generalizes 'concatMap' to arbitrary monads. concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b] concatMapM f xs = liftM concat (mapM f xs)

As long as we're playing the permutation game, I also frequently use
mconcatMap, and mconcatMapM. Actually, my concatMapM is secretly
'(Monad m, Monoid b) => (a -> m b) -> [a] -> m b', but I suppose you
could argue that's inconsistent with the existing naming scheme.
I guess I don't mind it because unlike the generalization of [a] to
Foldable a, I haven't had ambiguity problems with generalizing [a] to
Monoid a. Just personal experience though.
On Fri, Feb 8, 2019 at 9:04 AM Carter Schonwald
friend asked me to raise this
previously https://ghc.haskell.org/trac/ghc/ticket/2042 seems like it iddn't happen last time because base lived outside of ghc?
-- | The 'concatMapM' function generalizes 'concatMap' to arbitrary monads. concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b] concatMapM f xs = liftM concat (mapM f xs)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

That does seem nice.
I don’t actually have a horse in this race mind you , I was merely relaying
a privately communicated from a friend proposal for feedback about its
merits etc.
On Fri, Feb 8, 2019 at 12:57 PM Evan Laforge
As long as we're playing the permutation game, I also frequently use mconcatMap, and mconcatMapM. Actually, my concatMapM is secretly '(Monad m, Monoid b) => (a -> m b) -> [a] -> m b', but I suppose you could argue that's inconsistent with the existing naming scheme.
I guess I don't mind it because unlike the generalization of [a] to Foldable a, I haven't had ambiguity problems with generalizing [a] to Monoid a. Just personal experience though.
On Fri, Feb 8, 2019 at 9:04 AM Carter Schonwald
wrote: friend asked me to raise this
previously https://ghc.haskell.org/trac/ghc/ticket/2042 seems like it iddn't happen last time because base lived outside of ghc?
-- | The 'concatMapM' function generalizes 'concatMap' to arbitrary
monads.
concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b] concatMapM f xs = liftM concat (mapM f xs)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I'm neutral to slightly negative on the proposal, but if one is going to
put it forth, this is a pretty crippled version of what the combinator
could be.
Switching liftM to fmap, and mapM to traverse gets you Applicative m.
There is no reason to limit this to Monad.
-Edward
On Fri, Feb 8, 2019 at 12:04 PM Carter Schonwald
friend asked me to raise this
previously https://ghc.haskell.org/trac/ghc/ticket/2042 seems like it iddn't happen last time because base lived outside of ghc?
-- | The 'concatMapM' function generalizes 'concatMap' to arbitrary monads. concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b] concatMapM f xs = liftM concat (mapM f xs)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I really don't see why we need this.
On Fri, Feb 8, 2019, 12:04 PM Carter Schonwald friend asked me to raise this previously https://ghc.haskell.org/trac/ghc/ticket/2042
seems like it iddn't happen last time because base lived outside of ghc? -- | The 'concatMapM' function generalizes 'concatMap' to arbitrary monads.
concatMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b]
concatMapM f xs = liftM concat (mapM f xs) _______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (4)
-
Carter Schonwald
-
David Feuer
-
Edward Kmett
-
Evan Laforge