Proposal: Add concatMapM function (#2042)

Conor McBride conor at strictlypositive.org
Tue Jan 15 15:31:48 EST 2008


Hi folks

I think Ross has boiled it down pretty well...

On 14 Jan 2008, at 22:53, Ross Paterson wrote:

> Perhaps (using mapM from Data.Traversable):
>
> foldMapM :: (Monad m, Traversable f, Monoid v) => (a -> m v) -> f a  
> -> m v
> foldMapM f = liftM fold . mapM f
>
> (with an Applicative conterpart too)

(As with many numerous episodes, I guess the
need for monadic versions of applicative operations
is something we have to live with for the moment.
There is nothing essentially monadic going on here.)

...but you can go a little further. concatMapM,
foldMapM, etc, are just newtype isotopes of foldMap.

Here's what I'd do: it's perhaps not 98y enough
(MPTCs, fundeps) for all but a far-flung corner of
the library. What do you think?

Step 1. Introduce a general utility to support the
newtype-adds-structure pattern

 > class Unpack p u | p -> u where
 >   unpack :: p -> u

and when you create a newtype, instantiate Unpack.
For example

 > newtype AMonoid a x = AMonoid {aMonoid :: a x}

 > instance Unpack (AMonoid a x) (a x) where
 >   unpack = aMonoid

I don't like having to remember a zillion unpacking
functions. If you want to be more explicit, eg, to
push types in, add

 > un :: Unpack p u => (u -> p) -> p -> u
 > un _ = unpack

so (un AMonoid) is another name for aMonoid.

Step 2. Implement this crunchy little third-order
gadget.

 > ala ::  Unpack p' u' =>
 >         (u -> p) ->
 >         ((a -> p) -> a' -> p') ->
 >         (a -> u) -> a' -> u'
 > ala pack hitWith hammer =
 >   unpack . hitWith (pack . hammer)

The idea is that (ala pack hitWith) invokes the
map-like operator hitWith, but exploiting the extra
structure identified by the packer, typically a
newtype constructor.

These two greatly increase the value of higher-order
operations like traverse, and correspondingly reduce
the need to extend one's library with special cases
of them.

Without the Unpack MPTC, you could at least add

 > modulo :: (u -> p) -> (p' -> u') ->
 >           ((a -> p) -> a' -> p') ->
 >           (a -> u) -> a' -> u'
 > modulo fancy plain hitWith hammer =
 >   plain . hitWith (fancy . hammer)

which may be worth having a standard name for.

Step 3. Expose the structure you need. Here, it's
applicative lifting of monoids (you can add your own
monadic version).

 > instance (Applicative a, Monoid x) =>
 >  Monoid (AMonoid a x) where
 >   mempty = AMonoid (pure mempty)
 >   mappend (AMonoid x) (AMonoid y) =
 >     AMonoid (pure mappend <*> x <*> y)

This is a generally useful way to be specific about
a very common kind of derived monoid structure.

And now we're home!

 > parpSplat ::
 >   (Applicative parp, Foldable f, Monoid splat) =>
 >   (x -> parp splat) -> f x -> parp splat
 > parpSplat = ala AMonoid foldMap
 >          -- modulo AMonoid aMonoid foldMap

Haskell's classes are the best damn rhythm section in
the industry: you hum it, they play it.

>
> But is this too small, and too orthogonal a combination, for the  
> library?

IMHO, yes.

All the best

Conor



More information about the Libraries mailing list