
Yikes. I have been doing a fair bit of productive programming in Haskell, thinking that I am making a bit of progress. Then I hit something that is apparently *really simple* that I do not understand at all. How discouraging. Here is the code that makes me realize I don't understand types or type inference very well at all yet: f :: a f = 1 When I try to load the above, ghci gives me: No instance for (Num a) arising from the literal `2' In the expression: 2 In an equation for `f': f = 2 Failed, modules loaded: none. Ok, so then I try: g:: (Num a) => a g = 2 This compiles. Why? I mean, why is the first example (defining f) wrong, but the second example (defining g) ok? A slight variation on this is: h:: a h = 'a' to which ghci replies: Couldn't match type `a' with `Char' `a' is a rigid type variable bound by the type signature for c :: a at /Users/David/Project/EoP/ch04/weak.hs:114:1 In the expression: 'a' In an equation for `c': c = 'a' This last example is probably the most basic one which I need to understand. But, why is the problem apparently a different one than in the definition of "f" above? Of course, I cannot think of a reason to actually define things as shown above under ordinary circumstances. The code above is just boiled down to the simplest case I could find to illustrate my confusion. I guess I interpret "f::a" to mean "f is some (any) type a". So why can't it be whatever "1" is, which I suppose is Integer. What is the type system looking for? And why does the constraint (Num a) make things ok? Please point me in the direction of any reading I should do to clear up my confusion. TIA. - Jake -

