[Haskell-beginners] Functions as containers; implications on being a Monad ((->) r)

Rein Henrichs rein.henrichs at gmail.com
Fri Jun 24 22:54:22 UTC 2016


Don't be led astray by leaky analogies. A Functor is not a container.
*Some* Functor
instances are* like* containers. When this analogy stops working, discard
it and think about the problem directly. Like any other typeclass, Functor
is just a collection of methods and laws[1]; its instances are just types
which have law abiding implementations of the methods. Knowing the type of
fmap and its laws, we know what it means for ((->) r) to be an instance: it
means that we can define

    fmap :: (a -> b) -> f a -> f b

for f = ((->) r) and prove that it satisfies the laws.

Substituting for f, we have:

    fmap :: (a -> b) -> (r -> a) -> (r -> b)

By alpha equivalence, we can rename this to

    fmap :: (b -> c) -> (a -> b) -> a -> c

and immediately we find a candidate implementation in function composition, (.)
:: (b -> c) -> (a -> b) -> a -> c:

   fmap f g = f . g

Now we must prove that this implementation is law abiding. I'll show a
proof for the first law, fmap id = id, with assistance from a few
definitions:

1) f . g = \x -> f (g x)
2) id x = x
3) \x -> f x = f

  fmap id f
= id . f          {- definition of fmap -}
= \x -> id (f x)  {- by (1) -}
= \x -> f x       {- by (2) -}
= f               {- by (3) -}
= id f            {- by (2) -}

Thus we have fmap id f = id f and (by eta reduction) fmap id = id. Try to
prove the second law for yourself! Once you've proven it, you know that ((->)
r) is an instance of Functor where fmap = (.)[2]. If you do the same for
Applicative and Monad then you will know exactly how ((->) r) is a Functor,
an Applicative, and a Monad.

Then you can experiment by applying the typeclass methods to functions to
see what the practical value of these definitions is. For example. the
Applicative instance lets you plumb a shared argument to a number of
functions. Here's a contrived example:

> (++) <$> map toUpper <*> reverse $ "Hello"
"HELLOolleH"

-R

[1] The laws are not really a part of the typeclass proper (i.e., the
compiler doesn't know anything about them), but developers need to ensure
that their instances are law abiding so that they behave as expected.
[2]: Actually, it turns out that one only needs to prove the first law for
fmap because the second law is implied by the first, but that's a topic for
another day!

On Sat, Jun 4, 2016 at 5:11 PM Gesh <gesh at gesh.uni.cx> wrote:

> On 2016-06-04 19:56, Daniel Bergey wrote:
> > I think "a functor is a container" is not so helpful.  It works OK for
> > Maybe and List, but it doesn't seem helpful in understanding Either,
> > Reader, Writer, State, Continuation, promises.
> This is correct. However, a large class of types form what are called
> "Representable Functors".
> These include Lists, Trees, ((->) r), etc.
>
> A representable functor is any type f with an isomorphism `(f a ~ r ->
> a)` for some r.
> For example, `Stream a ~ Natural -> a` under the isomorphism:
>  > toFunction xs = \i -> xs !! i
>  > toList f = fromList $ map f [0..]
> > I *think* it's the case that for (r ->), there isn't anything we can do
> > with the Monad instance that we can't do with Applicative.  If someone
> > can confirm or refute that, I'd appreciate it.  That's of course not
> > true in general for other monads.
> Indeed, for any representable functor, this all follows from the fact
> that we can write a lawful
> join from Reader's <*>. Letting `join m = flip ($) <*> m`, we have:
>  > (join . pure) x = \r -> ($ r) (const x r) = \r -> x $ r = x
>  > (join . fmap pure) x = \r -> ($ r) ((pure . x) r) = \r -> (const (x
> r)) r = \r -> x r = x
>  > (join . fmap join) x = \r -> ($ r) ((join . x) r) = \r -> join (x r)
> r = \r -> (\s -> ($s) (x r s)) r
>  >  = \r -> x r r r = \r -> ($r) (\s -> x s s) r = join (\s -> ($s) (x
> s)) = (join . join) x
>
> Hence, given the applicative instance for Reader, we obtain the Monad
> instance for free.
> Therefore, working under the isomorphism, we have the same for any
> representable functor.
>
> In particular, this gives that Stream is a Monad, where return gives the
> constant stream and
> join takes the diagonal of a stream of streams.
>
> Again, as noted, this is more or less the only way in which the
> "Functors/Applicatives/Monads are nice/nicer/nicest containers" analogy
> works.
> There are more things in heaven and earth than are described in that
> analogy, but it's a start.
>
> Hope this helps, and that it lacks errors/misleading material,
> Gesh
> P.S. Code for working with representable functors can be found in
> representable-functors.
> Code for working with Streams can be found in streams. Both are on Hackage.
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20160624/e0e8d935/attachment.html>


More information about the Beginners mailing list