FunctorM

John Meacham john at repetae.net
Thu May 27 20:11:58 EDT 2004


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⑈ 


More information about the Libraries mailing list