
Hello, I was just looking at the FunctorM library that was recently added. I have a few comments: * Why is this library under "Data" and the rest of the monadic stuff is under "Control" (Related to this, what does the Reader monad have to do with Control?) * A better name for this might be "forEach". This is what I added to the Prelude of my monad library: -- | Apply a monadic function to each element in a container. -- In theory speak, this is a class that identifies functors which -- distribute over all monads. class ForEach f where forEach :: Monad m => f a -> (a -> m b) -> m (f b) instance ForEach [] where forEach xs f = mapM f xs instance ForEach Maybe where forEach Nothing f = return Nothing forEach (Just x) f = Just # f x forEach_ :: (Monad m, ForEach f) => f a -> (a -> m b) -> m () forEach_ xs f = forEach xs f >> return () -Iavor

Hello, Aside from naming issues, there seem to be some problems with the way FunctorM is currently implemented. First of all, `FunctorM` should be a superclass of `Functor' because there is an obvios implementation of fmap in terms of fmapM
import Data.FunctorM import Control.Monad.Identity
fmap' :: FunctorM f => (a -> b) -> f a -> f b fmap' f = runIdentity . fmapM (return . f) It is already annyoing enough that `Funtor' isn't a subclass of `Monad' although every monad must also be functor.
Now, FunctorM should be based on the simplest operations possible, which in this case is the distributive law and not a monadic version of fmap (which might be provided for efficiency reasons).
class Functor f => FunctorM' f where dist' :: Monad m => f (m a) -> m (f a) fmapM' :: Monad m => (a -> m b) -> f a -> m (f b)
dist' = fmapM' id fmapM' f = dist' . fmap f
-- for example instance FunctorM' [] where dist' = sequence fmapM' = mapM
Thomas

Hello,
On Mon, 21 Mar 2005 00:29:38 +0100, Thomas Jäger
Hello,
Aside from naming issues, there seem to be some problems with the way FunctorM is currently implemented.
First of all, `FunctorM` should be a superclass of `Functor' because there is an obvios implementation of fmap in terms of fmapM
import Data.FunctorM import Control.Monad.Identity
fmap' :: FunctorM f => (a -> b) -> f a -> f b fmap' f = runIdentity . fmapM (return . f) It is already annyoing enough that `Funtor' isn't a subclass of `Monad' although every monad must also be functor.
I think you are right. Does anyone remember why "Functor" is not a superclass of "Monad"?
Now, FunctorM should be based on the simplest operations possible, which in this case is the distributive law and not a monadic version of fmap (which might be provided for efficiency reasons).
class Functor f => FunctorM' f where dist' :: Monad m => f (m a) -> m (f a) fmapM' :: Monad m => (a -> m b) -> f a -> m (f b)
dist' = fmapM' id The "id" should be "return".
fmapM' f = dist' . fmap f
-- for example instance FunctorM' [] where dist' = sequence fmapM' = mapM
Well this is what I thought at first as well, but then I was looking through my code and realized that I hardly ever use "sequence" but I use "mapM" a lot. But of course one could have both operations in the class (as in your example). -Iavor
participants (2)
-
Iavor Diatchki
-
Thomas Jäger