
I think this would be a good idea. I find it's both simple and useful. I use a module [1] almost identical to this for accumulating values from an RDF graph. I also have fmapM_ defined. #g -- [1] http://www.ninebynine.org/Software/HaskellUtils/FunctorM.hs At 17:11 27/05/04 -0700, John Meacham wrote:
Pretty simple, and quite useful. perhaps it could be added as Control.FunctorM ?
just as Functor generalises 'map', FunctorM generalises 'mapM'.
there are probably some instances I missed. note that unlike Functor, an instance for IO cannot be written for FunctorM.
module FunctorM where
import Array
class FunctorM f where fmapM :: Monad m => (a -> m b) -> f a -> m (f b)
instance FunctorM [] where fmapM f xs = mapM f xs
instance FunctorM Maybe where fmapM _ Nothing = return Nothing fmapM f (Just x) = f x >>= return . Just
instance Ix i => FunctorM (Array i) where fmapM f a = sequence [ f e >>= return . (,) i | (i,e) <- assocs a] >>= return . array b where b = bounds a
-- John Meacham - ârepetae.netâjohnâ _______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact