Collecting values from Functors?
Tomasz Zielonka
t.zielonka@students.mimuw.edu.pl
Thu, 5 Jun 2003 12:13:53 +0200
On Thu, Jun 05, 2003 at 09:08:03AM +1200, Tom Pledger wrote:
> | I am sorry, I misunderstood the problem.
>
> You're too modest. :-)
>
> There *is* a solution in that direction.
Yes, I knew I could use a State monad or a Writer monad, but I thought
that it would be an overkill. Fold is more appropriate here.
> 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) [])
I like this solution. The fseq function seems to be more general.
> Regards,
> Tom
Regards,
Tom
:)
--
.signature: Too many levels of symbolic links