Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Functions as containers; implications on being a Monad
      ((->) r) (Alex Belanger)
   2. Re:  Functions as containers;     implications on being a Monad
      ((->) r) (Daniel Bergey)
   3. Re:  Functions as containers; implications on being a Monad
      ((->) r) (Gesh)


----------------------------------------------------------------------

Message: 1
Date: Sat, 4 Jun 2016 10:27:05 -0400
From: Alex Belanger <i.caught....@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Functions as containers; implications
        on being a Monad ((->) r)
Message-ID:
        <CADSky2yP_eo1fUX2t4Tmxmc=r+a5gsoiy35zfg0d-vcomlh...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Does it help if I bring your:

(\x -> x+7) <$> (+3) => (+10)

It doesn't magically become `(+10)`. The previous step unseen is `(+7) .
(+3)`. fmap for ((->) r) is defined as function  composition `.`.

fmap f g = f . g

You can think of functors as containers or contexts; both analogies work
well up to some degree (with the latter maybe more abstract and thus
flexible).

Another small terminology tip that could help you with your thinkering
might be to call ((->) r) a partially applied function. Suddently, it
narrows how you can potentially use/combine them.

Last tip, Monad ((->) r) is commonly refered to as the Reader monad.
Example of how it'd be used:

doThings = do
    a <- (*2)
    b <- (+10)
    return (a + b)

Notice how we can work with partially applied functions to which something
have yet to be applied and create a new partial function whose argument is
going to fill all the open holes.

This isn't easy to explain without looking at the types of everything, so I
encourage you to write it down and work out the types (:

Alex
On Jun 4, 2016 12:41 AM, "Raja" <rajasha...@gmail.com> wrote:


Everyone agrees ((->) r) is a Functor, an Applicative and a Monad but I've
never seen any good writeup going into details of explaining this.

So I was trying to brainstorm with my brother and went pretty far into the
concept for quite a few hours, but still got stuck when it came to Monads.

Before I showcase the question/problem I wanted to share our thinking
process.

Lets stick with common types like Maybe a, [a], simple function (a -> b)

**Everything is a Container**

 Just 4 => this is a container wrapping some value
[1,2,3] => this is a container wrapping bunch of values
(+3) => this is a container wrapping domains & ranges (infinite dictionary)

**When is a Container a Functor**

If we can peek inside a container and apply a simple function (a->b) to
each of its values and wrap the result back inside the container, then it
becomes a Functor.

Let's use (\x -> x+7) as simple function along with above three Containers

(\x -> x+7) <$> Just 4 => Just 11
(\x -> x+7) <$> [1,2,3] => [8,9,10]
(\x -> x+7) <$> (+3) => (+10)  -- well there is no Show defined but you get
the idea

**When is a Container an Applicative**

The simple function from above is also now wrapped inside a container and
we should be able to peek to use it just like functor. Also lets simplify
(\x -> x+7) to (+7).

Just (+7) <*> Just 4 => Just 11
[(+7)] <*> [1,2,3] => [8,9,10]
(\x -> (+7)) <*> (+3) => (+10) -- again no Show defined but works when pass
a number
-- but (+7) still needs to be wrapped in a Container though

**When is a Container a Monad**

This time we don't have a simple function (a->b) instead we have a
non-simple function (a -> Container). But rest stays almost the same.

We have to first peek inside a container and apply non-simple function to
each of its values. Since its a non-simple function we need to collect all
the returned Containers, unwrap them and wrap them all back in a Container
again.
(it almost feels like unwrap and wrapping them back is going to complicate
things)

Also Non-simple function cannot be reused as is for all three Containers
like in Functors & Applicatives.

Just 4 >>= (\x -> Just (x+7)) => Just 11
[1,2,3] >>= (\x -> [x+7]) => [8,9,10]
(+3) >>= (\x -> (+7)) => (+7)

Wait a minute ... the last line doesn't look right. Or should I say it
doesn't feel right to discard the `x' altogether.

OK let's jump to do this:
(+3) >>= (\x -> (+x)) => ??? -- apparently this solves for the equation:
f(x) = 2x + 3

(is 2x + 3 obvious for anyone??? it took us way longer to derive it)
(Does it have anything to do with Monad laws by any chance?)

This is where it feels like "Functions as containers" concept starts to
breakdown; its not the right analogy for Monads.

What does it even mean to unwrap a bunch of functions and wrap them back
again?

Hope this intrigues some of you as it did to us. Any thoughts and comments
greatly appreciated.

Thanks,
Raja

_______________________________________________
Beginners mailing list
Beginners@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/20160604/63791f50/attachment-0001.html>

------------------------------

Message: 2
Date: Sat, 04 Jun 2016 12:56:02 -0400
From: Daniel Bergey <ber...@alum.mit.edu>
To: Raja <rajasha...@gmail.com>, beginners@haskell.org
Subject: Re: [Haskell-beginners] Functions as containers;       implications
        on being a Monad ((->) r)
Message-ID:
        <87k2i4x599.fsf@chladni.i-did-not-set--mail-host-address--so-tickle-me>
        
Content-Type: text/plain; charset=utf-8

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.

For the instance ((->) r), it's important to keep track of which argument is the
r.  I think it helps to write the lambdas explicitly, rather than the
point-free (+3).  Keeping the type variables straight is also a reminder
that all these need to work for any types r, a, b, not only when all
three types are Int: (r ~ a ~ b ~ Int).

