
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⑈

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

In article <20040528001157.GA1924@momenergy.repetae.net>,
John Meacham
class FunctorM f where fmapM :: Monad m => (a -> m b) -> f a -> m (f b)
I have an equivalent (I think) class in HBase in its big library of Functor classes: class (Functor f) => ExtractableFunctor f where { fextract :: forall g a. (FunctorApplyReturn g) => f (g a) -> g (f a); }; for :: (ExtractableFunctor f,FunctorApplyReturn m) => (a -> m b) -> (f a -> m (f b)); for foo fa = fextract (fmap foo fa); The important thing here is that a FunctorApplyReturn is more general than Monad, it has only return and "fapply :: f (a -> b) -> f a -> f b". Given this, it's also possible to write this function (by using a state monad): ftolist :: (ExtractableFunctor f) => f a -> [a] The main Functor classes in HBase are arranged like this: Functor <= FunctorApply <= FunctorApplyReturn <= Monad Doubtless if I knew a little more category theory, I'd have better names for them. It would be nice if the standard libraries adopted a superclass arrangement like this... -- Ashley Yakeley, Seattle WA

At 00:55 04/06/04 -0700, Ashley Yakeley wrote:
In article <20040528001157.GA1924@momenergy.repetae.net>, John Meacham
wrote: class FunctorM f where fmapM :: Monad m => (a -> m b) -> f a -> m (f b)
I have an equivalent (I think) class in HBase in its big library of Functor classes:
class (Functor f) => ExtractableFunctor f where { fextract :: forall g a. (FunctorApplyReturn g) => f (g a) -> g (f a); };
for :: (ExtractableFunctor f,FunctorApplyReturn m) => (a -> m b) -> (f a -> m (f b)); for foo fa = fextract (fmap foo fa);
The important thing here is that a FunctorApplyReturn is more general than Monad, it has only return and "fapply :: f (a -> b) -> f a -> f b".
I think the monadic 'zero' may be useful in applications of FunctorM, in that it provides a way to cleanly handle errors encountered during the "traversal". #g --
Given this, it's also possible to write this function (by using a state monad):
ftolist :: (ExtractableFunctor f) => f a -> [a]
The main Functor classes in HBase are arranged like this:
Functor <= FunctorApply <= FunctorApplyReturn <= Monad
Doubtless if I knew a little more category theory, I'd have better names for them. It would be nice if the standard libraries adopted a superclass arrangement like this...
-- Ashley Yakeley, Seattle WA
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact
participants (3)
-
Ashley Yakeley
-
Graham Klyne
-
John Meacham