17

In the comments of the question Tacit function composition in Haskell, people mentioned making a Num instance for a -> r, so I thought I'd play with using function notation to represent multiplication:

{-# LANGUAGE TypeFamilies #-}
import Control.Applicative

instance Show (a->r) where   -- not needed in recent GHC versions
  show f = " a function "

instance Eq (a->r) where     -- not needed in recent GHC versions
  f == g = error "sorry, Haskell, I lied, I can't really compare functions for equality"

instance (Num r,a~r) => Num (a -> r) where
  (+) = liftA2 (+)
  (-) = liftA2 (-)
  (*) = liftA2 (*)
  abs = liftA abs
  negate = liftA negate
  signum = liftA signum
  fromInteger a = (fromInteger a *)

Note that the fromInteger definition means I can write 3 4 which evaluates to 12, and 7 (2+8) is 70, just as you'd hope.

Then it all goes wonderfully, entertainingly weird! Please explain this wierdness if you can:

*Main> 1 2 3
18
*Main> 1 2 4
32
*Main> 1 2 5
50
*Main> 2 2 3
36
*Main> 2 2 4
64
*Main> 2 2 5
100
*Main> (2 3) (5 2)
600

[Edit: used Applicative instead of Monad because Applicative is great generally, but it doesn't make much difference at all to the code.]

Community
  • 1
  • 1
AndrewC
  • 32,300
  • 7
  • 79
  • 115
  • 2
    In GHC 7.4, it is possible to remove the dummy `Show` and `Eq` instances, as `Num` no longer requires them. – sdcvvc Aug 28 '12 at 03:39
  • 3
    `Monad` is overkill here. The simpler & more general `Applicative` suffices. – Conal Aug 28 '12 at 15:33
  • @sdcvvc I'll be upgrading sometime soon, yes. – AndrewC Aug 28 '12 at 16:53
  • @Conal You're very right. Applicative is much nicer, I was just mindlessly using the Classes from the original context. I understood the answer below when I saw `liftM2 (*) (2*) (3*)` because I thought of that as `(*) <$> (2*) <*> (3*)`, which makes sense. [Thanks for your work which led me to the wonderfully functional Applicative world. I still remember clearly when I first read Philip Wadler's _The essence of functional programming_, and I had a similar moment of revelation when reading your work on tangible values: _this_ is what UI should be like in fp, _this_ is what Applicative means.] – AndrewC Aug 28 '12 at 17:11
  • @Conal I've edited it now to use Applicative. It's surprising how much easier it feels conceptually now, with almost no change at all to the code! – AndrewC Aug 30 '12 at 08:07

1 Answers1

21

In an expression like 2 3 4 with your instances, both 2 and 3 are functions. So 2 is actually (2 *) and has a type Num a => a -> a. 3 is the same. 2 3 is then (2 *) (3 *) which is the same as 2 * (3 *). By your instance, this is liftM2 (*) 2 (3 *) which is then liftM2 (*) (2 *) (3 *). Now this expression works without any of your instances.

So what does this mean? Well, liftM2 for functions is a sort of double composition. In particular, liftM2 f g h is the same as \ x -> f (g x) (h x). So liftM2 (*) (2 *) (3 *) is then \ x -> (*) ((2 *) x) ((3 *) x). Simplifying a bit, we get: \ x -> (2 * x) * (3 * x). So now we know that 2 3 4 is actually (2 * 4) * (3 * 4).

Now then, why does liftM2 for functions work this way? Let's look at the monad instance for (->) r (keep in mind that (->) r is (r ->) but we can't write type-level operator sections):

instance Monad ((->) r) where  
    return x = \_ -> x  
    h >>= f = \w -> f (h w) w  

So return is const. >>= is a little weird. I think it's easier to see this in terms of join. For functions, join works like this:

join f = \ x -> f x x

That is, it takes a function of two arguments and turns it into a function of one argument by using that argument twice. Simple enough. This definition also makes sense. For functions, join has to turn a function of two arguments into a function of one; the only reasonable way to do this is to use that one argument twice.

>>= is fmap followed by join. For functions, fmap is just (.). So now >>= is equal to:

h >>= f = join (f . h)

which is just:

h >>= f = \ x -> (f . h) x x

now we just get rid of . to get:

h >>= f = \ x -> f (h x) x

So now that we know how >>= works, we can look at liftM2. liftM2 is defined as follows:

liftM2 f a b = a >>= \ a' -> b >>= \ b' -> return (f a' b')

We can simply this bit by bit. First, return (f a' b') turns into \ _ -> f a' b'. Combined with the \ b' ->, we get: \ b' _ -> f a' b'. Then b >>= \ b' _ -> f a' b' turns into:

 \ x -> (\ b' _ -> f a' b') (b x) x

since the second x is ignored, we get: \ x -> (\ b' -> f a' b') (b x) which is then reduced to \ x -> f a' (b x). So this leaves us with:

a >>= \ a' -> \ x -> f a' (b x)

Again, we substitute >>=:

\ y -> (\ a' x -> f a' (b x)) (a y) y

this reduces to:

 \ y -> f (a y) (b y)

which is exactly what we used as liftM2 earlier!

Hopefully now the behavior of 2 3 4 makes sense completely.

Tikhon Jelvis
  • 67,485
  • 18
  • 177
  • 214
  • Ah yes - as soon as you got to `liftM2 (*) (2 *) (3 *) 4` I saw why it was squaring the last argument - this just means `(+) $ (2*) 4 $ (3*) 4`. And `(2 3) (5 2)` has unnecessary brackets, so it's just `2 4 (5 2)` and is 300 for the same reason. – AndrewC Aug 26 '12 at 22:27
  • By the way, I'm happy with the Applicative and Monad instances for `(->) r` and should have said so in the question, it's just my brain just started leaking out of my ears when I did `2 3 4`, and I didn't even try to hand-evaluate. doh! Your explanation will make it far clearer for others though, so thanks also. – AndrewC Aug 26 '12 at 22:30
  • 2
    @AndrewC: I just wrote down my thought process from when I was figuring out exactly what `2 3 4` did, so it was helping myself as much as anybody else :P. – Tikhon Jelvis Aug 26 '12 at 22:38