[Haskell-cafe] Re: Map list of functions over a single argument

Nicolas Frisby nicolas.frisby at gmail.com
Tue Feb 20 15:10:50 EST 2007


Here comes an overwhelming post (so stop here if you're not interested
in applicative functors), but apfelmus stepped in this direction. The
funny part is that, modulo dictionary passing (which might be compiled
away), all 6 functions below do the Exact Same Thing because of
newtype erasure (Calling all experts: am I right about that?).

All of the themes below are explained in the Applicative Functors
pearl, which is an excellent read. See:
  http://lambda-the-ultimate.org/node/1137

The "aha!" this code attempts to illuminate is that the point that
'maps' can be written as the sequencing of the environment monad is
akin to saying that "all regular polygons have a perimeter" as opposed
to "all 2-dimensional shapes have a perimeter." Both are obviously
legitimate claims, but we might be able to squeeze a little more
understanding out of the second version. A more germaine formulation:
it's not the monadic properties of the environment reader that we need
in order to solve this problem so much as it is the applicative
functor properties of the environment reader (which also happens to be
a monad).

Moreover, it doesn't just work for lists of functions--e.g. it could
work for trees too. The required property here is captured by
Data.Traversable, which the list type constructor satisfies. Use of
traversable often comes hand-in-hand with applicative functors.



\begin{code}
import qualified Control.Monad as M
import Control.Monad.Reader
import qualified Control.Applicative as AF
import qualified Data.Traversable as T

-- Nothing Fancy Here:
-- to avoid confusion with monad during this presentation,
-- we create a newtype for environment as an applicative functor
newtype ReaderAF r a = ReaderAF { runReaderAF :: r -> a }
instance Functor (ReaderAF r) where
    fmap fn (ReaderAF f) = ReaderAF (fn . f)
instance AF.Applicative (ReaderAF r) where
    pure a = ReaderAF (const a)
    (ReaderAF f) <*> (ReaderAF g) = ReaderAF (\r -> (f r) (g r))



-- our target functions
maps, mi_maps, me_maps, afe_maps, afi_maps, maf_maps :: [a -> b] -> a -> [b]



-- conventional
maps fs a = map ($ a) fs

-- monadic (implicit reader)
mi_maps fs a = (M.sequence fs) a

-- monadic (explicit reader)
me_maps fs a = runReader (M.sequence fs') a
    where fs' = map Reader fs

-- applicative functor (explicit reader)
afe_maps fs a = runReaderAF (T.sequenceA fs') a
    where fs' = map ReaderAF fs

-- applicative functor (implicit reader)
afi_maps fs a = (T.sequenceA fs) a

-- combination (a monad as an applicative functor)
maf_maps fs a = runReader (AF.unwrapMonad (T.sequenceA fs')) a
    where fs' = map (AF.WrapMonad . Reader) fs
\end{code}


Also, Data.Traversable exports a function 'sequence' that generalizes
the one from Control.Monad/Prelude to work on more than just lists:

Prelude> :m + Data.Traversable
Prelude Data.Traversable> :t Data.Traversable.sequence
Data.Traversable.sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)

So we could have even written 4 more versions of the function that
again all reduce to the same thing (modulo dictionary passing)!

It isn't really highlighted above, but one high-level difference
between monads and applicative functors is a question of how paramount
is the notion of sequencing (the >>= kind of sequencing more so than
the 'sequence' kind of sequencing).

Sorry for the dropping the concept bomb on a simple question, but
hopefully someone enjoyed the adventure.

Nick

On 2/20/07, David House <dmhouse at gmail.com> wrote:
> On 20/02/07, apfelmus at quantentunnel.de <apfelmus at quantentunnel.de> wrote:
> > It's also known as
> >
> >   sequence :: Monad m => [m b] -> m [b]
> >
> > with m = (->) a
>
> Don't forget to import Control.Monad.Instances for this to work.


More information about the Haskell-Cafe mailing list