Currying in Haskell with 2+ arguments - haskell

I'm starting to learn Haskell so I need to understand currying also (it's the first time I've seen this technique too). I think I get how it works in some cases where the currification only "eliminates" one of the parameters. Like in the next example where I'm trying to calculate the product of 4 numbers.
This is the uncurried function:
prod :: Integer->Integer->Integer->Integer->Integer
prod x y z t = x * y * z * t
This is the curried function:
prod' :: Integer->Integer->Integer->Integer->Integer
prod' x y z = (*) (x*y*z)
But I don't understand how could I continue this dynamic and do for example the same function with only two arguments and so on:
prod'' :: Integer->Integer->Integer->Integer->Integer
prod'' x y =

This is the uncurried function:
prod :: Integer -> Integer -> Integer -> Integer -> Integer
prod x y z t = x * y * z * t
This is already a curried function. In fact all functions in Haskell are automatically curried. Indeed, you here wrote a function that looks like:
prod :: Integer -> (Integer -> (Integer -> (Integer -> Integer)))
Haskell will thus produce a function that looks like:
prod :: Integer -> (Integer -> (Integer -> (Integer -> Integer)))
prod = \x -> (\y -> (\z -> (\t -> x * y * z * t)))
Indeed, we can for example generate such function:
prod2 = prod 2
This will have type:
prod2 :: Integer -> (Integer -> (Integer -> Integer))
prod2 = prod 2
and we can continue with:
prod2_4 :: Integer -> (Integer -> Integer)
prod2_4 = prod2 4
and eventually:
prod2_4_6 :: Integer -> Integer
prod2_4_6 = prod2_4 6
EDIT
The function prod' with:
prod'' x y = (*) ((*) (x*y))
Since that means you multiply (*) (x*y) with the next parameter. But (*) (x*y) is a function. You can only multiply numbers. Strictly speaking you can make functions numbers. But the Haskell compiler thus complains that:
Prelude> prod'' x y = (*) ((*) (x*y))
<interactive>:1:1: error:
• Non type-variable argument in the constraint: Num (a -> a)
(Use FlexibleContexts to permit this)
• When checking the inferred type
prod'' :: forall a.
(Num (a -> a), Num a) =>
a -> a -> (a -> a) -> a -> a
It thus says that you here aim to perform an operation with a function a -> a as first operand, but that this function is not an instance of the Num typeclass.

What you have is
prod x y z t = x * y * z * t
= (x * y * z) * t
= (*) (x * y * z) t
Hence by eta reduction (where we replace foo x = bar x with foo = bar)
prod x y z = (*) (x * y * z)
= (*) ( (x * y) * z )
= (*) ( (*) (x * y) z )
= ((*) . (*) (x * y)) z
so that by eta reduction again,
prod x y = (*) . (*) (x * y)
Here (.) is the function composition operator, defined as
(f . g) x = f (g x)
What you're asking about is known as point-free style. "Point-free" means "without explicitly mentioning the [implied] arguments" ("point" is a mathematician's jargon for "argument" here).
"Currying" is an orthogonal issue, although Haskell being a curried language makes such definitions -- and partial application ones, shown in Willem's answer -- easier to write. "Currying" means functions take their arguments one at a time, so it is easy to partially apply a function to a value.
We can continue the process of pulling the last argument out so it can be eliminated by eta reduction further. But it usually rapidly leads to more and more obfuscated code, like prod = ((((*) .) . (*)) .) . (*).
That's because written code is a one-dimensional encoding of an inherently two-dimensional (or even higher-dimensional) computational graph structure,
prod =
/
*
/ \
*
/ \
<-- *
\
You can experiment with it here. E.g., if (*) were right-associative, we'd get even more convoluted code
\x y z t -> x * (y * (z * t))
==
(. ((. (*)) . (.) . (*))) . (.) . (.) . (*)
representing just as clear-looking, just slightly rearranged, graph structure
/
<-- *
\ /
*
\ /
*
\

Related

Starting with Haskell

Can someone explain to me whats going on in this function?
applyTwice :: (a -> a) -> a -> a
applyTwice f x = f (f x)
I do understand what curried functions are, this could be re-written like this:
applyTwice :: ((a -> a) -> (a -> (a)))
applyTwice f x = f (f x)
However I dont fully understand the (+3) operator and how it works. Maybe it's something really stupid but I can't figure it out.
Can someone explain step by step how the function works? Thanks =)
applyTwice :: ((a -> a) -> (a -> (a)))
applyTwice f x = f (f x)
Haskell has "operator slicing": if you omit one or both of the arguments to an operator, Haskell automatically turns it into a function for you.
Specifically, (+3) is missing the first argument (Haskell has no unary +). So, Haskell makes that expression into a function that takes the missing argument, and returns the input value plus 3:
-- all the following functions are the same
f1 x = x + 3
f2 = (+3)
f3 = \ x -> x + 3
Similarly, if you omit both arguments, Haskell turns it into a function with two (curried) arguments:
-- all the following functions are the same
g1 x y = x + y
g2 = (+)
g3 = \ x y -> x + y
From comments: note that Haskell does have unary -. So, (-n) is not an operator slice, it just evaluates the negative (same as negate n).
If you want to slice binary - the way you do +, you can use (subtract n) instead:
-- all the following functions are the same
h1 x = x - 3
h2 = subtract 3
h3 = \ x -> x - 3

