[Haskell-beginners] Understanding Monads: Help with 20 Intermediate Haskell Exercises

Gesh gesh at gesh.uni.cx
Wed May 18 17:10:08 UTC 2016


On 2016-05-18 13:24, Tushar Tyagi wrote:
> Hi,
>
> In order to wrap my head around Applicatives and Monads, I started 
> doing the
> exercises at 
> http://blog.tmorris.net/posts/20-intermediate-haskell-exercises/
>
> The main class being used for the questions is:
> |class Misty m where banana :: (a -> m b) -> m a -> m b unicorn :: a -> 
> m afurry' :: (a -> b) -> m a -> m b Question #13 asks to create the 
> following function: ||apple :: (Misty m) => m a -> m (a -> b) -> m b |||After thinking for around an hour for this, I could not crack it and 
> tried looking at other people's solutions, two of which are: | |apple 
> = banana . flip furry' apple ma mab = banana (\ab -> furry' ab ma) mab ||
|Note that these two definitions are equivalent, as we may calculate:
 >   banana . flip furry'
 > = banana . (\x y -> furry' y x)
 > = \z -> banana ((\x y -> furry' y x) z)
 > = \z -> banana (\y -> furry' y z)
 > = \ma -> banana (\ab -> furry' ab ma)
So far, we haven't made use of anything about banana and furry' - this
calculation works for any pair of functions such that the expression 
typechecks.
However, we only know that the expression has type (a -> b) for some a,b.
Suppose we assume that b is a type of form (c -> d), giving the entire
expression the type (a -> c -> d). Then we may write:
 > = \ma mab -> banana (\ab -> furry' ab ma) mab
To see this point in another context, consider the function `id x = x`.
If we assume that `x :: a -> b` (e.g. by writing the type signature
`id :: (a -> b) -> (a -> b)`), then we may also write `id f = \x -> f x`.

In our case, we may make this assumption, since banana accepts two 
arguments.
(More formally, `banana :: a -> b -> c` for some a,b,c).
|
> ||
> |I also tried hoogle to see what this function is in the real world, 
> and the underlying implementation in the source code. Turns out, one 
> of the applicatives uses this flip technique (monads use a different 
> one): |(<**>) = liftA2 (flip ($))
> |Although the code compiles with the solutions, I am still not able to 
> wrap my head around them. |
This is a good idea in general if you're stuck with these questions.
However, it does come with the risk of mistakenly thinking you've found the
correct real-world code.
This is the case here. Whereas (<**>) and apple have the same type, they 
have
different semantics. Instead, you want `flip ap`.
 > ap           :: (Monad m) => m (a -> b) -> m a -> m b
 > ap m1 m2     = do { x1 <- m1; x2 <- m2; return (x1 x2) }
It is left as an exercise to the reader to show that, by the desugaring of
do-notation as specified in section 3.14 of the Haskell 98 report, we 
have the
following equivalent definition of `apple=flip ap`:
 > apple mx mf = mf >>= \f -> mx >>= \x -> return (f x)

We may then use the definitions:
 > liftM        :: (Monad m) => (a1 -> r) -> m a1 -> m r
 > liftM f m1   = do { x1 <- m1; return (f x1) }
 > (=<<)        :: Monad m => (a -> m b) -> m a -> m b
 > f =<< x      = x >>= f
to obtain:
 > apple mx mf = mf >>= \f -> mx >>= \x -> return (f x)
 >             = mf >>= \f -> liftM f mx
 >             = flip liftM mx =<< mf
Some pointfreeifying gives:
 >   \mx mf -> flip liftM mx =<< mf
 > = \mx mf -> (=<<) (flip liftM mx) mf
 > = \mx -> (=<<) (flip liftM mx)
 > = (=<<) . flip liftM
Notice that (=<<) and banana have the same type, and so do liftM and furry',
to realize this is the original definition you gave.

In contrast, <**> would reduce to (exercise):
 > mx <**> mf = mx >>= \x -> mf >>= \f -> return (f x)
Note that the order of the `mx >>=...` and `mf >>=...` parts is reversed.
In general, these might not commute.
For example, if `mx=print 1`, `mf=print 2 >>= \_ -> return id`, we'd 
have that
`mx `apple` mf` prints first 2, then 1, whereas `mx <**> mf` prints first 1,
then 2.
> |For instance, from what I understand from composition, the output of 
> one function becomes the input of the next one. But the input and 
> outputs of these functions vary: banana :: Misty m => (a -> m b) -> m 
> a -> m b flip furry' :: Misty m => m a -> (a -> b) -> m b banana . 
> flip furry' :: Misty m => m a -> m (a -> b) -> m b |
> |I am thinking that the entire `(a -> b) -> m b` in flip furry' ||is being sent to banana as the first argument: (a -> m b), but what 
> happens after that? |
|This is correct.

To be completely formal, this is how you show that `banana . flip 
furry'` has
the desired type. (cf. TaPL by Benjamin Pierce)
(Note that we drop the Misty m contexts for convenience):
 > flip :: (a -> b -> c) -> b -> a -> c
 > -------------------------------------- (T-ARR-ASSOC)
 > flip :: (a -> b -> c) -> (b -> a -> c)
 > furry' :: (a -> b) -> m a -> m b
 > ----------------------------------------------------- (T-APP)
 > flip furry' :: m a -> (a -> b) -> m b
 > --------------------------------------- (T-ARR-ASSOC)
 > flip furry' :: m a -> ((a -> b) -> m b)
 >
 > banana :: (a -> m b) -> m a -> m b
 > ------------------------------------ (T-ARR-ASSOC)
 > banana :: (a -> m b) -> (m a -> m b)
 >
 > (.) :: (b -> c) -> (a -> b) -> a -> c
 > --------------------------------------------------------------------- 
(T-INST)
 > (.) :: ((a -> m b) -> (m a -> m b)) -> (d -> (a -> m b)) -> d -> (m a 
-> m b)
 > banana :: (a -> m b) -> (m a -> m b)
 > ------------------------------------------------- (T-APP)
 > (.) banana :: (d -> (a -> m b)) -> d -> (m a -> m b)
 > --------------------------------------------------------------------- 
(T-INST)
 > (.) banana :: (m a -> ((a -> b) -> m b)) -> m a -> (m (a -> b) -> m b)
 > flip furry' :: m a -> ((a -> b) -> m b)
 > --------------------------------------------------------------------- 
(T-APP)
 > (.) banana (flip furry') :: m a -> (m (a -> b) -> m b)
 > ------------------------------------------------------ (T-ARR-ASSOC')
 > banana . flip furry' :: m a -> m (a -> b) -> m b


Basically, what's going on is that T-APP makes sure that in the expression
`f x`, f :: a -> b and x :: a; and T-ARR-ASSOC and T-ARR-ASSOC' allow us to
rewrite the type (a -> b -> c) as (a -> (b -> c)) and back.

The interesting bit is the occurrences of T-INST. What's going on is 
that you're
applying a polymorphic function at a more specified type. T-INST allows 
you to
instantiate the type variables in a type so as to make stuff line up.
This allows us, for example, to write:
 > idFunc :: (a -> b) -> (a -> b)
 > idFunc f = id f
with the derivation:
 > id :: a -> a
 > ------------ (T-INST)
 > id :: (a -> b) -> (a -> b)
 > f  :: (a -> b)
 > -------------------------- (T-APP)
 > id f :: (a -> b)

In our case, we have two occurrences of T-INST. Each of them is there in 
order
to make the type variables in (.) line up with the types of banana and 
furry'.
The occurrences are reproduced below:
 > (.) :: (b -> c) -> (a -> b) -> a -> c
 > --------------------------------------------------------------------- 
(T-INST)
 > (.) :: ((a -> m b) -> (m a -> m b)) -> (d -> (a -> m b)) -> d -> (m a 
-> m b)

 > (.) banana :: (d -> (a -> m b)) -> d -> (m a -> m b)
 > --------------------------------------------------------------------- 
(T-INST)
 > (.) banana :: (m a -> ((a -> b) -> m b)) -> m a -> (m (a -> b) -> m b)
Note that in order to get (.) banana to be able to get furry' as a 
parameter,
we had to give a the type (a -> b) and d the type m a.
Similarly, when we got (.) to be able to get banana as a parameter, we also
forced its second parameter to be a binary function.

|
> |In the second solution, the types pass, i.e. the lambda is basically 
> furry' which has the type a -> ... -> m b, exactly what is needed in 
> the call to banana. But where will it get the function ab? And how 
> will banana work with the second argument? The definition in the class 
> requires it to be `m a`, but here we are passing it `m a -> m b`. |
|In light of the above, you may want to recheck this claim.

HTH,
Gesh

P.S. Sorry if this email is overly long and formal.
|||


More information about the Beginners mailing list