Function Type Confusion ..

I was reading "Arrows and Computation" http://www.soi.city.ac.uk/~ross/papers/fop.ps.gz (trying to lose my 'beginner' status) when I saw (on page one) add :: (b -> Int) -> (b -> Int) -> (b -> Int) add f g b = f b + g b It seemed like the type definition was wrong (short at least). I tried it anyway .. module Main where add :: (b -> Int) -> (b -> Int) -> (b -> Int) add f g b = f b + g b main = do x <- return $ add (+2) (+3) 7 print x The program compiles and runs and produces '19' ! For fun I loaded into ghci and got what I believe is the proper type .. *Main> :t add add :: (b -> Int) -> (b -> Int) -> b -> Int When I try the same thing with something simpler (leaving a bit off the type definition) I get the expected error (by me) .. module Main where dog :: Int -> Int dog a b = a + b main = do x <- return $ dog 2 3 print x Main.hs:5:0: The equation(s) for `dog' have two arguments, but its type `Int -> Int' has only one What am I missing? .. Apparently something fundamental about type definitions .. Any help appreciated. Tom

Tom Poliquin wrote:
add :: (b -> Int) -> (b -> Int) -> (b -> Int) add f g b = f b + g b
The program compiles and runs and produces '19' !
For fun I loaded into ghci and got what I believe is the proper type ..
*Main> :t add add :: (b -> Int) -> (b -> Int) -> b -> Int
When I try the same thing with something simpler (leaving a bit off the type definition) I get the expected error (by me) ..
In type expressions, the symbol -> is right-associative. So ... -> (b -> Int) is exactly the same as ... -> b -> Int -Yitz

On 27 Jan 2009, at 18:42, Tom Poliquin wrote:
I was reading "Arrows and Computation"
http://www.soi.city.ac.uk/~ross/papers/fop.ps.gz
(trying to lose my 'beginner' status) when I saw (on page one)
add :: (b -> Int) -> (b -> Int) -> (b -> Int) add f g b = f b + g b
It seemed like the type definition was wrong (short at least).
I tried it anyway ..
module Main where add :: (b -> Int) -> (b -> Int) -> (b -> Int) add f g b = f b + g b main = do x <- return $ add (+2) (+3) 7 print x
The program compiles and runs and produces '19' !
For fun I loaded into ghci and got what I believe is the proper type ..
*Main> :t add add :: (b -> Int) -> (b -> Int) -> b -> Int
When I try the same thing with something simpler (leaving a bit off the type definition) I get the expected error (by me) ..
module Main where dog :: Int -> Int dog a b = a + b
main = do x <- return $ dog 2 3 print x
Main.hs:5:0: The equation(s) for `dog' have two arguments, but its type `Int -> Int' has only one
What am I missing? .. Apparently something fundamental about type definitions ..
What you're observing is "currying" at work When in Haskell we write the type a -> b, we mean "a function, which accepts items of type 'a', and returns items of type 'b'". Importantly, the -> type operator is right associative. Now, when we say a -> b -> c, right associativity of -> means that this *really* is a -> (b -> c), so, our function takes a single argument, of type a, and produces a new function, which accepts a single argument of type b, and produces something of type c. We can see this at work, lets define this function: f = (+ 1) plus gets applied to a single argument, and returns a new function. We can investigate the type of the new function 'f', and discover that it's a => a -> a – it takes a single numeric argument, and returns something of the same type. Now lets go back and look at your examples: You expected the type of add to be (b -> Int) -> (b -> Int) -> b -> Int, but instead saw the type signature (b -> Int) -> (b -> Int) -> (b -> Int). *but*, thanks to right associativity, those two types are equal! The only reason it's written with parentheses is that the author is trying to draw your eye to the fact that it's a "function transformer" – it takes two functions, and produces a new function based on them. Your dog function gives you an error, because indeed, it takes one argument (a), and returns a new function, which accepts another argument (b), and returns a + b. Thus, it's type signature is Int -> (Int -> Int), which can be written without parentheses as Int -> Int -
Int.
Hope that helps Bob

