Could this be added to Data?
John Meacham
john at repetae.net
Sun Jan 16 01:26:15 EST 2005
Could someone with CVS write access add this to Data? I brought it up
before and there wern't any objections and several people responded
saying they have implemented the exact same module (with the same names)
so it would seem to make sense to include it.
There are probably some more instances that can be added from the rest
of the libraries.
John
--
John Meacham - ⑆repetae.net⑆john⑈
-------------- next part --------------
module Data.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
More information about the Libraries
mailing list