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:  Understanding the function monad ((->) r) (Rahul Muttineni)
   2. Re:  Understanding the function monad ((->) r) (Benjamin Edwards)
   3. Re:  Understanding the function monad ((->) r) (Olumide)


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

Message: 1
Date: Tue, 21 Feb 2017 20:02:55 +0530
From: Rahul Muttineni <rahulm...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Understanding the function monad
        ((->) r)
Message-ID:
        <CANij+eTi1ZKyWytgu84VPJh0P1=b_+zhi-6r-m1r22jv-ec...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi Olumide,

Let the types help you out.

The Monad typeclass (omitting the superclass constraints):

class Monad m where
  return :: a -> m a
  (>>=) :: m a -> (a -> m b) -> m b

Write out the specialised type signatures for (->) r:

{-# LANGUAGE InstanceSigs #-}
-- This extension allows you to specify the type signatures in instance
declarations

instance Monad ((->) r) where
  return :: a -> (r -> a)
  (>>=) :: (r -> a) -> (a -> (r -> b)) -> (r -> b)

Now we look at how to make some definition of return that type checks.
We're given an a and we want to return a function that takes an r and
returns an a. Well the only way you can really do this is ignoring the r
and returning the value you were given in all cases! Because 'a' can be
*anything*, you really don't have much else you can do! Hence:

  return :: a -> (r -> a)
  return a = \_ -> a

Now let's take a look at (>>=). Since this is a bit complicated, let's work
backwards from the result type. We want a function that gives us a b given
an r and given two functions with types (r -> a) and (a -> (r -> b)). To
get a b, we need to use the second function. To use the second function, we
must have an a, which we can get from the first function!

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

Hope that helps!
Rahul


On Tue, Feb 21, 2017 at 5:04 PM, Olumide <50...@web.de> wrote:

> On 21/02/2017 10:25, Benjamin Edwards wrote:
>
>> What is it that you are having difficulty with? Is it "why" this is a
>> good definition? Is it that you don't understand how it works?
>>
>
> I simply can't grok f (h w) w.
>
> - Olumide
>
> On Tue, 21 Feb 2017 at 10:15 Olumide <50...@web.de
>> <mailto:50...@web.de>> wrote:
>>
>>     Hello List,
>>
>>     I am having enormous difficulty understanding the definition of the
>> bind
>>     operator of ((->) r) as show below and would appreciate help i  this
>>     regard.
>>
>>     instance Monad ((->) r) where
>>          return x = \_ -> x
>>          h >>= f = \w -> f (h w) w
>>
>>     Thanks,
>>
>>     - Olumide
>>
>>     _______________________________________________
>>     Beginners mailing list
>>     Beginners@haskell.org <mailto:Beginners@haskell.org>
>>     http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
>>
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>>
>>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>



-- 
Rahul Muttineni
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20170221/19183ac6/attachment-0001.html>

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

Message: 2
Date: Tue, 21 Feb 2017 15:08:45 +0000
From: Benjamin Edwards <edwards.b...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Understanding the function monad
        ((->) r)
Message-ID:
        <CAN6k4njnviJo6fPcx33WQdEN=ibyq3fvehykwns81ytw+9h...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

The thing that you might also be missing is that function application binds
tightest. Hopefully the parenthesis that Rahul has added help you out
there. If not:

\w -> f (h w) w

f will be applied to the result of (h r) which yields another function,
which is then applied to r

that is

\w ->
let x = h w
g = f x
in g w

would yield exactly the same result. I apologise for the indentation, I
need a better mail client.

Ben

On Tue, 21 Feb 2017 at 14:34 Rahul Muttineni <rahulm...@gmail.com> wrote:

> Hi Olumide,
>
> Let the types help you out.
>
> The Monad typeclass (omitting the superclass constraints):
>
> class Monad m where
>   return :: a -> m a
>   (>>=) :: m a -> (a -> m b) -> m b
>
> Write out the specialised type signatures for (->) r:
>
> {-# LANGUAGE InstanceSigs #-}
> -- This extension allows you to specify the type signatures in instance
> declarations
>
> instance Monad ((->) r) where
>   return :: a -> (r -> a)
>   (>>=) :: (r -> a) -> (a -> (r -> b)) -> (r -> b)
>
> Now we look at how to make some definition of return that type checks.
> We're given an a and we want to return a function that takes an r and
> returns an a. Well the only way you can really do this is ignoring the r
> and returning the value you were given in all cases! Because 'a' can be
> *anything*, you really don't have much else you can do! Hence:
>
>   return :: a -> (r -> a)
>   return a = \_ -> a
>
> Now let's take a look at (>>=). Since this is a bit complicated, let's
> work backwards from the result type. We want a function that gives us a b
> given an r and given two functions with types (r -> a) and (a -> (r -> b)).
> To get a b, we need to use the second function. To use the second function,
> we must have an a, which we can get from the first function!
>
>   (>>=) :: (r -> a) -> (a -> (r -> b)) -> (r -> b)
>   (>>=) f g = \r -> (g (f r)) r
>
> Hope that helps!
> Rahul
>
>
> On Tue, Feb 21, 2017 at 5:04 PM, Olumide <50...@web.de> wrote:
>
> On 21/02/2017 10:25, Benjamin Edwards wrote:
>
> What is it that you are having difficulty with? Is it "why" this is a
> good definition? Is it that you don't understand how it works?
>
>
> I simply can't grok f (h w) w.
>
> - Olumide
>
> On Tue, 21 Feb 2017 at 10:15 Olumide <50...@web.de
> <mailto:50...@web.de>> wrote:
>
>     Hello List,
>
>     I am having enormous difficulty understanding the definition of the
> bind
>     operator of ((->) r) as show below and would appreciate help i  this
>     regard.
>
>     instance Monad ((->) r) where
>          return x = \_ -> x
>          h >>= f = \w -> f (h w) w
>
>     Thanks,
>
>     - Olumide
>
>     _______________________________________________
>     Beginners mailing list
>     Beginners@haskell.org <mailto:Beginners@haskell.org>
>     http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
>
>
> --
> Rahul Muttineni
> _______________________________________________
> 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/20170221/3cb83e46/attachment-0001.html>

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

Message: 3
Date: Tue, 21 Feb 2017 15:52:22 +0000
From: Olumide <50...@web.de>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Understanding the function monad
        ((->) r)
Message-ID: <ed369053-5c89-5d86-4aaf-d6e9f3a63...@web.de>
Content-Type: text/plain; charset=utf-8; format=flowed

On 21/02/2017 15:08, Benjamin Edwards wrote:
> The thing that you might also be missing is that function application
> binds tightest. Hopefully the parenthesis that Rahul has added help you
> out there. If not:
>
> \w -> f (h w) w
>
> f will be applied to the result of (h r) which yields another function,
> which is then applied to r

Did you mean to write (h w)?

- Olumide



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

Subject: Digest Footer

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


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

End of Beginners Digest, Vol 104, Issue 12
******************************************

Reply via email to