So we have:
fmap :: (a -> b) -> (r -> a) -> (r -> b)
fmap f g = \r -> f (g r)

fmap (\x -> x + 7) (\r -> r + 3) = \r -> (r + 3) + 7

(<*>) :: (r -> a -> b) -> (r -> a) -> (r -> b)
f <*> g = \r -> f r (g r)

Since r, a, b may all be different types, this is the only possible definition.

(\r -> (\x -> x + 7)) <*> (\r -> r + 3) = \r -> (r + 3) + 7

Note that the function on the left of <*> ignores its r parameter, so
this is exactly the same as the fmap example.  This follows the law (for
any Applicative) that

fmap f === pure f <*>

For an example that doesn't ignore the r:

(\r -> (\x -> r + x)) <*> (\r -> r + 3) = \r -> r + (r + 3)

Note also that the function on the left takes the argument of type r
first, and the argument of type a second.  The second argument to >>=,
on the other hand, takes an a, then an r:

(>>=) :: (r -> a) -> (a -> (r -> b)) -> (r -> b)
f >>= g = \r -> g (f r)

(\r -> r + 3) >>= (\x -> (\r -> r + 7)) = \r -> r + 7

Here the function on the right of >>= ignores its argument, so this
isn't very interesting.

(\r -> r + 3) >>= (\x -> (\r -> r + x)) = \r -> r + (r + 3)

is a bit more interesting. It uses both functions, but it's exactly the
same as the second Applicative example.

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.

Hope this helps.

bergey


On 2016-06-04 at 00:40, Raja <rajasha...@gmail.com> wrote:
> Everyone agrees ((->) r) is a Functor, an Applicative and a Monad but I've 
> never seen
> any good writeup going into details of explaining this.
>
> So I was trying to brainstorm with my brother and went pretty far into the 
> concept for
> quite a few hours, but still got stuck when it came to Monads.
>
> Before I showcase the question/problem I wanted to share our thinking process.
>
> Lets stick with common types like Maybe a, [a], simple function (a -> b)
>
> **Everything is a Container**
>
> ?Just 4 => this is a container wrapping some value
> [1,2,3] => this is a container wrapping bunch of values
> (+3) => this is a container wrapping domains & ranges (infinite dictionary)
>
> **When is a Container a Functor**
>
> If we can peek inside a container and apply a simple function (a->b) to each 
> of its
> values and wrap the result back inside the container, then it becomes a 
> Functor.
>
> Let's use (\x -> x+7) as simple function along with above three Containers
>
> (\x -> x+7) <$> Just 4 => Just 11
> (\x -> x+7) <$> [1,2,3] => [8,9,10]
> (\x -> x+7) <$> (+3) => (+10) ?-- well there is no Show defined but you get 
> the idea
>
> **When is a Container an Applicative**
>
> The simple function from above is also now wrapped inside a container and we 
> should be
> able to peek to use it just like functor. Also lets simplify (\x -> x+7) to 
> (+7).
>
> Just (+7) <*> Just 4 => Just 11
> [(+7)] <*> [1,2,3] => [8,9,10]
> (\x -> (+7)) <*> (+3) => (+10) -- again no Show defined but works when pass a 
> number
> -- but (+7) still needs to be wrapped in a Container though
>
> **When is a Container a Monad**
>
> This time we don't have a simple function (a->b) instead we have a non-simple 
> function
> (a -> Container). But rest stays almost the same.?
>
> We have to first peek inside a container and apply non-simple function to 
> each of its
> values. Since its a non-simple function we need to collect all the returned 
> Containers,
> unwrap them and wrap them all back in a Container again.?
> (it almost feels like unwrap and wrapping them back is going to complicate 
> things)
>
> Also Non-simple function cannot be reused as is for all three Containers like 
> in
> Functors & Applicatives.
>
> Just 4 >>= (\x -> Just (x+7)) => Just 11
> [1,2,3] >>= (\x -> [x+7]) => [8,9,10]
> (+3) >>= (\x -> (+7)) => (+7)?
>
> Wait a minute ... the last line doesn't look right. Or should I say it 
> doesn't feel
> right to discard the `x' altogether.?
>
> OK let's jump to do this:
> (+3) >>= (\x -> (+x)) => ??? -- apparently this solves for the equation: f(x) 
> = 2x + 3
>
> (is 2x + 3 obvious for anyone??? it took us way longer to derive it)
> (Does it have anything to do with Monad laws by any chance?)
>
> This is where it feels like "Functions as containers" concept starts to 
> breakdown; its
> not the right analogy for Monads.?
>
> What does it even mean to unwrap a bunch of functions and wrap them back 
> again?
>
> Hope this intrigues some of you as it did to us. Any thoughts and comments 
> greatly
> appreciated.
>
> Thanks,
> Raja
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

Message: 3
Date: Sun, 5 Jun 2016 03:10:47 +0300
From: Gesh <g...@gesh.uni.cx>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Functions as containers; implications
        on being a Monad ((->) r)
Message-ID: <cb3cdb2a-4db2-1b9f-0d0d-f5b3593ef...@gesh.uni.cx>
Content-Type: text/plain; charset=utf-8; format=flowed

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.


------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 96, Issue 8
****************************************

Reply via email to