How is Ratio implemented in Haskell?

This is something I have been confused about for a while and I am not sure how I can learn more about it. Let's say I have the following program:
main :: IO ()
main = do
x <- liftM read getLine
y <- liftM read getLine
print (x % y)
If I run this with the input 6 and 2, it will print 3 % 1.
At what point does the simplification happen (namely the division by the gcd)? Is it implemented in show? If so, then is the underlying representation of the rational still 6 % 2? If not, then does (%) do the simplification? I was under the impression that (%) is a data constructor, so how would a data constructor do anything more than "construct"? More importantly, how would I actually go about doing similar things with my own data constructors?
I appreciate any help on the topic.
Ratio is actually implemented in GHC.Real (on GHC, obviously), and is defined as
data Ratio a = !a :% !a deriving (Eq)
The bangs are just there for strictness. As you can see, the function % is not a data constructor, but :% is. Since you aren't supposed to construct a Ratio directly, you use the % function, which calls reduce.
reduce :: (Integral a) => a -> a -> Ratio a
{-# SPECIALISE reduce :: Integer -> Integer -> Rational #-}
reduce _ 0 = ratioZeroDenominatorError
reduce x y = (x `quot` d) :% (y `quot` d)
where d = gcd x y
(%) :: (Integral a) => a -> a -> Ratio a
x % y = reduce (x * signum y) (abs y)
The rule is that if an operator starts with a colon :, then it is a constructor, otherwise it is just a normal operator. In fact, this is part of the Haskell standard, all type operators must have a colon as their first character.
You can just look at the source to see for yourself:
instance (Integral a) => Num (Ratio a) where
(x:%y) + (x':%y') = reduce (x*y' + x'*y) (y*y')
(x:%y) - (x':%y') = reduce (x*y' - x'*y) (y*y')
(x:%y) * (x':%y') = reduce (x * x') (y * y')
negate (x:%y) = (-x) :% y
abs (x:%y) = abs x :% y
signum (x:%_) = signum x :% 1
fromInteger x = fromInteger x :% 1
reduce :: (Integral a) => a -> a -> Ratio a
reduce _ 0 = ratioZeroDenominatorError
reduce x y = (x `quot` d) :% (y `quot` d)
where d = gcd x y

What does the following lambda function in Haskell actually return?

Consider the following lambda function in Haskell:
(\x g n -> g (x * n))
It takes two parameters: a Num named x and a function g which takes a Num named n and returns something else. The lambda function returns another function of the same type as g:
(\x g n -> g (x * n)) :: Num a => a -> (a -> t) -> a -> t
What I don't understand is what does the expression g (x * n) actually represent. For example consider the following use case:
((\x g n -> g (x * n)) 2 id)
In this case x is 2 and g is id. However what is n? What does g (x * n) represent? By simple substitution it can be reduced to id (2 * n). Is this the same as id . (2 *)? If so then why not simply write (\x g -> g . (x *))?
I'm going to contradict chirlu. (\x g n -> g (x * n)) is a function of one argument.
Because all functions only take one argument. It's just that that function returns another function, which returns another function.
Desugared, it's the same as
\x -> \g -> \n -> g (x * n)
Which is pretty close to its type
Num a => a -> (a -> b) -> a -> b
Expanding your use case:
(\x g n -> g (x * n)) 2 id
Let's expand that
(\x -> \g -> \n -> g (x * n)) 2 id
Which is the same as
((\x -> \g -> \n -> g (x * n)) 2) id
Now we can apply the inner function to its argument to get
(let x = 2 in \g -> \n -> g (x * n)) id
or
(\g -> \n -> g (2 * n)) id
Now we can apply this function to its argument to get
let g = id in \n -> g (2 * n)
or
\n -> id (2 * n)
Which, via inspection, we can state is equivalent to
\n -> 2 * n
Or, point-free
(2*)
You're close. The last example you gave, ((\x g n -> g (x * n)) 2 id) represents a partial application of the function. It has a type signature of Num a => a -> t and is equivalent to the following: \n -> id (2 * n).

Numbers as multiplicative functions (weird but entertaining)

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.]
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.

Why is the type of this function (a -> a) -> a?

Why is the type of this function (a -> a) -> a?
Prelude> let y f = f (y f)
Prelude> :t y
y :: (t -> t) -> t
Shouldn't it be an infinite/recursive type?
I was going to try and put into words what I think it's type should be, but I just can't do it for some reason.
y :: (t -> t) -> ?WTFIsGoingOnOnTheRHS?
I don't get how f (y f) resolves to a value. The following makes a little more sense to me:
Prelude> let y f x = f (y f) x
Prelude> :t y
y :: ((a -> b) -> a -> b) -> a -> b
But it's still ridiculously confusing. What's going on?
Well, y has to be of type (a -> b) -> c, for some a, b and c we don't know yet; after all, it takes a function, f, and applies it to an argument, so it must be a function taking a function.
Since y f = f x (again, for some x), we know that the return type of y must be the return type of f itself. So, we can refine the type of y a bit: it must be (a -> b) -> b for some a and b we don't know yet.
To figure out what a is, we just have to look at the type of the value passed to f. It's y f, which is the expression we're trying to figure out the type of right now. We're saying that the type of y is (a -> b) -> b (for some a, b, etc.), so we can say that this application of y f must be of type b itself.
So, the type of the argument to f is b. Put it all back together, and we get (b -> b) -> b — which is, of course, the same thing as (a -> a) -> a.
Here's a more intuitive, but less precise view of things: we're saying that y f = f (y f), which we can expand to the equivalent y f = f (f (y f)), y f = f (f (f (y f))), and so on. So, we know that we can always apply another f around the whole thing, and since the "whole thing" in question is the result of applying f to an argument, f has to have the type a -> a; and since we just concluded that the whole thing is the result of applying f to an argument, the return type of y must be that of f itself — coming together, again, as (a -> a) -> a.
Just two points to add to other people's answers.
The function you're defining is usually called fix, and it is a fixed-point combinator: a function that computes the fixed point of another function. In mathematics, the fixed point of a function f is an argument x such that f x = x. This already allows you to infer that the type of fix has to be (a -> a) -> a; "function that takes a function from a to a, and returns an a."
You've called your function y, which seems to be after the Y combinator, but this is an inaccurate name: the Y combinator is one specific fixed point combinator, but not the same as the one you've defined here.
I don't get how f (y f) resolves to a value.
Well, the trick is that Haskell is a non-strict (a.k.a. "lazy") language. The calculation of f (y f) can terminate if f doesn't need to evaluate its y f argument in all cases. So, if you're defining factorial (as John L illustrates), fac (y fac) 1 evaluates to 1 without evaluating y fac.
Strict languages can't do this, so in those languages you cannot define a fixed-point combinator in this way. In those languages, the textbook fixed-point combinator is the Y combinator proper.
#ehird's done a good job of explaining the type, so I'd like to show how it can resolve to a value with some examples.
f1 :: Int -> Int
f1 _ = 5
-- expansion of y applied to f1
y f1
f1 (y f1) -- definition of y
5 -- definition of f1 (the argument is ignored)
-- here's an example that uses the argument, a factorial function
fac :: (Int -> Int) -> (Int -> Int)
fac next 1 = 1
fac next n = n * next (n-1)
y fac :: Int -> Int
fac (y fac) -- def. of y
-- at this point, further evaluation requires the next argument
-- so let's try 3
fac (y fac) 3 :: Int
3 * (y fac) 2 -- def. of fac
3 * (fac (y fac) 2) -- def. of y
3 * (2 * (y fac) 1) -- def. of fac
3 * (2 * (fac (y fac) 1) -- def. of y
3 * (2 * 1) -- def. of fac
You can follow the same steps with any function you like to see what will happen. Both of these examples converge to values, but that doesn't always happen.
Let me tell about a combinator. It's called the "fixpoint combinator" and it has the following property:
The Property: the "fixpoint combinator" takes a function f :: (a -> a) and discovers a "fixed point" x :: a of that function such that f x == x. Some implementations of the fixpoint combinator might be better or worse at "discovering", but assuming it terminates, it will produce a fixed point of the input function. Any function that satisfies The Property can be called a "fixpoint combinator".
Call this "fixpoint combinator" y. Based on what we just said, the following are true:
-- as we said, y's input is f :: a -> a, and its output is x :: a, therefore
y :: (a -> a) -> a
-- let x be the fixed point discovered by applying f to y
y f == x -- because y discovers x, a fixed point of f, per The Property
f x == x -- the behavior of a fixed point, per The Property
-- now, per substitution of "x" with "f x" in "y f == x"
y f == f x
-- again, per substitution of "x" with "y f" in the previous line
y f == f (y f)
So there you go. You have defined y in terms of the essential property of the fixpoint combinator:
y f == f (y f). Instead of assuming that y f discovers x, you can assume that x represents a divergent computation, and still come to the same conclusion (iinm).
Since your function satisfies The Property, we can conclude that it is a fixpoint combinator, and that the other properties we have stated, including the type, are applicable to your function.
This isn't exactly a solid proof, but I hope it provides additional insight.

Resources