The trick is this: add :: (b -> Int) -> (b -> Int) -> (b -> Int) is equal to add :: (b -> Int) -> (b -> Int) -> b -> Int This is because the function arrow is right-associative. Reading the function type in the latter way, you can then look at add f g b = f b + g b in a new way. f has type (b -> Int), g also has this type. The b has type b and the function result is an Int. Intuitively you can look at this function in two ways, as a function that takes two functions as arguments and then returns a function, or as a function that takes two functions and a value, and then returns a value. (You can take one more step and see it as a function that takes one argument (of type b -> Int) and then returns a function of type (b -> Int) -> b -> Int.) Similarly the function can be defined as: add f g = \b -> f b + g b which is a more direct implementation of the first type you gave. It's all equivalent though. It's actually pretty cool when you get used to it. Paul Tom Poliquin wrote:
I was reading "Arrows and Computation"
http://www.soi.city.ac.uk/~ross/papers/fop.ps.gz
(trying to lose my 'beginner' status) when I saw (on page one)
add :: (b -> Int) -> (b -> Int) -> (b -> Int) add f g b = f b + g b
It seemed like the type definition was wrong (short at least).
I tried it anyway ..
module Main where add :: (b -> Int) -> (b -> Int) -> (b -> Int) add f g b = f b + g b main = do x <- return $ add (+2) (+3) 7 print x
The program compiles and runs and produces '19' !
For fun I loaded into ghci and got what I believe is the proper type ..
*Main> :t add add :: (b -> Int) -> (b -> Int) -> b -> Int
When I try the same thing with something simpler (leaving a bit off the type definition) I get the expected error (by me) ..
module Main where dog :: Int -> Int dog a b = a + b
main = do x <- return $ dog 2 3 print x
Main.hs:5:0: The equation(s) for `dog' have two arguments, but its type `Int -> Int' has only one
What am I missing? .. Apparently something fundamental about type definitions ..
Any help appreciated.
Tom
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Tue, Jan 27, 2009 at 09:42:54AM -0800, Tom Poliquin wrote:
I was reading "Arrows and Computation"
http://www.soi.city.ac.uk/~ross/papers/fop.ps.gz
(trying to lose my 'beginner' status) when I saw (on page one)
add :: (b -> Int) -> (b -> Int) -> (b -> Int) add f g b = f b + g b
It seemed like the type definition was wrong (short at least).
Hi Tom, that's a great paper to read! I think your confusion seems to stem from this simple fact: every function in Haskell only takes one argument. Functions that look like they take multiple arguments, for example add :: Int -> Int -> Int add x y = x + y are really one-argument functions which return functions. In the above example, 'add' is a function which takes a single Int, and returns a function as output. This output function also takes a single Int and finally returns an Int. Observe: Prelude> let add x y = (x + y :: Int) Prelude> :t add add :: Int -> Int -> Int Prelude> :t add 3 add 3 :: Int -> Int Prelude> :t (add 3) 5 (add 3) 5 :: Int Prelude> (add 3) 5 8 Prelude> add 3 5 8 So we could also write the type of 'add' like this: add :: Int -> (Int -> Int) and in fact, this add's real type. Int -> Int -> Int is just an abbreviation; -> associates to the right, so we can omit parentheses that occur at the rightmost end of a type. As you can see above, by the same token, function application associates to the left, so 'add 3 5' is really just an abbreviation for '(add 3) 5': ie., first apply 'add' to 3, obtaining another function as output, then apply that function to 5. By now I'm sure you can see that (b -> Int) -> (b -> Int) -> (b -> Int) is exactly the same type as (b -> Int) -> (b -> Int) -> b -> Int. You can think of something of this type *either* as something which takes two arguments of type (b -> Int) and returns a function of type (b -> Int); *or* as something which takes three arguments, two of type (b -> Int) and one of type b, and returns something of type Int; these are in fact just two different ways to think about the same thing. Hope that is helpful! -Brent

