understanding curried function calls

Here's a simple exercise from Stephanie Weirich's class [1] that I am having a hard time with. consider doTwice :: (a -> a) -> a -> a doTwice f x = f (f x) what does this do? ex1 :: (a -> a) -> a -> a ex1 = doTwice doTwice At least, it is clear that there is a parameter to doTwice missing. So, I wanted to do: ex1 y = (doTwice doTwice) y but this gets me nowhere as I don't know how to apply the definition of doTwice inside the parenthesis without naming the arguments. What is the systematic way to evaluate these expressions? I actually got really stumped when I considered. ex2 :: (a -> a) -> a -> a ex2 = doTwice doTwice doTwice doTwice I assume this is not the same as ex2 = (doTwice doTwice doTwice) doTwice what's being applied to what here!? Are there any resources with many practice exercises like this one? Thanks, Dimitri [1] http://www.seas.upenn.edu/~cis552/lectures/Lec2.html

Dimitri DeFigueiredo
writes:
Here's a simple exercise from Stephanie Weirich's class [1] that I am having a hard time with.
consider
doTwice :: (a -> a) -> a -> a doTwice f x = f (f x)
what does this do?
ex1 :: (a -> a) -> a -> a ex1 = doTwice doTwice
Another way to write doTwice is: doTwice :: (a -> a) -> (a -> a) doTwice f = \x -> f (f x) This is equivalent. If you stare it for a while, it should answer the rest of your questions. John

