Collecting values from Functors?
Tom Pledger
Tom.Pledger@peace.com
Thu, 5 Jun 2003 09:08:03 +1200
Tomasz Zielonka writes:
| On Wed, Jun 04, 2003 at 08:38:29PM +0200, Tomasz Zielonka wrote:
:
| > 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 am sorry, I misunderstood the problem.
You're too modest. :-)
There *is* a solution in that direction.
Here's my version of fmapM, which was inspired by something in Tim
Sheard's paper "Generic Unification via Two-Level Types and
Parameterized Modules".
import Control.Monad.State
-- ------------------------------------------------------------
-- Functors through which monads may be lifted
class Functor f => FunctorSeq f where
fseq :: Monad m => f (m a) -> m (f a)
instance FunctorSeq [] where
fseq = sequence
instance FunctorSeq Maybe where
fseq Nothing = return Nothing
fseq (Just mx) = do x <- mx; return (Just x)
fmapM :: (Monad m, FunctorSeq f) => (a -> m b) -> f a -> m (f b)
fmapM f xs = fseq (fmap f xs)
fseq2list :: (FunctorSeq f) => f a -> [a]
fseq2list fa
= reverse (execState (fmapM (\a -> modify (a:)) fa) [])
The question was "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?"
A: Yes, use something like fseq2list, provided that you first declare
your tree type as an instance of something like FunctorM or
FunctorSeq.
Regards,
Tom