confusing type signature with sections

I wrote code to shift and scale the range [-1, 1] to [0, 1] and mapped it on a list. Prelude> map (\n -> ((n + 1) / 2)) [-1, 0, 1] [0.0,0.5,1.0] I thought using sections would better express the simplicity of this operation. Prelude> :t (+ 1) (+ 1) :: Num a => a -> a Prelude> :t (/ 2) (/ 2) :: Fractional a => a -> a Given the types of those sections, I thought it sensible for me to compose them like this. Prelude> :t ((+ 1) / 2) ((+ 1) / 2) :: (Fractional (a -> a), Num a) => a -> a This didn't work of course, and its type baffles me. Though it ends with "Num a) => a -> a", it gives an error when given a number. I don't understand what "(Fractional (a -> a), ...) =>" really means. It seems like I've asked Haskell to perform "/" on the arguments "(+ 1)" and "2", but that ought to be disallowed by the type of "/". I eventually realized I should use the composition operator (below), but I'm still curious what I created with "((+ 1) / 2)". Prelude> :t (/ 2) . (+ 1) (/ 2) . (+ 1) :: Fractional c => c -> c Thanks! Patrick

Patrick Redmond
I wrote code to shift and scale the range [-1, 1] to [0, 1] and mapped it on a list.
Prelude> map (\n -> ((n + 1) / 2)) [-1, 0, 1] [0.0,0.5,1.0]
I thought using sections would better express the simplicity of this operation.
Prelude> :t (+ 1) (+ 1) :: Num a => a -> a
Prelude> :t (/ 2) (/ 2) :: Fractional a => a -> a
Given the types of those sections, I thought it sensible for me to compose them like this.
Prelude> :t ((+ 1) / 2) ((+ 1) / 2) :: (Fractional (a -> a), Num a) => a -> a
This didn't work of course, and its type baffles me. Though it ends with "Num a) => a -> a", it gives an error when given a number. I don't understand what "(Fractional (a -> a), ...) =>" really means. It seems like I've asked Haskell to perform "/" on the arguments "(+ 1)" and "2", but that ought to be disallowed by the type of "/".
Well, what is the type of (/) ? Prelude> :t (/) (/) :: Fractional a => a -> a -> a By writing ((+ 1) / 2), you are indeed dividing (+ 1) by 2. You can divide any two things of some type a, as long as that type is a fractional type. Here your two things are (+ 1), which is of type (Num a) => a -> a, and 2, which is of type (Num a') => a'. (Here I've added prime symbols to distinguish between the type variables in the two type signatures, as they are not necessarily the same when you put the two expressions together into the same context.) Now, because we are writing ((+ 1) / 2) and we know that (/) takes two arguments that must be of the same type, we know that the type (Num a') => a' -> a' and the type (Num a'') => a'' have to be the same type, so it must be that a' = a -> a, so now we have: (+ 1) :: (Num a, Num (a -> a)) => a -> a 2 :: (Num a, Num (a -> a)) => a -> a Furthermore, since (/) not only takes two arguments that are of the same type but also requires that this type must be Fractional, we actually have (+ 1) :: (Num a, Num (a -> a), Fractional (a -> a)) => a -> a 2 :: (Num a, Num (a -> a), Fractional (a -> a)) => a -> a But the Fractional typeclass actually is a subset of the Num typeclass (that is, a type must be a Num type before it can be a Fractional type). So the first "Num (a -> a)" is redundant. Thus we finally get (+ 1) :: (Num a, Fractional (a -> a)) => a -> a 2 :: (Num a, Fractional (a -> a)) => a -> a (/) :: (Num a, Fractional (a -> a)) => (a -> a) -> (a -> a) -> a -> a ((+ 1) / 2) :: (Num a, Fractional (a -> a)) => a -> a Hopefully that makes more sense. -Keshav

On Tue, Oct 1, 2013 at 5:25 PM, Patrick Redmond
Prelude> :t ((+ 1) / 2) ((+ 1) / 2) :: (Fractional (a -> a), Num a) => a -> a
The key is that typeclasses are open. You could write a Fractional instance for (a -> a), in which case it would be possible to do _something_ with this code. Would it be useful? Even Haskell can't guarantee that. -Karl

Thank you both!
The key is that typeclasses are open. You could write a Fractional instance for (a -> a), in which case it would be possible to do _something_ with this code. Would it be useful? Even Haskell can't guarantee that.
Yes, this is important! Thanks.
Now, because we are writing ((+ 1) / 2) and we know that (/) takes two arguments that must be of the same type, we know that the type (Num a') => a' -> a' and the type (Num a'') => a'' have to be the same type, so it must be that a' = a -> a, so now we have:
(+ 1) :: (Num a, Num (a -> a)) => a -> a 2 :: (Num a, Num (a -> a)) => a -> a
I'm still a little confused here. How can passing "2" into "(+ 1) /" cause its type to be mangled? "2" has a type "(Num a) => a". How can the presence of "(+ 1)" force the type of "2" to suddenly accept an argument? How come it doesn't happen the other way around? (Meaning "2" forces the type of "(+ 1)" to become simply "(Num a) => a".) Prelude> :t 2 / (+ 1) 2 / (+ 1) :: (Fractional (a -> a), Num a) => a -> a Thank you, Patrick

Patrick Redmond
Thank you both!
The key is that typeclasses are open. You could write a Fractional instance for (a -> a), in which case it would be possible to do _something_ with this code. Would it be useful? Even Haskell can't guarantee that.
Yes, this is important! Thanks.
Now, because we are writing ((+ 1) / 2) and we know that (/) takes two arguments that must be of the same type, we know that the type (Num a') => a' -> a' and the type (Num a'') => a'' have to be the same type, so it must be that a' = a -> a, so now we have:
(+ 1) :: (Num a, Num (a -> a)) => a -> a 2 :: (Num a, Num (a -> a)) => a -> a
I'm still a little confused here. How can passing "2" into "(+ 1) /" cause its type to be mangled? "2" has a type "(Num a) => a". How can the presence of "(+ 1)" force the type of "2" to suddenly accept an argument? How come it doesn't happen the other way around? (Meaning "2" forces the type of "(+ 1)" to become simply "(Num a) => a".)
Remember that in type signatures, "a" represents *any* type. And one example of a type that "a" can be is "b -> c", i.e. a function. The type isn't being mangled, it's being refined -- more information is being added. The type "a" doesn't say anything about arguments -- a value of type "a" might be a function, or it might not be. A value of type "a -> a" is definitely a function, so something has been learned about the type. And you can't go the other way (making (+ 1) go from type "a -> a" to just type "a") because that's throwing away information. -Keshav
participants (3)
-
Karl Voelker
-
Keshav Kini
-
Patrick Redmond