This is exactly what I did, but it doesn't give me a systematic way to evaluate the expressions. In other words, I don't really know why it works or what else to try in different circumstances. The problem arises when I have curried multi-argument functions. People complain about pointer notation in type declarations in C. Well, this is pointer notation++. And it is worse if I can't find resources to learn it. Eventually, I would like to be able to grok famous beasts like this one. foldl :: (a-> b-> a) -> a-> [b] -> a foldl f a bs= foldr (\b g x-> g(f x b)) id bs a But I need a consistent approach. Cheers, Dimitri Em 20/08/14 04:10, John Wiegley escreveu:
Dimitri DeFigueiredo
writes: Here's a simple exercise from Stephanie Weirich's class [1] that I am having a hard time with. consider doTwice :: (a -> a) -> a -> a doTwice f x = f (f x) what does this do? ex1 :: (a -> a) -> a -> a ex1 = doTwice doTwice Another way to write doTwice is: doTwice :: (a -> a) -> (a -> a) doTwice f = \x -> f (f x)
This is equivalent. If you stare it for a while, it should answer the rest of your questions.
John _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Dimitri DeFigueiredo
writes:
Eventually, I would like to be able to grok famous beasts like this one.
foldl :: (a -> b -> a) -> a -> [b] -> a foldl f a bs = foldr (\b g x -> g (f x b)) id bs a
Let's uncurry every function involved manually, after swapping the type variables to make what comes later less confusing: foldl :: (b -> a -> b) -> b -> [a] -> b foldl f b as = foldr (\a g b -> g (f b a)) id as b foldl' :: (b -> a -> b) -> b -> ([a] -> b) foldl' f b = \as -> foldr (\a g b -> g (f b a)) id as b foldl'' :: (b -> a -> b) -> (b -> ([a] -> b)) foldl'' f = \b -> \as -> foldr (\a g b -> g (f b a)) id as b foldl''' :: (b -> (a -> b)) -> (b -> ([a] -> b)) foldl''' f = \b -> \as -> (((foldr (\a -> \g -> \b -> g ((f b) a))) id) as) b We have a function that takes a function and returns a function. The function it takes maps a value to *a function from an element to a value of the same type*. The function it returns maps a value to a function over a list of elements to a value of the same type. Or: Given a function a -> (b -> a), foldl lifts this to a function over lists of elements, a -> ([b] -> a). Not quite a map, since map lifts a -> b to [a] -> [b]. But map is just a fold: map f :: (a -> b) -> ([a] -> [b]) map f = foldl (\b -> \a -> b ++ [f a]) [] Looking at the types, we're dropping "b ->" from the input and output functions of foldl, and changing the final result to a list: foldl :: (b -> (a -> b)) -> (b -> ([a] -> b)) map :: (a -> b) -> ([a] -> [b]) Folds expose the "book-keeping" value that map uses to accumulate its result, allowing us to accumulate any value we want. Now foldMap should make more sense (I've specialized it to lists here for the sake of presentation): foldMap' :: Monoid b => (a -> b) -> ([a] -> b) We don't have access to the accumulator, as we do with foldl, but knowing it's a Monoid we can merge values into the result by returning monoidal values. All of these types can be generalized to work over any notion of "container" using Data.Foldable: foldl :: Foldable f => (b -> (a -> b)) -> (b -> (f a -> b)) fmap :: Functor f => (a -> b) -> (f a -> f b) foldMap :: Foldable f, Monoid b => (a -> b) -> (f a -> b) I have diverted from the main theme of how to read curried function types, but I wanted to drive home how potent this notion of "functions returning functions" is, and that currying really only gives us a more convenient way of naming the arguments to the lambda abstractions being returned. (In GHC there can also be performance differences between the two, but otherwise they should be regarded as equivalent). John

Dear Dimitri: I am having a hard time with.
doTwice f x = f (f x) what does this do? What is the systematic way to evaluate these expressions?
You might recognize the numeral two from pure http://en.wikipedia.org/wiki/Lambda_calculus and the fact that some lambda expressions are irreducible while others never arrive at such a normal form.
Are there any resources with many practice exercises like this one?
None that I am aware of. You mostly find theoretical revelations. Possibly because there is often nothing more practical than the right theory. But it is easy to make up some practical examples to play with: let pow2 f x = f (f x) in [ pow2 (pow2 (pow2 (1+)))) 0, pow2 pow2 pow2 (1+) 0] == [2^3, 2^2^2^2] Current Haskell compilers will not tell you directly that pow2 pow2 pow2 pow2 = do65536times and pow 2 pow2 (pow2 pow2) = do256times but just do so in concrete cases. Try pow2 pow2 (+1) 0 Or pow2 pow2 (++"-") "." Thanks,
Dimiti [1] http://www.seas.upenn.edu/~cis552/lectures/Lec2.html

On Wed, Aug 20, 2014 at 02:19:16AM -0600, Dimitri DeFigueiredo wrote:
doTwice :: (a -> a) -> a -> a doTwice f x = f (f x)
what does this do?
ex1 :: (a -> a) -> a -> a ex1 = doTwice doTwice
At least, it is clear that there is a parameter to doTwice missing. So, I wanted to do:
ex1 y = (doTwice doTwice) y
but this gets me nowhere as I don't know how to apply the definition of doTwice inside the parenthesis without naming the arguments.
Note that function application associates to the left, so (doTwice doTwice) y = doTwice doTwice y So, we have ex1 y = doTwice doTwice y = doTwice (doTwice y) -- definition of doTwice Now we are stuck again; we can add another arbitrary parameter. ex1 y z = doTwice (doTwice y) z = (doTwice y) ((doTwice y) z) = doTwice y (doTwice y z) -- remove unnecessary parentheses = y (y (doTwice y z)) = y (y (y (y z))) Does that help?
What is the systematic way to evaluate these expressions? I actually got really stumped when I considered.
ex2 :: (a -> a) -> a -> a ex2 = doTwice doTwice doTwice doTwice
I assume this is not the same as
ex2 = (doTwice doTwice doTwice) doTwice
These ARE exactly the same. It's always the case that f w x y z ... = (((f w) x) y) z ... -Brent

Hi Brent, Is this how we go about solving these then? Keep adding parameters on the right until we have enough of them that we are able to apply the function definition. In other words, in ex1 = doTwice doTwice the first doTwice needs another parameter, so you added 'y'. ex1 y = (doTwice doTwice) y = doTwice doTwice y Then we can apply the definition. We got stuck again, so you added another parameter 'z'. Then again applied the definition of the left most function. And so on. Is there a similarly systematic approach for the foldl implemented by foldr example? I'm looking for systematic approaches that I can then practice. Thanks! Dimitri Em 20/08/14 14:30, Brent Yorgey escreveu:
On Wed, Aug 20, 2014 at 02:19:16AM -0600, Dimitri DeFigueiredo wrote:
doTwice :: (a -> a) -> a -> a doTwice f x = f (f x)
what does this do?
ex1 :: (a -> a) -> a -> a ex1 = doTwice doTwice
At least, it is clear that there is a parameter to doTwice missing. So, I wanted to do:
ex1 y = (doTwice doTwice) y
but this gets me nowhere as I don't know how to apply the definition of doTwice inside the parenthesis without naming the arguments. Note that function application associates to the left, so
(doTwice doTwice) y = doTwice doTwice y
So, we have
ex1 y = doTwice doTwice y = doTwice (doTwice y) -- definition of doTwice
Now we are stuck again; we can add another arbitrary parameter.
ex1 y z = doTwice (doTwice y) z = (doTwice y) ((doTwice y) z) = doTwice y (doTwice y z) -- remove unnecessary parentheses = y (y (doTwice y z)) = y (y (y (y z)))
Does that help?
What is the systematic way to evaluate these expressions? I actually got really stumped when I considered.
ex2 :: (a -> a) -> a -> a ex2 = doTwice doTwice doTwice doTwice
I assume this is not the same as
ex2 = (doTwice doTwice doTwice) doTwice These ARE exactly the same. It's always the case that
f w x y z ... = (((f w) x) y) z ...
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi Dimitri, Yes, this is one possible systematic approach, which will always work. And it's the one I happen to prefer. (Another approach is to turn everything into lambdas, as pointed out earlier in this thread, but that is noisier and does not correspond to the usual Haskelly way of defining functions.) I am not sure exactly what you are trying to do with the foldl/foldr example, but you should be able to use this same approach to evaluate it. -Brent On Wed, Aug 20, 2014 at 03:11:22PM -0600, Dimitri DeFigueiredo wrote:
Hi Brent,
Is this how we go about solving these then? Keep adding parameters on the right until we have enough of them that we are able to apply the function definition.
In other words, in ex1 = doTwice doTwice
the first doTwice needs another parameter, so you added 'y'. ex1 y = (doTwice doTwice) y = doTwice doTwice y
Then we can apply the definition. We got stuck again, so you added another parameter 'z'. Then again applied the definition of the left most function. And so on.
Is there a similarly systematic approach for the foldl implemented by foldr example? I'm looking for systematic approaches that I can then practice.
Thanks!
Dimitri
Em 20/08/14 14:30, Brent Yorgey escreveu:
On Wed, Aug 20, 2014 at 02:19:16AM -0600, Dimitri DeFigueiredo wrote:
doTwice :: (a -> a) -> a -> a doTwice f x = f (f x)
what does this do?
ex1 :: (a -> a) -> a -> a ex1 = doTwice doTwice
At least, it is clear that there is a parameter to doTwice missing. So, I wanted to do:
ex1 y = (doTwice doTwice) y
but this gets me nowhere as I don't know how to apply the definition of doTwice inside the parenthesis without naming the arguments. Note that function application associates to the left, so
(doTwice doTwice) y = doTwice doTwice y
So, we have
ex1 y = doTwice doTwice y = doTwice (doTwice y) -- definition of doTwice
Now we are stuck again; we can add another arbitrary parameter.
ex1 y z = doTwice (doTwice y) z = (doTwice y) ((doTwice y) z) = doTwice y (doTwice y z) -- remove unnecessary parentheses = y (y (doTwice y z)) = y (y (y (y z)))
Does that help?
What is the systematic way to evaluate these expressions? I actually got really stumped when I considered.
ex2 :: (a -> a) -> a -> a ex2 = doTwice doTwice doTwice doTwice
I assume this is not the same as
ex2 = (doTwice doTwice doTwice) doTwice These ARE exactly the same. It's always the case that
f w x y z ... = (((f w) x) y) z ...
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On 2014-08-20 11:19, Dimitri DeFigueiredo wrote:
What is the systematic way to evaluate these expressions? The canonical evaluation of Haskell is given by the Report[0]. Among other things, it gives, in chapter 3, the semantics of Haskell constructs.
f x = b is equivalent to f = \x -> b
However, since Haskell's semantics resemble those of lambda calculus[1] so much, we (or at least I) usually use lambda calculus semantics to reason about Haskell code, keeping in mind the how Haskell expressions desugar. In our case, the relevant syntactic sugar is that that
\x y -> b is equivalent to \x -> \y -> b and that function application is left-associative. That means that f x y is equivalent to (f x) y
Returning to your examples, they give us:
ex1 = doTwice doTwice -- inlining the definition of doTwice = (\f x -> f (f x)) doTwice -- beta reduction = \x -> doTwice (doTwice x) -- inline doTwice = \x -> doTwice ((\f y -> f (f y)) x) -- beta = \x -> doTwice (\y -> x (x y)) -- inline doTwice = \x -> (\f z -> f (f z)) (\y -> x (x y)) -- beta = \x -> (\z -> (\y -> x (x y)) ((\w -> x (x w)) z)) -- beta = \x -> (\z -> (\y -> x (x y)) (x (x z))) -- beta = \x -> (\z -> x (x (x (x z)))) -- combining lambdas = \x z -> x (x (x z)) -- irreducible And similarly, combining steps for brevity: -- Proposition: foldl f a xs = foldr (\e g b -> g (f b e)) id bs a
-- Proof: By decomposition into constructor cases
-- Case [] foldl f a [] = a foldr (\e g b -> g (f b e)) id [] a = (foldr (\e g b -> g (f b e)) id []) a = id a = a
-- Case (:) -- Induction hypothesis: -- foldl f a xs = foldr (\e g b -> g (f b e)) id xs a -- for all f, a foldl f a (x:xs) = foldl f (f a x) xs foldr (\e g b -> g (f b e)) id (x:xs) a = (foldr (\e g b -> g (f b e)) id (x:xs)) a = ((\e g b -> g (f b e)) x (foldr (\e g b -> g (f b e)) id xs)) a = (\b -> foldr (\e g b -> g (f b e)) id xs (f b x)) a = foldr (\e g b -> g (f b e)) id xs (f a x) = foldl f (f a x) xs
Hope this helps, Gesh [0] - https://www.haskell.org/onlinereport/haskell2010/ [1] - https://en.wikipedia.org/wiki/Lambda_calculus#Reduction

Fantastic Gesh! That's much more clear now. These are the rules I wanted. I will try to apply them everywhere to practice now. I think the rule \x y -> b is equivalent to \x -> \y -> b is what I was missing to avoid the confusion when trying to evaluate expressions with multi-parameter functions. Thanks, Dimitri Em 20/08/14 18:14, Gesh escreveu:
On 2014-08-20 11:19, Dimitri DeFigueiredo wrote:
What is the systematic way to evaluate these expressions? The canonical evaluation of Haskell is given by the Report[0]. Among other things, it gives, in chapter 3, the semantics of Haskell constructs.
However, since Haskell's semantics resemble those of lambda calculus[1] so much, we (or at least I) usually use lambda calculus semantics to reason about Haskell code, keeping in mind the how Haskell expressions desugar.
f x = b is equivalent to f = \x -> b
In our case, the relevant syntactic sugar is that that
\x y -> b is equivalent to \x -> \y -> b and that function application is left-associative. That means that f x y is equivalent to (f x) y
Returning to your examples, they give us:
ex1 = doTwice doTwice -- inlining the definition of doTwice = (\f x -> f (f x)) doTwice -- beta reduction = \x -> doTwice (doTwice x) -- inline doTwice = \x -> doTwice ((\f y -> f (f y)) x) -- beta = \x -> doTwice (\y -> x (x y)) -- inline doTwice = \x -> (\f z -> f (f z)) (\y -> x (x y)) -- beta = \x -> (\z -> (\y -> x (x y)) ((\w -> x (x w)) z)) -- beta = \x -> (\z -> (\y -> x (x y)) (x (x z))) -- beta = \x -> (\z -> x (x (x (x z)))) -- combining lambdas = \x z -> x (x (x z)) -- irreducible And similarly, combining steps for brevity: -- Proposition: foldl f a xs = foldr (\e g b -> g (f b e)) id bs a
-- Proof: By decomposition into constructor cases
-- Case [] foldl f a [] = a foldr (\e g b -> g (f b e)) id [] a = (foldr (\e g b -> g (f b e)) id []) a = id a = a
-- Case (:) -- Induction hypothesis: -- foldl f a xs = foldr (\e g b -> g (f b e)) id xs a -- for all f, a foldl f a (x:xs) = foldl f (f a x) xs foldr (\e g b -> g (f b e)) id (x:xs) a = (foldr (\e g b -> g (f b e)) id (x:xs)) a = ((\e g b -> g (f b e)) x (foldr (\e g b -> g (f b e)) id xs)) a = (\b -> foldr (\e g b -> g (f b e)) id xs (f b x)) a = foldr (\e g b -> g (f b e)) id xs (f a x) = foldl f (f a x) xs
Hope this helps, Gesh
[0] - https://www.haskell.org/onlinereport/haskell2010/ [1] - https://en.wikipedia.org/wiki/Lambda_calculus#Reduction _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (5)
-
Brent Yorgey
-
Dimitri DeFigueiredo
-
Gesh
-
John Wiegley
-
Roman Czyborra