
I'd been playing with pointfree, looking at what certain patterns transformed into, and I came across this: pauls@Mudskipper> pointfree -v "\x -> x + x" ~ Transformed to pointfree style: ap (+) id Optimized expression: ap (+) id join (+) Basically I wanted to see what happened when you used a parameter multiple times within a function. Intrigued by this, I did the following: Prelude Control.Monad> :t ap (+) id ap (+) id :: (Num a, Monad ((->) a)) => a -> a I'm aware that 'ap' is related the liftM, but what is this monad, and why are we working in a monad at all? ...and surely this isn't the same as the original code as we now have a different type signature?

On 25 November 2010 01:44, Paul Sargent
I'm aware that 'ap' is related the liftM, but what is this monad, and why are we working in a monad at all?
...and surely this isn't the same as the original code as we now have a different type signature?_______________________________________________
Its the Reader monad. The Reader monad introduces a "static argument" into the computation. The code is equivalent to the original - if you want you can declare it as a binding without generalizing it to Monad: Prelude Control.Monad> let f = ap (+) id :: Num a => a -> a Pointfree is presumably introducing it because it can't find elementary definitions that are only functional types - the combinators in the Haskell Prelude and Data.Function are perhaps a little meagre. In one stroke it is a use of the 'w' combinator: f :: Num a => a -> a f = w (+) -- | W combinator - warbler - elementary duplicator. w :: (r1 -> r1 -> ans) -> r1 -> ans w f x = f x x Monadic ap for the Reader monad corresponds to the Starling 's' combinator, so it is also: g :: Num a => a -> a g = starling (+) id Again, Pointfree doesn't have starling available: starling :: (r1 -> a -> ans) -> (r1 -> a) -> r1 -> ans starling f g x = f x (g x)

Thanks Stephen, On 25 Nov 2010, at 09:12, Stephen Tetley wrote:
On 25 November 2010 01:44, Paul Sargent
wrote: [SNIP] I'm aware that 'ap' is related the liftM, but what is this monad, and why are we working in a monad at all?
...and surely this isn't the same as the original code as we now have a different type signature?_______________________________________________
Its the Reader monad.
[...]
Pointfree is presumably introducing it because it can't find elementary definitions that are only functional types [...]
In one stroke it is a use of the 'w' combinator:
-- | W combinator - warbler - elementary duplicator. w :: (r1 -> r1 -> ans) -> r1 -> ans w f x = f x x
Monadic ap for the Reader monad corresponds to the Starling 's' combinator:
starling :: (r1 -> a -> ans) -> (r1 -> a) -> r1 -> ans starling f g x = f x (g x)
The Starling and Warbler combinators make perfect sense to me. I'm still trying to see how ap in the Reader Monad is equivalent to Starling. I think this is exposing some holes in my Haskell knowledge, so I'm using it as a learning exercise. We use them in the same way, and we're saying they're equivalent: let f x = starling (+) id let g x = ap (+) id Yet, they have quite different type signatures. starling :: (r1 -> a -> ans) -> (r1 -> a) -> r1 -> ans ap :: (Monad m) => m (a -> b) -> m a -> m b So, my first question is what makes haskell choose the Reader monad in this case? Secondly, (+) is a function of two arguments, and id a function of one. This binds naturally with starling, but not apparently with ap. Apparently ap wants a single argument function within a monad as it's first argument, so to me (+) shouldn't satisfy. I suspect the answer to this has something to do with my first question. Digging a little deeper, I decided to look at the definition of ap: ap = liftM2 id liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) } liftM2 makes sense to me, but again we seem to have a mismatch of types. liftM2 wants a two argument function for it's first argument, but ap provides id. I'm finding myself tumbling further and further down the rabbit hole. Paul

Paul Sargent
Digging a little deeper, I decided to look at the definition of ap:
ap = liftM2 id
liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) }
liftM2 makes sense to me, but again we seem to have a mismatch of types. liftM2 wants a two argument function for it's first argument, but ap provides id. I'm finding myself tumbling further and further down the rabbit hole.
id has type a -> a, so if you "instantiate" a to `a2 -> r', you get: id :: (a2 -> r) -> (a2 -> r) Since -> is right-associative this is the same as: id :: (a2 -> r) -> a2 -> r So that's how id can be seen as a two-argument function in this case. That results in liftM2 id having the type: liftM2 id :: (Monad m) => m (a2 -> r) -> m a2 -> m r If you now insert the Reader monad for m, you get: liftM2 id :: (s -> a2 -> r) -> (s -> a2) -> (s -> r) So appying (liftM2 id), which is ap, to (+), causes s, a2 and r to be the same type, since (+) has type (Num a) => a -> a -> a. liftM2 id (+) :: Num a => (a -> a) -> a -> a If you then apply that to id, as in ap (+) id, you get: ap (+) id = liftM2 id (+) id :: Num a => a -> a So this explains the type, and if you then expand the definitions of liftM2 and >>= and return for the Reader monad, you will see that this corresponds to \x -> x + x. Regards, Daniel

Hi Paul Its Pointfree that's choosing `ap` - I've never got round to using it myself but I assume it only re-writes using only "standard" functions (Prelude + Base?). As there isn't a specific definition of Starling available for the functional type it chooses Monadic ap. Nowadays it could also choose (<*>) from Control.Applicative. The monad instance for functions is the Reader monad without a newtype wrapper: m x == (r1 -> x) ap :: (Monad m) => m (a -> b) -> m a -> m b Subsituting you get: ap :: (r1 -> a -> b) -> (r1 -> a) -> (r1 -> b) If you want you can knocking out the bracket of the last part... ap :: (r1 -> a -> b) -> (r1 -> a) -> r1 -> b Same with liftM2 liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r Nicer var names: liftM2 :: (Monad m) => (a -> b -> ans) -> m a -> m b -> m ans Substituting, m x == (r1 -> x) liftM2 :: (a -> b -> c) -> (r1 -> a) -> (r1 -> b) -> (r1 -> ans) This matches the Phoenix combinator also known as Big Phi. I think it was in the combinator set used by David Turner in the implementation of SASL (SASL's abstract machine used combinators as its machine code). phoenix :: (a -> b -> ans) -> (r1 -> a) -> (r1 -> b) -> r1 -> ans

I don't know whether this is related or not, but I have the following somewhere in my code: -- the following is apparently eqivalent to (\ i -> foo (bar i) i). -- pointfree suggests so. i don't understand why. (foo =<< bar) Is this a similar situation? -- Ozgur Akgun

Ozgur Akgun
I don't know whether this is related or not, but I have the following somewhere in my code:
-- the following is apparently eqivalent to (\ i -> foo (bar i) i). -- pointfree suggests so. i don't understand why. (foo =<< bar)
Is this a similar situation?
Yes, it is. In the reader monad a computation is a function of one argument: foo :: a -> e -> b bar :: e -> a Running such a computation means passing a specific argument 'e' to all those functions and regarding monadic bindings like normal let bindings. Let me write this in 'do' syntax, so it gets clearer: do x <- bar foo x becomes: let x = bar e in foo x e I found the reader monad most useful in applicative style: splits :: [a] -> [([a], [a])] splits = zip <$> inits <*> tails Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
participants (5)
-
Daniel Schoepe
-
Ertugrul Soeylemez
-
Ozgur Akgun
-
Paul Sargent
-
Stephen Tetley