On Thu, Jul 28, 2011 at 19:42, Jake Penton
h:: a h = 'a'
to which ghci replies:
Couldn't match type `a' with `Char' `a' is a rigid type variable bound by the type signature for c :: a at /Users/David/Project/EoP/ch04/weak.hs:114:1 In the expression: 'a' In an equation for `c': c = 'a'
This last example is probably the most basic one which I need to understand. But, why is the problem apparently a different one than in the definition of "f" above?
The other one was complicated by polymorphism: a numeric literal is compiled into a call to fromIntegral, whose result type is Num a => a. The problem is that, when you say something's type is "a", you are not saying "pick an appropriate type for me"; you are saying "whoever invokes this can ask for any type it wants" (equivalently: "I promise to be able to produce *any possible* type"). But then you give the value as Num a => a in the first example and Char in the second example, neither of which is "any possible type". An explicit type is a complete contract; having contracted to produce an "a" (any type), you can't then offer only a Char or a Num a => a. You have to satisfy the contract which says "any type", otherwise you're doing the type checking equivalent of a bait-and-switch. You can't express "pick a type for me" in a type signature; types are concrete, and a type variable in a signature is a concrete "anything", meaning the caller can request whatever it wants and you must produce it. The type must be *completely* described by the signature; what it says is what you're committed to, and you can't then offer something else. If you need a partial type signature, there are some tricks you can use which let you force types in the implementation without specifying a concrete signature (see http://okmij.org/ftp/Haskell/types.html#partial-sigs). -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On 2011-07-28, at 8:23 PM, Brandon Allbery wrote:
On Thu, Jul 28, 2011 at 19:42, Jake Penton
wrote: h:: a h = 'a' to which ghci replies:
Couldn't match type `a' with `Char' `a' is a rigid type variable bound by the type signature for c :: a at /Users/David/Project/EoP/ch04/weak.hs:114:1 In the expression: 'a' In an equation for `c': c = 'a'
This last example is probably the most basic one which I need to understand. But, why is the problem apparently a different one than in the definition of "f" above?
The other one was complicated by polymorphism: a numeric literal is compiled into a call to fromIntegral, whose result type is Num a => a.
The problem is that, when you say something's type is "a", you are not saying "pick an appropriate type for me"; you are saying "whoever invokes this can ask for any type it wants" (equivalently: "I promise to be able to produce *any possible* type"). But then you give the value as Num a => a in the first example and Char in the second example, neither of which is "any possible type".
An explicit type is a complete contract; having contracted to produce an "a" (any type), you can't then offer only a Char or a Num a => a. You have to satisfy the contract which says "any type", otherwise you're doing the type checking equivalent of a bait-and-switch.
You can't express "pick a type for me" in a type signature; types are concrete, and a type variable in a signature is a concrete "anything", meaning the caller can request whatever it wants and you must produce it. The type must be *completely* described by the signature; what it says is what you're committed to, and you can't then offer something else. If you need a partial type signature, there are some tricks you can use which let you force types in the implementation without specifying a concrete signature (see http://okmij.org/ftp/Haskell/types.html#partial-sigs).
Ok, thanks. I have some studying to do about haskell types, clearly. Does that mean then that there is no definition possible of f other than 'undefined'? I mean this compiles: f::a f = undefined But is there any other possible second line defining f? - Jake -

On Friday 29 July 2011, 03:26:33, Jake Penton wrote:
Ok, thanks. I have some studying to do about haskell types, clearly.
Does that mean then that there is no definition possible of f other than 'undefined'? I mean this compiles:
f::a f = undefined
But is there any other possible second line defining f?
Sure, you can write the same thing in many different ways: f :: a f = f f :: a f = let x = x in x f :: a f = error "Foo" but all definitions of "f :: a" that compile yield (some kind of) bottom, since _|_ is the only value that is common to all types (whether an attempt to evaluate such a value yields actual nontermination or an exception message depends; the first two don't terminate in ghci but result in "<<loop>>" when used in a compiled programme).
- Jake -

On Thu, Jul 28, 2011 at 21:26, Jake Penton
Does that mean then that there is no definition possible of f other than 'undefined'? I mean this compiles:
f::a f = undefined
But is there any other possible second line defining f?
Only more complicated forms of the same thing:
f = error "impossible value" f = let x = x in x -- infinite evaluation
You'll occasionally see discussion of the role of "bottom" in the language; that's what this is. Technically, bottom is the least defined value of a type, and since in standard Haskell all types are "lifted" (their values are computed via thunks of some kind; this is what enables laziness) bottom inhabits every type, and is the only "value" that does so. (Various extensions introduce and make use of unlifted types, which are always strict; as such, they can never really be bottom, as any attempt to use bottom in the context of an unlifted type leads to a runtime error, infinite loop, crash, or other form of nontermination.) -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

Well, thanks everyone. I'm getting there slowly. I have had less success learning Haskell by just using it than any other language I have tackled. I seem to need to cycle regularly between some theoretical study and practical use. Actually, starting in September I shall be taking a grad course on languages. The text is Types and Programming Languages by Pierce. I looked quickly at the book after posting my question, and believe that the course will plug some major gaps in my understanding of types. - Jake -

So, why is it possible to work with the map :: (a -> b) -> [a] -> [b] function? One can use it with list of number and functions on numbers, can't one.

On 2011-07-29, at 6:54 AM, Gary Klindt wrote:
So, why is it possible to work with the map :: (a -> b) -> [a] -> [b] function? One can use it with list of number and functions on numbers, can't one.
Yeah. Your question is pretty much an example of what what troubling me in my original post. And frankly, I doubt that my reasoning on this will get straightened out until I have studied the type system more thoroughly. Naively, the difference I see between your example using map and my original post is that I was *defining* f: f::a f = 1 which, I suppose, is quite a bit different than *calling* map. To parallel my example, one would (mistakenly) write something like this: map::(a -> b) -> [a] -> [b] map f lst = ['a','b','c'] The above gives the same message I got. It is tempting to think that " ['a','b','c'] is a list of b's, so it should work", but that is clearly wrong. - j -

On Fri, 2011-07-29 at 07:27 -0400, Jake Penton wrote:
On 2011-07-29, at 6:54 AM, Gary Klindt wrote:
So, why is it possible to work with the map :: (a -> b) -> [a] -> [b] function? One can use it with list of number and functions on numbers, can't one.
Yeah. Your question is pretty much an example of what what troubling me in my original post. And frankly, I doubt that my reasoning on this will get straightened out until I have studied the type system more thoroughly.
Naively, the difference I see between your example using map and my original post is that I was *defining* f:
f::a f = 1
which, I suppose, is quite a bit different than *calling* map. To parallel my example, one would (mistakenly) write something like this:
map::(a -> b) -> [a] -> [b] map f lst = ['a','b','c']
The above gives the same message I got. It is tempting to think that " ['a','b','c'] is a list of b's, so it should work", but that is clearly wrong.
Maybe it helps to read the type signatures with explicit type abstraction and instantiation. f :: a means f :: forall a. a that is, I can choose any type for a, and f will have that type. Let us make the choice explict: say if I use f in "hello" ++ f, f will be of type String, we can write f_{String} :: String, if I use it in (5 :: Int) + f, it will be an Int, ie. f_{Int} :: Int, and so on. So f must be typable to every type we can instantiate it with. Now consider map. Here the thing different from f is, that type variables occur not only on output positions, but also on input positions of the function, ie. (a -> b) and [a] are at input positions. And the type instantiation of map gets fixed by the inputs. If we apply map to a function g :: Char -> Int, the concrete instantiation of map is already fixed, we have to choose Int for a and Char for b, ie apply map_{Char, Int} :: (Char -> Int) -> [Char] -> [Int] to g. Otherwise the program can't be typed. In particular, that means that map g only takes lists with characters as further argument and returns lists with integers. What happens in your definition above is that you fix b already to [Char] by your fixed output, so the map above can only be typed to map :: forall a. (a -> b) -> [a] -> [Char] Its maybe interesting to think about what functions of polymorphic type can do. map for example is vastly described by its type. The type says it takes an arbitrary function mapping from a to b and a list of elements of type a to return elements of type b. Since map does not "know" what types a and b will be when it is called, it can only apply f to values of type a to generate values of type b (or use undefined). For example map f [] can only return a list with entries undefined, or f undefined. Cheers, Daniel.
- j - _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

The point is that in
f::a
you are saying that f is of an undefined type a. But in
f=1
you're saying that a must be a type that supports the value 1, and not all do (eg strings, booleans).
Therefore you have to tell the compiler that you are constraining a to allow it to take the value 1, hence the constraint Num a, which does just that.
The error message is telling you just this: it can't find a constraint that tells it that a is in the class Num, so it is complaining because what you have written could fail if you used f in a context where it was inferred to have a non numerical type. Constraints allow the type-inference engine to spot such errors, saving you from terrible grief in debugging.
Sent from my iPhone
On 29 Jul 2011, at 00:42, Jake Penton
Yikes.
I have been doing a fair bit of productive programming in Haskell, thinking that I am making a bit of progress. Then I hit something that is apparently *really simple* that I do not understand at all. How discouraging.
Here is the code that makes me realize I don't understand types or type inference very well at all yet:
f :: a f = 1
When I try to load the above, ghci gives me:
No instance for (Num a) arising from the literal `2' In the expression: 2 In an equation for `f': f = 2 Failed, modules loaded: none.
Ok, so then I try:
g:: (Num a) => a g = 2
This compiles.
Why? I mean, why is the first example (defining f) wrong, but the second example (defining g) ok?
A slight variation on this is:
h:: a h = 'a'
to which ghci replies:
Couldn't match type `a' with `Char' `a' is a rigid type variable bound by the type signature for c :: a at /Users/David/Project/EoP/ch04/weak.hs:114:1 In the expression: 'a' In an equation for `c': c = 'a'
This last example is probably the most basic one which I need to understand. But, why is the problem apparently a different one than in the definition of "f" above?
Of course, I cannot think of a reason to actually define things as shown above under ordinary circumstances. The code above is just boiled down to the simplest case I could find to illustrate my confusion.
I guess I interpret "f::a" to mean "f is some (any) type a". So why can't it be whatever "1" is, which I suppose is Integer. What is the type system looking for? And why does the constraint (Num a) make things ok?
Please point me in the direction of any reading I should do to clear up my confusion.
TIA.
- Jake - _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Jul 28, 2011, at 7:42 PM, Jake Penton wrote:
I guess I interpret "f::a" to mean "f is some (any) type a". So why can't it be whatever "1" is, which I suppose is Integer. What is the type system looking for? And why does the constraint (Num a) make things ok?
This right here is the core of your confusion. As you probably know, in all major typed "object-oriented" languages this is true; for example, in Java "Object foo;" means that "foo" is some type extending Object, and "List bar;" means that "bar" is some type satisfying the List interface. But in typed functional languages, the mode of "quantification" has the opposite default. In Haskell, 'f::a' means "FOR EVERY type a, f can be that type". This is universal quantification - just like the upside-down A ("for all") in logic, the type declaration must be true for all values of "a". Sometimes it's important to be clear about which type of quantification you're talking about. When you do, "f :: a" would be written "f :: forall a. a", and what you had in mind would be written "f :: exists a. a". The key difference is that in the "forall" case, the person using 'f' gets to choose its concrete type, but in the "exists" case the concrete type is chosen by the person defining it. When type classes are involved, they just add restrictions to the type. For example, "f :: Num a => a" still has an implied "forall", but the "Num a =>" part means that instead of "for every type a ...", you have "for every type a which implements Num ...". Similarly, "f :: exists a. Num a => a" would mean "for some type a which implements Num ...". So "f :: a; f = 1" doesn't work because it doesn't restrict the type enough. By restricting the type to "Num a => a", gain the ability to use the functions in the Num class, one of which is "fromInteger", which is called implicitly whenever you use a literal integer - that's what makes integer literals polymorphic in Haskell. Similarly, "f = 3.14" would require "f :: Fractional a => a" because "3.14" implicitly calls "fromRational", a function defined in the Fractional type class. -- James PS. Although some Haskell compilers support them as optional language extensions, "forall" and "exists" are not official Haskell syntax - just conventions that humans use to keep things straight when thinking about the types.

On 2011-07-29, at 9:23 AM, James Cook wrote:
On Jul 28, 2011, at 7:42 PM, Jake Penton wrote:
I guess I interpret "f::a" to mean "f is some (any) type a". So why can't it be whatever "1" is, which I suppose is Integer. What is the type system looking for? And why does the constraint (Num a) make things ok?
This right here is the core of your confusion. As you probably know, in all major typed "object-oriented" languages this is true; for example, in Java "Object foo;" means that "foo" is some type extending Object, and "List bar;" means that "bar" is some type satisfying the List interface. But in typed functional languages, the mode of "quantification" has the opposite default. In Haskell, 'f::a' means "FOR EVERY type a, f can be that type".
This is universal quantification - just like the upside-down A ("for all") in logic, the type declaration must be true for all values of "a". Sometimes it's important to be clear about which type of quantification you're talking about. When you do, "f :: a" would be written "f :: forall a. a", and what you had in mind would be written "f :: exists a. a". The key difference is that in the "forall" case, the person using 'f' gets to choose its concrete type, but in the "exists" case the concrete type is chosen by the person defining it.
When type classes are involved, they just add restrictions to the type. For example, "f :: Num a => a" still has an implied "forall", but the "Num a =>" part means that instead of "for every type a ...", you have "for every type a which implements Num ...". Similarly, "f :: exists a. Num a => a" would mean "for some type a which implements Num ...". So "f :: a; f = 1" doesn't work because it doesn't restrict the type enough. By restricting the type to "Num a => a", gain the ability to use the functions in the Num class, one of which is "fromInteger", which is called implicitly whenever you use a literal integer - that's what makes integer literals polymorphic in Haskell. Similarly, "f = 3.14" would require "f :: Fractional a => a" because "3.14" implicitly calls "fromRational", a function defined in the Fractional type class.
-- James
PS. Although some Haskell compilers support them as optional language extensions, "forall" and "exists" are not official Haskell syntax - just conventions that humans use to keep things straight when thinking about the types.
Well, there have been a couple of answers on this thread that suggest that a constraint/context will work. But this does not clear things up entirely for me. I probably do not understand your answer. But adding a constraint by itself does not of itself change things, although perhaps you are not suggesting that it would. For example, this does not compile: f :: Fractional a => a f = 3.14 This does: class Foo a where f :: Fractional a => a instance Foo Float where f = 3.14 So I infer that the reason that my example int the original post compiles is something other than merely the presence of the constraint. This compiles: f :: Num a => a f = 1

On Fri, 2011-07-29 at 09:49 -0400, Jake Penton wrote:
For example, this does not compile:
f :: Fractional a => a f = 3.14
I can load this to ghci and also compile f :: Fractional a => a f = 3.14 main = print f with ghc and call the program to return 3.14. (ghc version 7.01) Cheers, Daniel.

On 2011-07-29, at 10:02 AM, Daniel Seidel wrote:
On Fri, 2011-07-29 at 09:49 -0400, Jake Penton wrote:
For example, this does not compile:
f :: Fractional a => a f = 3.14
I can load this to ghci and also compile
Yeah, sorry - so can I. I must have screwed up earlier. Fat fingers, bleary eyes.... But, getting back to my point (or possibly making an unrelated one for all I know), how about this, which I *hope* I am right in saying does NOT compile, even though Bool is an instance of Ord: g :: Ord a => a g = True It still seems to me that the mere presence of a constraint does not make a difference by itself. Does the difference here lie in compiler calls to fromFractional or fromIntegral in appropriate cases? - J -

Ask yourself this: is True *every* instance of Ord? You are expecting it to be an "any", but it's an "every" (forall). By the way, True happens to be an instance of Ord but it doesn't have to be. You're working backwards here, I think. It happens that useful operations on things in class Ord generally produce Bool; that doesn't mean Bool must be Ord. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On 2011-07-29, at 11:22 AM, Brandon Allbery wrote:
Ask yourself this: is True *every* instance of Ord? You are expecting it to be an "any", but it's an "every" (forall).
By the way, True happens to be an instance of Ord but it doesn't have to be. You're working backwards here, I think. It happens that useful operations on things in class Ord generally produce Bool; that doesn't mean Bool must be Ord.
Right - actually, I did not expect it to compile. I gave the code as, perhaps, a counterexample to what some other responses seemed to be asserting, although it is possible I did not get their point(s) correctly. They seemed to say that adding a constraint is of itself what makes the cases that used numeric literals work. But it seems (as described in Brent Yorgey's post) that there is more to it than that. - J -

It's true but incomplete: the implicit fromIntegral is what enables
the numeric example to produce any numeric type, whike the Num
constraint just announces that fact. The constraint itself is a
contract; fromIntegral is what delivers on the contract.
On 2011-07-29, Jake Penton
On 2011-07-29, at 11:22 AM, Brandon Allbery wrote:
Ask yourself this: is True *every* instance of Ord? You are expecting it to be an "any", but it's an "every" (forall).
By the way, True happens to be an instance of Ord but it doesn't have to be. You're working backwards here, I think. It happens that useful operations on things in class Ord generally produce Bool; that doesn't mean Bool must be Ord.
Right - actually, I did not expect it to compile. I gave the code as, perhaps, a counterexample to what some other responses seemed to be asserting, although it is possible I did not get their point(s) correctly. They seemed to say that adding a constraint is of itself what makes the cases that used numeric literals work. But it seems (as described in Brent Yorgey's post) that there is more to it than that.
- J -
-- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On Friday 29 July 2011, 18:14:30, Jake Penton wrote:
On 2011-07-29, at 11:22 AM, Brandon Allbery wrote:
Ask yourself this: is True *every* instance of Ord? You are expecting it to be an "any", but it's an "every" (forall).
By the way, True happens to be an instance of Ord but it doesn't have to be. You're working backwards here, I think. It happens that useful operations on things in class Ord generally produce Bool; that doesn't mean Bool must be Ord.
Right - actually, I did not expect it to compile. I gave the code as, perhaps, a counterexample to what some other responses seemed to be asserting, although it is possible I did not get their point(s) correctly. They seemed to say that adding a constraint is of itself what makes the cases that used numeric literals work.
Given the fact that per the report a numeric literal is interpreted as a call to fromInteger or fromRational (depending on whether it's an integer literal or a fractional literal), the addition of the constraint is all that is needed to make it work, since by those functions' types, the value represented by a numeric literal is polymorphic. f = 1 is really f = fromInteger 1& (where n& stands for the Integer of the appropriate value, it's not Haskell; in GHC [with integer-gmp], it would be f = fromInteger (S# 1#) where S# is a constructor of Integer [MagicHash extension required to use it] and 1# is a literal of type Int#, raw signed machine int, four or eight bytes of raw memory). True, on the other hand, is a monomorphic value of type Bool, it cannot have any other type than Bool and trying to specify any other type for it leads to a compile time error.
But it seems (as described in Brent Yorgey's post) that there is more to it than that.
The fundamental difference is monomorphic vs. polymorphic expressions. A monomorphic expression like [True] has a specific type, it doesn't make sense to add constraints to it (but it makes sense to ask whether constraints are satisfied for using it). A polymorphic expression like (toEnum 0) can have many types, but in general the types it can have are constrained by the types of subexpressions/used functions. There is a minimal set of constraints you need to specify, e.g. l = [toEnum 0, 3] needs the constraints (Enum a) and (Num a) in the type signature l :: (Num a, Enum a) => [a] but you can use more or more restrictive constraints to specify a less general type than it could have, for example l :: (Enum a, Bounded a, Num a, Read a) => [a] or l :: (Enum a, RealFrac a) => [a] are valid signatures since they are less general/more constrained than the first one. You could also give a monomorphic signature, l :: [Double], which will compile if and only if the specified type of list elements belongs to Num and Enum.

On Fri, Jul 29, 2011 at 11:02:26AM -0400, Jake Penton wrote:
On 2011-07-29, at 10:02 AM, Daniel Seidel wrote:
On Fri, 2011-07-29 at 09:49 -0400, Jake Penton wrote:
For example, this does not compile:
f :: Fractional a => a f = 3.14
I can load this to ghci and also compile
Yeah, sorry - so can I. I must have screwed up earlier. Fat fingers, bleary eyes....
But, getting back to my point (or possibly making an unrelated one for all I know), how about this, which I *hope* I am right in saying does NOT compile, even though Bool is an instance of Ord:
g :: Ord a => a g = True
It still seems to me that the mere presence of a constraint does not make a difference by itself. Does the difference here lie in compiler calls to fromFractional or fromIntegral in appropriate cases?
Yes. The difference is that numeric literals are special -- they are polymorphic. 3 has type (Num a) => a, and 3.14 has type (Fractional a) => a. So, f :: Fractional a => a promises to be able to take on ANY fractional type, and sure enough, 3.14 can be any fractional type. However, g :: Ord a => a promises to be able to take on ANY Ord type, but True has type Bool, which is too specific. I should be able to write (for example) if g < 'x' then ... else ... using g at type Char (since Char is an instance of Ord), but you can easily see that this will not work if g = True. Hence the error. -Brent

On Jul 29, 2011, at 9:49 AM, Jake Penton wrote:
Well, there have been a couple of answers on this thread that suggest that a constraint/context will work. But this does not clear things up entirely for me. I probably do not understand your answer. But adding a constraint by itself does not of itself change things, although perhaps you are not suggesting that it would.
For example, this does not compile:
f :: Fractional a => a f = 3.14
It should. Is there something else in the file you're compiling which somehow conflicts? What error does it print?
This does:
class Foo a where f :: Fractional a => a
instance Foo Float where f = 3.14
So I infer that the reason that my example int the original post compiles is something other than merely the presence of the constraint. This compiles:
f :: Num a => a f = 1
Actually, it is solely the presence of the constraint which makes it OK. By constraining it, you're saying "f can produce a value of any type, so long as that type implements Num" - and by saying that, you get to rely on the compiler enforcing it, so you can use all the functions Num provides. One of those functions is "fromInteger", which the compiler uses in the implementation of "1". When you say "f = 1", the compiler interprets that as "f = fromInteger (1 :: Integer)". Without the constraint, you're not allowed to use "fromInteger" because that function doesn't exist for all types. -- James
participants (8)
-
Brandon Allbery
-
Brent Yorgey
-
Daniel Fischer
-
Daniel Seidel
-
Gary Klindt
-
Jake Penton
-
James Cook
-
Julian Porter