[Haskell-beginners] Function Type Confusion ..

Thomas Davie tom.davie at gmail.com
Tue Jan 27 13:32:04 EST 2009


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






More information about the Beginners mailing list