Collecting values from Functors?

Graham Klyne GK@ninebynine.org
Fri, 06 Jun 2003 18:46:59 +0100


[Moved to haskell-cafe]

At 20:40 04/06/03 +0200, Tomasz Zielonka wrote:
> > > > I'm trying to figure if there's any way I can use (say) monads to 
> collect
> > > > values from a Functor.
> > > >
> > > > For example, suppose I have a tree of some values that supports 
> fmap, is
> > > > there any way I can use the fmap function to collect a list of all 
> the node
> > > > values?
> > >
> > > No, you need a fold to do that.
>
> > Or a variant of Functor constructor class that I have proposed some time
> > ago on comp.lang.functional:
> >
> > class FunctorM t where
> >     fmapM :: Monad m => (a -> m b) -> (t a -> m (t b))
> >     fmapM_ :: Monad m => (a -> m b) -> (t a -> m ())
> >     fmapM_ f t = fmapM f t >> return ()
> >
> > instance FunctorM [] where
> >     fmapM = mapM
> >     fmapM_ = mapM_

I've done a little playing with this, which seems to work on a small scale, 
and am just wanting to check if I am properly understanding your idea...

'Arc' is a small part of a data structure I am playing with, which is 
currently a Functor.  I've made this an instance of FunctorM, defining 
fmapM which has some recognizable similarity with fmap.  Finally, there's a 
monad type CollectNodes using Control.Monad.State and constructor function 
mungeNode to actually apply the transformation and collect results.

It seems to work -- is this roughly what you envisaged?

[[
-- spike-FunctorM.hs

import Control.Monad.State

class FunctorM t where
     fmapM  :: Monad m => (a -> m b) -> (t a -> m (t b))
     fmapM_ :: Monad m => (a -> m b) -> (t a -> m ())
     fmapM_ f t = fmapM f t >> return ()

data Arc lb = Arc { asubj, apred, aobj :: lb }
     deriving (Eq, Show)

instance Functor Arc where
     fmap f (Arc s p o) = Arc (f s) (f p) (f o)

instance FunctorM Arc where
     -- fmapM :: (lb -> m l2) -> Arc lb -> m (Arc l2)
     fmapM f (Arc s p o) =
         do  { s' <- f s
             ; p' <- f p
             ; o' <- f o
             ; return $ Arc s' p' o'
             }

--  CollectNodes a b is a state transformer on a state of
--  type '[a]', which additionally returns a value of type 'b'.
type CollectNodes a b = State [a] b
         -- constructor State { runState :: (s -> (a, s)) }
         -- runState  :: State s a -> s -> (a, s)
         -- evalState :: State s a -> s -> a
         -- execState :: State s a -> s -> s
         -- mapState  :: ((a, s) -> (b, s)) -> State s a -> State s b
         -- withState :: (s -> s) -> State s a -> State s a
         -- instance MonadState s (State s)
         -- get       :: m s    -- (CollectNodes a b) [a]
         -- put       :: s -> m ()
         -- modify    :: (MonadState s m) => (s -> s) -> m ()
         -- gets      :: (MonadState s m) => (s -> a) -> m a

mungeNode :: lb -> CollectNodes lb (Maybe lb)
mungeNode lab =
     do  { modify (lab:)         -- accumulate labels
         ; return (Just lab)     -- return modified label
         }

a1 = Arc "s1" "p1" "o1"

r1 = runState ( fmapM mungeNode a1 ) []
]]

I think, but haven't worked out the details, that one could define fmap in 
terms of fmapM.  (I read somewhere about an identity Monad, but can't 
recall the reference -- I think that might do it.)

I'm also harbouring a suspiscion that this FunctorM framework might be 
subsumed by gmap and friends, but I'll leave that for another day.

#g


-------------------
Graham Klyne
<GK@NineByNine.org>
PGP: 0FAA 69FF C083 000B A2E9  A131 01B9 1C7A DBCA CB5E