At the very least, it does seem like we're going to need to do a broader survey of the instances out there, as well as fix a lot more Applicative instances to have a better (*>) first as well as thoroughly document what to do, if we want to proceed on this front.

If we ultimately want to remove mapM from the class to get it a more permissive type signature, and get mapM_ from Foldable to have the more general signature to boot, then we'll need to figure out how to address these concerns.

It still strikes me as the right general direction to go in, but this is troubling.

-Edward

On Mon, Aug 3, 2015 at 12:33 PM, Ben Gamari <ben@well-typed.com> wrote:
Edward Kmett <ekmett@gmail.com> writes:

> On Tue, May 12, 2015 at 3:58 AM, Simon Marlow <marlowsd@gmail.com> wrote:
>
>>
>> Yes, I'm not really concerned that mapM is a method of Traversable rather
>> than just being an alias for traverse, but I'm wondering why we define it
>> in the list instance rather than using the default.
>>
>
> We were pretty paranoid about introducing space or time regressions and
> didn't have a proof that we wouldn't introduce them by changing something
> there, so we left it alone.
>
On a related note, D924 [1] proposed that mapM_ be redefined in
terms of traverse_. Unfortunately at least one monad in GHC itself was
adversely affected [2] by this change, resulting in non-linear complexity in
a previously well-behaved function (a minimal demonstration of this can
be found below).

We discussed this in the GHC weekly meeting and felt that we should
ensure that the libraries group was aware of this issue.

Cheers,

- Ben


[1] https://phabricator.haskell.org/D924
[2] https://ghc.haskell.org/trac/ghc/ticket/10711
[3] Demonstration of regression in complexity of mapM_ when expressed in
    terms of `traverse_`,

{{{
module Main where

import Control.Monad hiding (mapM_)
import Prelude hiding (mapM_)

-- | Testcase derived from Assembler monad in ByteCodeAsm
data Assembler a
    = Thing Int (Int -> Assembler a)
    | Pure a

instance Functor Assembler where
    fmap = liftM

instance Applicative Assembler where
    pure = return
    (<*>) = ap

instance Monad Assembler where
    return = Pure
    Pure x >>= f = f x
    Thing i k >>= f = Thing i (k >=> f)

-- This is traverse_
mapA_ :: (Foldable t, Monad f) => (a -> f b) -> t a -> f ()
mapA_ f = foldr ((*>) . f) (pure ())

-- This is the current definition
mapM_ :: (Foldable t, Monad f) => (a -> f b) -> t a -> f ()
mapM_ f = foldr ((>>) . f) (pure ())

test = map (\i->Thing i (const $ return 2)) [0..10000]

doTestM = mapM_ id test
doTestA = mapA_ id test

run :: Assembler a -> a
run (Thing i f) = run (f i)
run (Pure r) = r
{-# NOINLINE run #-}

main :: IO ()
main = print $ run doTestM
}}}

--
You received this message because you are subscribed to the Google Groups "haskell-core-libraries" group.
To unsubscribe from this group and stop receiving emails from it, send an email to haskell-core-libraries+unsubscribe@googlegroups.com.
For more options, visit https://groups.google.com/d/optout.