On Tue, Jan 27, 2009 at 09:42:54AM -0800, Tom Poliquin wrote:
I was reading "Arrows and Computation"
http://www.soi.city.ac.uk/~ross/papers/fop.ps.gz
(trying to lose my 'beginner' status) when I saw (on page one)
add :: (b -> Int) -> (b -> Int) -> (b -> Int) add f g b = f b + g b
It seemed like the type definition was wrong (short at least).
.....
The trick is this: add :: (b -> Int) -> (b -> Int) -> (b -> Int) is equal to add :: (b -> Int) -> (b -> Int) -> b -> Int
Wow! .. Thanks everyone for the fast and informative responses. I get it now. I'm an old time imperative (C, Java, etc) programmer and I find Haskell incredibly powerful ... and fun! Now I can move on to page two in "Arrows and Computation" .. Thanks again .. Tom On Tuesday 27 January 2009 10:39, Brent Yorgey wrote:
On Tue, Jan 27, 2009 at 09:42:54AM -0800, Tom Poliquin wrote:
I was reading "Arrows and Computation"
http://www.soi.city.ac.uk/~ross/papers/fop.ps.gz
(trying to lose my 'beginner' status) when I saw (on page one)
add :: (b -> Int) -> (b -> Int) -> (b -> Int) add f g b = f b + g b
It seemed like the type definition was wrong (short at least).
Hi Tom, that's a great paper to read! I think your confusion seems to stem from this simple fact: every function in Haskell only takes one argument.
Functions that look like they take multiple arguments, for example
add :: Int -> Int -> Int add x y = x + y
are really one-argument functions which return functions. In the above example, 'add' is a function which takes a single Int, and returns a function as output. This output function also takes a single Int and finally returns an Int. Observe:
Prelude> let add x y = (x + y :: Int) Prelude> :t add add :: Int -> Int -> Int Prelude> :t add 3 add 3 :: Int -> Int Prelude> :t (add 3) 5 (add 3) 5 :: Int Prelude> (add 3) 5 8 Prelude> add 3 5 8
So we could also write the type of 'add' like this:
add :: Int -> (Int -> Int)
and in fact, this add's real type. Int -> Int -> Int is just an abbreviation; -> associates to the right, so we can omit parentheses that occur at the rightmost end of a type. As you can see above, by the same token, function application associates to the left, so 'add 3 5' is really just an abbreviation for '(add 3) 5': ie., first apply 'add' to 3, obtaining another function as output, then apply that function to 5.
By now I'm sure you can see that
(b -> Int) -> (b -> Int) -> (b -> Int)
is exactly the same type as
(b -> Int) -> (b -> Int) -> b -> Int.
You can think of something of this type *either* as something which takes two arguments of type (b -> Int) and returns a function of type (b -> Int); *or* as something which takes three arguments, two of type (b -> Int) and one of type b, and returns something of type Int; these are in fact just two different ways to think about the same thing.
Hope that is helpful! -Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Tue, Jan 27, 2009 at 10:47:40AM -0800, Tom Poliquin wrote:
On Tue, Jan 27, 2009 at 09:42:54AM -0800, Tom Poliquin wrote:
I was reading "Arrows and Computation"
http://www.soi.city.ac.uk/~ross/papers/fop.ps.gz
(trying to lose my 'beginner' status) when I saw (on page one)
add :: (b -> Int) -> (b -> Int) -> (b -> Int) add f g b = f b + g b
It seemed like the type definition was wrong (short at least).
.....
The trick is this: add :: (b -> Int) -> (b -> Int) -> (b -> Int) is equal to add :: (b -> Int) -> (b -> Int) -> b -> Int
Wow! .. Thanks everyone for the fast and informative responses.
I get it now.
I'm an old time imperative (C, Java, etc) programmer and I find Haskell incredibly powerful ... and fun!
Now I can move on to page two in "Arrows and Computation" ..
Thanks again ..
Tom
Great! Have fun. I can guarantee you'll have more questions, so feel free to ask more on this list, or for quick questions there's also the #haskell IRC channel on freenode.net, which is another great place to learn and ask questions. -Brent
participants (5)
-
Brent Yorgey
-
Paul Visschers
-
Thomas Davie
-
Tom Poliquin
-
Yitzchak Gale