Extending the idea of a general Num to other types?

I like the fact that Haskel treats numbers in a generic way, so you can lift them to any other datatype by instantiating Num. Can the same be done on other builtin constructs? For example, if I have [a], can this list be lifted to other types? I guess not, because no type class exists for the list type? Does this make sense? I'm still searching for correct terminology... Thanks, Peter

2007/9/2, Peter Verswyvelen
Can the same be done on other builtin constructs? For example, if I have [a], can this list be lifted to other types? I guess not, because no type class exists for the list type?
You can indeed already do that, except it won't be a single instance since list have a bucketful of interesting properties. A good starting is looking at what list is an instance of and trying to identify the set of instance which interest us in this case, Foldable and Functor are probably a good start, embodying most of the interesting way to access a data structure as a list (head and tail don't really make sense for most of the alternatives, except other "sequence" library which currently provide this functionality in an ad-hoc way, see Sequence and ByteString for example of that). An alternative is Traversable. -- Jedaï

Chaddaï Fouché wrote:
You can indeed already do that, except it won't be a single instance since list have a bucketful of interesting properties. A good starting is looking at what list is an instance of and trying to identify the set of instance which interest us in this case, Foldable and Functor are probably a good start, embodying most of the interesting way to access a data structure as a list (head and tail don't really make sense for most of the alternatives, except other "sequence" library which currently provide this functionality in an ad-hoc way, see Sequence and ByteString for example of that). An alternative is Traversable. Thanks!
But before digging into this, maybe I should rephrase myself by giving a more specific (although useless) example of what I mean. When I write: data Foo = Foo Int Int deriving (Show,Eq) instance Num Foo where fromInteger x = Foo x' x' where x' = fromInteger x _ + _ = error "Not relevant for example" _ * _ = error "Not relevant for example" abs _ = error "Not relevant for example" signum _ = error "Not relevant for example" x = 42::Foo I don't have to apply the Foo data constructor to lift the number 42 because I guess the compiler has builtin support for calling fromInteger (or fromRational). I even don't have to add the type annotation most of the time when the compiler can infer the type needed, which is very cool, sometimes a bit annoying. However, now I try the same for lists data Bar = Bar [Int] [Int] -- A List type class does not exist, so this cannot work instance List Bar where fromList x = Bar x x -- This does not work y = [1..10]::Bar So the only way to do this, is to create a constructor function like bar x = Bar x x which means the usage of lists in Haskell is not as general as numbers, in the sense one cannot take advantage of the builtin syntactic sugar of lists like [x,y,z] := x : (y : (z : [])) So if I would like to use this compact notation for e.g. creating a Set datatype, I would have to create special constructor functions (fromList or mkSet or whatever) Is this correct? If so, I'm sure a good reason must exist for this :) Thanks, Peter

You're right. The list syntax is only for lists in Haskell. It would be
nice if the list syntax was overloaded too.
You can overload numeric literals (by defining fromInteger) and string
literals (by defining fromString, in 6.7).
BTW, the [1..10] syntax is overloaded, you need an Enum instance.
-- Lennart
On 9/2/07, Peter Verswyvelen
Chaddaï Fouché wrote:
You can indeed already do that, except it won't be a single instance since list have a bucketful of interesting properties. A good starting is looking at what list is an instance of and trying to identify the set of instance which interest us in this case, Foldable and Functor are probably a good start, embodying most of the interesting way to access a data structure as a list (head and tail don't really make sense for most of the alternatives, except other "sequence" library which currently provide this functionality in an ad-hoc way, see Sequence and ByteString for example of that). An alternative is Traversable. Thanks!
But before digging into this, maybe I should rephrase myself by giving a more specific (although useless) example of what I mean.
When I write:
data Foo = Foo Int Int deriving (Show,Eq)
instance Num Foo where fromInteger x = Foo x' x' where x' = fromInteger x _ + _ = error "Not relevant for example" _ * _ = error "Not relevant for example" abs _ = error "Not relevant for example" signum _ = error "Not relevant for example"
x = 42::Foo
I don't have to apply the Foo data constructor to lift the number 42 because I guess the compiler has builtin support for calling fromInteger (or fromRational). I even don't have to add the type annotation most of the time when the compiler can infer the type needed, which is very cool, sometimes a bit annoying.
However, now I try the same for lists
data Bar = Bar [Int] [Int]
-- A List type class does not exist, so this cannot work instance List Bar where fromList x = Bar x x
-- This does not work y = [1..10]::Bar
So the only way to do this, is to create a constructor function like
bar x = Bar x x
which means the usage of lists in Haskell is not as general as numbers, in the sense one cannot take advantage of the builtin syntactic sugar of lists like
[x,y,z] := x : (y : (z : []))
So if I would like to use this compact notation for e.g. creating a Set datatype, I would have to create special constructor functions (fromList or mkSet or whatever)
Is this correct? If so, I'm sure a good reason must exist for this :)
Thanks, Peter
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Snif, this is sad... :-( Oh well, maybe this gets improved in Haskell Prime ;-) Lennart Augustsson wrote:
You're right. The list syntax is only for lists in Haskell. It would be nice if the list syntax was overloaded too. You can overload numeric literals (by defining fromInteger) and string literals (by defining fromString, in 6.7). BTW, the [1..10] syntax is overloaded, you need an Enum instance.

On Sun, 2 Sep 2007, Lennart Augustsson wrote:
You're right. The list syntax is only for lists in Haskell. It would be nice if the list syntax was overloaded too.
The special list syntax isn't as good, as always proposed. I have collected some advantages of the bare infix notation: http://www.haskell.org/haskellwiki/List_notation

Okay. Now the following might not make sense at all, but... isn't the abstract concept of a list just a sequence of elements (okay, with a whole lot of extra properties)? So couldn't we write: do { 1;2;3;4 } instead of [1,2,3,4] somehow for some special "list builder" monad? And then do {1;2;3;4 } could be lifted to any kind of structure when you run it through a different builder. Ah, I guess not... I'm not familiar enough with monads. Henning Thielemann wrote:
On Sun, 2 Sep 2007, Lennart Augustsson wrote:
You're right. The list syntax is only for lists in Haskell. It would be nice if the list syntax was overloaded too.
The special list syntax isn't as good, as always proposed. I have collected some advantages of the bare infix notation: http://www.haskell.org/haskellwiki/List_notation

On Mon, 3 Sep 2007, Peter Verswyvelen wrote:
Okay. Now the following might not make sense at all, but... isn't the abstract concept of a list just a sequence of elements (okay, with a whole lot of extra properties)? So couldn't we write: do { 1;2;3;4 } instead of [1,2,3,4] somehow for some special "list builder" monad? And then do {1;2;3;4 } could be lifted to any kind of structure when you run it through a different builder. Ah, I guess not... I'm not familiar enough with monads.
Why not just FancySequence.fromList [1,2,3,4] or FancySequence.fromList $ 1:2:3:4:[] ?

Why not just FancySequence.fromList [1,2,3,4] or FancySequence.fromList $ 1:2:3:4:[] ? Yes of course, but the same could be said for numbers, e.g when you need an Int, you have to type (Int.fromNumber 1), (Float.fromNumber 1), (Double.fromNumber 1), etc... I don't like that because it makes writing numeric type independent generic code impossibe, so luckily the Haskell compiler automatically inserts fromInteger or fromRational calls to lift a generic number into a specific representation. But it does not provide
Henning Thielemann wrote: the same for lists, e.g. there is no fromList function which is a member of some List typeclass that the compiler automatically uses just like it does for numbers. I think this is a bit of a discrepancy.

On Tue, 4 Sep 2007, Peter Verswyvelen wrote:
Why not just FancySequence.fromList [1,2,3,4] or FancySequence.fromList $ 1:2:3:4:[] ? Yes of course, but the same could be said for numbers, e.g when you need an Int, you have to type (Int.fromNumber 1), (Float.fromNumber 1), (Double.fromNumber 1), etc... I don't like that because it makes writing numeric type independent generic code impossibe, so luckily the Haskell compiler automatically inserts fromInteger or fromRational calls to lift a generic number into a specific representation. But it does not provide
Henning Thielemann wrote: the same for lists, e.g. there is no fromList function which is a member of some List typeclass that the compiler automatically uses just like it does for numbers. I think this is a bit of a discrepancy.
If you are happy with writing "do {1;2;3;4}" you are certainly also happy with "cv [1,2,3,4]", where cv means 'convert' and is a method of a class for converting between lists and another sequence type. class ListCompatible lc where cv :: [a] -> lc a rt :: lc a -> [a] {- restore :-) -} Better don't adapt the names, but the idea would work, wouldn't it?

Henning Thielemann wrote:
If you are happy with writing "do {1;2;3;4}" you are certainly also happy with "cv [1,2,3,4]", where cv means 'convert' and is a method of a class for converting between lists and another sequence type.
class ListCompatible lc where cv :: [a] -> lc a rt :: lc a -> [a] {- restore :-) -}
Better don't adapt the names, but the idea would work, wouldn't it?
Oh but I will not write "do {1;2;3;4}", this was just an idea :-) Yep, your approach certainly works, but I just found it was a bit of a discrepancy in Haskell (numbers getting better lifting support than lists).

On Tue, 2007-09-04 at 16:06 +0200, Peter Verswyvelen wrote:
Henning Thielemann wrote:
If you are happy with writing "do {1;2;3;4}" you are certainly also happy with "cv [1,2,3,4]", where cv means 'convert' and is a method of a class for converting between lists and another sequence type.
class ListCompatible lc where cv :: [a] -> lc a rt :: lc a -> [a] {- restore :-) -}
Better don't adapt the names, but the idea would work, wouldn't it?
Oh but I will not write "do {1;2;3;4}", this was just an idea :-) Yep, your approach certainly works, but I just found it was a bit of a discrepancy in Haskell (numbers getting better lifting support than lists).
I don't think this has been mentioned explicitly yet, but the discrepancy is purely for pedagogical purposes. In Gofer, list comprehensions (and list syntax, IIRC) /was/ generalized (to an arbitrary instance of MonadPlus). But that means that any mistake in your syntax likely brings up a type error mentioning MonadPlus. This confuses CS freshmen (who are easily confused anyway); thus, Haskell restricts list syntax to lists so the type errors are simpler. By contrast, most CS freshman have already used languages with multiple number types, so all you have to do is explain that type errors involving Num are Haskell's way of dealing with them. So the syntax can be generalized to the type class in that case without confusing freshmen as much. jcc

Jonathan Cast wrote:
I don't think this has been mentioned explicitly yet, but the discrepancy is purely for pedagogical purposes.
In Gofer, list comprehensions (and list syntax, IIRC) /was/ generalized (to an arbitrary instance of MonadPlus). But that means that any mistake in your syntax likely brings up a type error mentioning MonadPlus. This confuses CS freshmen (who are easily confused anyway); thus, Haskell restricts list syntax to lists so the type errors are simpler.
By contrast, most CS freshman have already used languages with multiple number types, so all you have to do is explain that type errors involving Num are Haskell's way of dealing with them. So the syntax can be generalized to the type class in that case without confusing freshmen as much.
jcc
Well, that is a very good reason, but for newbies (or should I say, for me ;-) ), most error messages are very confusing anyway! An since Haskell is really an advanced language, why not go all the way? It feels to me that for learning FP to newbies, a small subset of Haskell would be more suitable to get started, so really easy error messages can be given (Helium does that already?) Otherwise you would need a very clever compiler/editor machine learning system, that looks at how a class of users fixes a certain error, so the compiler can adapt its error message the next time a similar pattern occurs (which is science fiction right now I think...) Now, these complex error messages are not just for Haskell; when I did complicated C++ template programming, the error message sometimes became as long as a full page when printed, and it took me more time to decipher the error than to fix the code ;-) PS: Gofer, is that an existing language? As far as some googling can tell me, it's dead?

On Tue, 2007-09-04 at 23:03 +0200, Peter Verswyvelen wrote:
Jonathan Cast wrote:
I don't think this has been mentioned explicitly yet, but the discrepancy is purely for pedagogical purposes.
In Gofer, list comprehensions (and list syntax, IIRC) /was/ generalized (to an arbitrary instance of MonadPlus). But that means that any mistake in your syntax likely brings up a type error mentioning MonadPlus. This confuses CS freshmen (who are easily confused anyway); thus, Haskell restricts list syntax to lists so the type errors are simpler.
By contrast, most CS freshman have already used languages with multiple number types, so all you have to do is explain that type errors involving Num are Haskell's way of dealing with them. So the syntax can be generalized to the type class in that case without confusing freshmen as much.
jcc
Well, that is a very good reason, but for newbies (or should I say, for me ;-) ), most error messages are very confusing anyway! An since Haskell is really an advanced language, why not go all the way? It feels to me that for learning FP to newbies, a small subset of Haskell would be more suitable to get started, so really easy error messages can be given (Helium does that already?)
Exactly. But the Haskell 98 standard pre-dates Helium. I think Haskell' could be made more complicated now that Helium exists, but don't know whether that's in the cards.
Otherwise you would need a very clever compiler/editor machine learning system, that looks at how a class of users fixes a certain error, so the compiler can adapt its error message the next time a similar pattern occurs (which is science fiction right now I think...)
GHC I think tries to mediate this through the minds of its developers.
Now, these complex error messages are not just for Haskell; when I did complicated C++ template programming, the error message sometimes became as long as a full page when printed, and it took me more time to decipher the error than to fix the code ;-)
PS: Gofer, is that an existing language? As far as some googling can tell me, it's dead?
Right. Gofer died the quick death of most research languages, although it influence Hugs. jcc

On Sep 4, 2007, at 5:03 PM, Peter Verswyvelen wrote:
Otherwise you would need a very clever compiler/editor machine learning system, that looks at how a class of users fixes a certain error, so the compiler can adapt its error message the next time a similar pattern occurs (which is science fiction right now I think...)
On that note, I've been finding GHC's type suggestions often worse than useless, and wish it wouldn't even bother to try -- even more confusing for new users to have the compiler suggest pointless things like declaring an instance of Num String or whatever. I'd prefer it if it could just tell me what *specific* part of an expression, which symbol even, the expected and inferred values differed. On the other hand, when trying to guess at operator precedence rules, the "applied to too many" and "applied to too few" errors are actually pretty handy. --S

| On that note, I've been finding GHC's type suggestions often worse | than useless, and wish it wouldn't even bother to try -- even more | confusing for new users to have the compiler suggest pointless things | like declaring an instance of Num String or whatever. I'd prefer it | if it could just tell me what *specific* part of an expression, which | symbol even, the expected and inferred values differed. On the other | hand, when trying to guess at operator precedence rules, the "applied | to too many" and "applied to too few" errors are actually pretty handy. It's difficult to make error messages helpful. The best improvement mechanism I know is this: when you come across a case where GHC produces an unhelpful message, send it in, along with the program that produced it, AND your suggestion for the error message you'd like to have seen. I don't promise instant action, but if you suffer in silence then nothing will improve. Sending a message keeps it on our radar *and* provides an example to motivate improvements. (Boiling the program down a bit is a help, so you don't have to send a massive tarball.) Another thing that can be worth a try is to try your boiled-down program with Helium, whose error-message infrastructure has received much more conscious design attention than GHC's. Simon

On Wed, 2007-09-05 at 08:19 +0100, Simon Peyton-Jones wrote:
| confusing for new users to have the compiler suggest pointless things | like declaring an instance of Num String or whatever.
This also gets my vote for the "Error-message-most-likely-to-be-unhelpful"-award. IME, this often arises from incorrect use of operators or wrong number of parameters, not missing instances.
It's difficult to make error messages helpful.
Certainly. But better to err on the side of brevity.
when you come across a case where GHC produces an unhelpful message, send it in, along with the program that produced it,
Contents of test/error.hs: f x s = x + show s Error message from GHCi: test/error.hs:2:8: No instance for (Num String) arising from use of `+' at test/error.hs:2:8-17 Possible fix: add an instance declaration for (Num String) In the expression: x + (show s) In the definition of `f': f x s = x + (show s)
your suggestion for the error message you'd like to have seen.
Suggestion: As is, with removal the "Possible fix", as it is often misleading (i.e. here, the programmer clearly meant to use '++' and not '+'. Perhaps rephrase to something like "String is not an instance of Num"? For a newbie, it may not be clear that Num is the class and String is the type. -k

| > when you come across a case where GHC produces an | > unhelpful message, send it in, along with the program | > that produced it, | | Contents of test/error.hs: | f x s = x + show s | | Error message from GHCi: | test/error.hs:2:8: | No instance for (Num String) | arising from use of `+' at test/error.hs:2:8-17 | Possible fix: add an instance declaration for (Num String) | In the expression: x + (show s) | In the definition of `f': f x s = x + (show s) | | > your suggestion for the error message you'd like to have seen. | | Suggestion: | As is, with removal the "Possible fix", as it is often misleading (i.e. | here, the programmer clearly meant to use '++' and not '+'. Is your suggestion specific to String? E.g. if I wrote data Complex = MkC Float Float real :: Float -> Complex real f = MkC f 0 f x s = x + real 1 then I really might have intended to use Complex as a Num type, and the suggestion is precisely on target. I'd be interested to know this particular "helpful suggestion" on GHC's part is more misleading than useful. What do others think? | rephrase to something like "String is not an instance of Num"? For a | newbie, it may not be clear that Num is the class and String is the | type. Good point. Not so easy for multi-parameter type classes! E.g. No instance for (Bar String Int). So we could have String is not an instance of class Foo -- single param No instance for (Bar String Int) -- multi-param Would that be better (single-param case is easier), or worse (inconsistent)? Simon

On Wed, 2007-09-05 at 09:56 +0100, Simon Peyton-Jones wrote:
Is your suggestion specific to String?
No.
then I really might have intended to use Complex as a Num type
IME this is much rarer, and I think if a newbie is told that Complex is not (but needs to be) and instance of Num, it is relatively easy to find the relevant information (Looking up 'instance' and/or 'class' in the index of any Haskell text book should do the trick)
| rephrase to something like "String is not an instance of Num"? For a | newbie, it may not be clear that Num is the class and String is the | type.
Good point. Not so easy for multi-parameter type classes! E.g. No instance for (Bar String Int). So we could have
String is not an instance of class Foo -- single param No instance for (Bar String Int) -- multi-param
If you quote things, you can also consider: 'String Int' is not an instance of class 'Bar'. Downside is that 'String Int' by itself may be confusingly unhaskellish. -k

On Sep 5, 2007, at 6:47 , Ketil Malde wrote:
On Wed, 2007-09-05 at 09:56 +0100, Simon Peyton-Jones wrote:
Good point. Not so easy for multi-parameter type classes! E.g. No instance for (Bar String Int). So we could have
String is not an instance of class Foo -- single param No instance for (Bar String Int) -- multi- param
If you quote things, you can also consider:
'String Int' is not an instance of class 'Bar'.
Downside is that 'String Int' by itself may be confusingly unhaskellish.
I'd phrase it instead as: Class "Num" has no instance for "String" Class "Num" has no instance for "Complex" Class "Bar" has no instance for "String" and "Int" (or maybe ("String","Int") since it's conceptually similar to a tuple, and the formulation above could conceivably be misconstrued as looking for separate instances for String and Int?) -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Ketil Malde wrote:
String is not an instance of class Foo -- single param No instance for (Bar String Int) -- multi-param
If you quote things, you can also consider:
'String Int' is not an instance of class 'Bar'.
Downside is that 'String Int' by itself may be confusingly unhaskellish.
String is not an instance of class Foo String and Int do not form an instance of multi-parameter class Bar ...alternatively, you can put the more mathsy form in brackets after the simple one, to make the generalisation from the single param to the multi-param more clear: String is not an instance of class Foo (No instance for Foo String) No instance for (Bar String Int)

Hello Simon, Wednesday, September 5, 2007, 12:56:18 PM, you wrote:
String is not an instance of class Foo -- single param No instance for (Bar String Int) -- multi-param
Would that be better (single-param case is easier), or worse (inconsistent)?
easier - most classes are one-parameter -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Instead of just adapting the compiler to give better errors, it would really help if a unique identifier was assigned to each error/warning, and if a WIKI and help file existed that describes the errors in detail. Maybe this is already the case, but after a quick search I failed to find such a list of errors. Cheers, Peter Bulat Ziganshin wrote:
Hello Simon,
Wednesday, September 5, 2007, 12:56:18 PM, you wrote:
String is not an instance of class Foo -- single param No instance for (Bar String Int) -- multi-param
Would that be better (single-param case is easier), or worse (inconsistent)?
easier - most classes are one-parameter

I'd prefer something slightly more specific, such as instead of No instance for (Num String) arising from use of `+' at test/error.hs:2:8-17 Possible fix: add an instance declaration for (Num String) In the expression: x + (show s) In the definition of `f': f x s = x + (show s) Maybe (+) is defined as Num a => a -> a -> a The second argument of (+) is of type String at test/ error.hs:2:8-17 String is not an instance of Num In the expression: x + (show s) In the definition of `f': f x s = x + (show s) It seems to me that anybody who gets declaring classes and instance declarations already will be able to figure out pretty quickly what to do if they wanted, e.g., Complex to be an instance of Real with a message like that. The problem is there's too much special-casing otherwise, since its not just Strings but other standard numeric types. For example, if I take "mod $ sqrt n $ m" then I probably don't want to declare an instance of "Floating Int" but just want to use a conversion operator like ceiling. Here's another related thing I ran into below (example simplified): testErr :: Integral a => a -> [a] testErr n = ceiling $ (exp $ sqrt $ log n) ** (1/2) testMe.hs:8:14: Could not deduce (Floating a) from the context (Integral a) arising from use of `**' at testMe.hs:8:14-42 Possible fix: add (Floating a) to the type signature(s) for `testErr' In the second argument of `($)', namely `(exp $ (sqrt $ (log n))) ** (1 / 2)' In the expression: ceiling $ ((exp $ (sqrt $ (log n))) ** (1 / 2)) In the definition of `testErr': testErr n = ceiling $ ((exp $ (sqrt $ (log n))) ** (1 / 2)) What I needed to do here was cast n using realToFrac (or at least I did that and it seemed to be the right decision). But, again, the compiler is suggesting that I declare something that's already an Integral as a Floating, which is conceptually similar to declaring an instance of "Floating Integral" (after all, it implies that such an instance can be/has been declared). Here the possible fix is a great deal more likely to be right, however, so I'm not sure it should be changed, except that a beginner might go and change Integral to Floating when they really *wanted* an Integral for other reasons. The real problem seems to be that the top level expression it returns is pretty huge. If I remove the " ** (1/2)" then I get a message closer to the one I'd like: Could not deduce (Floating a) from the context (Integral a) arising from use of `log' at testMe.hs:8:28-32 Possible fix: add (Floating a) to the type signature(s) for `testErr' In the second argument of `($)', namely `log n' In the second argument of `($)', namely `sqrt $ (log n)' In the second argument of `($)', namely `(exp $ (sqrt $ (log n)))' This seems like something more complicated with how the type- inference system works, and may not be as easily soluble, however. Alternately, it might lead to huge error-stack blowups in more complicated expressions? Again, relatedly, and now I'm *really* digressing, if I don't fix a type signature for testErr but write it so that it needs conflicting types of n then I get (calling the function from main): testErr n = mod n $ ceiling $ (exp $ sqrt $ log n) Ambiguous type variable `a' in the constraints: `Integral a' arising from use of `testErr' at testMe.hs:20:26-35 `RealFrac a' arising from use of `testErr' at testMe.hs:20:26-35 `Floating a' arising from use of `testErr' at testMe.hs:20:26-35 Probable fix: add a type signature that fixes these type variable (s) Again, its probably too much to ask of the type-inference system that it catch this type error in parsing testErr itself. And the error message is pretty helpful because if I set a type signature, then it forces me to figure out the conflict. Still, if it could expand with which elements of testErr caused it to infer each type (if there is no explicit signature, there is), then maybe that could be useful? --S On Sep 5, 2007, at 4:56 AM, Simon Peyton-Jones wrote:
Is your suggestion specific to String? E.g. if I wrote
data Complex = MkC Float Float
real :: Float -> Complex real f = MkC f 0
f x s = x + real 1
then I really might have intended to use Complex as a Num type, and the suggestion is precisely on target. I'd be interested to know this particular "helpful suggestion" on GHC's part is more misleading than useful. What do others think?
| rephrase to something like "String is not an instance of Num"? For a | newbie, it may not be clear that Num is the class and String is the | type.
Good point. Not so easy for multi-parameter type classes! E.g. No instance for (Bar String Int). So we could have
String is not an instance of class Foo -- single param No instance for (Bar String Int) -- multi-param
Would that be better (single-param case is easier), or worse (inconsistent)?
Simon

IMHO error reporting should be done in a hierarchical manner, so that you get a very brief description first, followed by many possible hints for fixing it, and each hint could have subhints etc... Now to make this easy to read, it should be integrated into some IDE of course, otherwise it would scare the hell out of newbies. When the system gets more clever (=AI stuff), it can hide much of the hierarchy, suggesting which hint is appropriate for the specific type of user. After all, depending on your skills, you will create different errors (although the stupid typo will be the most frequent?). Now I'm sure Simon can do the AI part much better than any computer ;-) Cheers, Peter Verswyvelen

On 9/5/07, Ketil Malde
On Wed, 2007-09-05 at 08:19 +0100, Simon Peyton-Jones wrote: Error message from GHCi: test/error.hs:2:8: No instance for (Num String) arising from use of `+' at test/error.hs:2:8-17 Possible fix: add an instance declaration for (Num String) In the expression: x + (show s) In the definition of `f': f x s = x + (show s)
your suggestion for the error message you'd like to have seen.
ghc --newbie-errors error.hs . . . . . . Error message from GHCi: test/error.hs:2:8: You have tried to apply the operator '+' to 'x' and 'show s' 'show s' is a String. I don't know how to apply '+' to a String. May I suggest either: (1) '+' is a method of type class Num. Tell me how to apply '+' to a String by making String an instance of the class Num (2) You didn't really mean '+' In the expression: x + (show s) In the definition of `f': f x s = x + (show s) -- Dan

Dan Piponi wrote:
On 9/5/07, Ketil Malde
wrote: On Wed, 2007-09-05 at 08:19 +0100, Simon Peyton-Jones wrote: Error message from GHCi: test/error.hs:2:8: No instance for (Num String) arising from use of `+' at test/error.hs:2:8-17 Possible fix: add an instance declaration for (Num String) In the expression: x + (show s) In the definition of `f': f x s = x + (show s)
your suggestion for the error message you'd like to have seen.
ghc --newbie-errors error.hs
. . . . . .
Error message from GHCi: test/error.hs:2:8: You have tried to apply the operator '+' to 'x' and 'show s' 'show s' is a String. I don't know how to apply '+' to a String. May I suggest either: (1) '+' is a method of type class Num. Tell me how to apply '+' to a String by making String an instance of the class Num (2) You didn't really mean '+' In the expression: x + (show s) In the definition of `f': f x s = x + (show s)
Splendid! And w/o the --newbie-errors drop the 'Possible fix:...'. In my experience, it is either unnecessary (because it is obvious which instance is missing) or (more often) misleading. As to the first line of the message 'No instance for (Num String)': I dislike the proposed 'String is not an instance of Num' for reasons already mentioned by others (multi parameter classes). I suggest to make it even shorter by directly quoting the missing syntax, i.e. 'Missing (instance Num String)'. Cheers Ben

Dan Piponi wrote:
On 9/5/07, Ketil Malde
wrote: On Wed, 2007-09-05 at 08:19 +0100, Simon Peyton-Jones wrote: Error message from GHCi: test/error.hs:2:8: No instance for (Num String) arising from use of `+' at test/error.hs:2:8-17 Possible fix: add an instance declaration for (Num String) In the expression: x + (show s) In the definition of `f': f x s = x + (show s)
your suggestion for the error message you'd like to have seen.
ghc --newbie-errors error.hs
. . . . . .
Well, most errors I get are what I would list as #1, and I would swap the order of your error and expand them to make this ideal error message with 4 fixes. The result is verbose, but I hope it is a helpful verbosity: Error message from GHCi: test/error.hs:2:8: You have tried to apply the operator "+" to "x" and "show s" "show s" is a String. I don't know how to apply "+" to a String. May I suggest: (1) The inferred type "String" is not what you intended, fix the operand(s) of "+". Adding type annotations may help locate the code to fix. (2) You didn't really mean to type "+", change "+" to the desired name. (3) "+" is a method of type class Num. Add an import for a module which defines an "instance String Num". (4) "+" is a method of type class Num. Tell me how to apply "+" to a String by making String a new instance of the class Num (instance Num String). In the expression: x + (show s) In the definition of `f': f x s = x + (show s) A newbie is unlikely to need the (4)rd suggestion unless they are working on classes and instances in which case they are likely to be able to understand it. I took the other suggestion on this list to also say (instance String Num) to make which instance is missing precise. Everyone not working on classes and instances will probably need a fix suggested by (1) or (2) or (3). The first two fixes are typographical errors of some kind. The (2)nd error is a typographical error in the error triggering code (here "+") that they ought to be able to spot when it is pointed out. I encounter problems caused by (1) fairly often. The user did something (either a logical error or a typo or wrong variable or accidentally shadowed the desired variable, etc) that caused the type inference to find a type which does not (and should not) have an instance of Num. This can be an error anywhere in the lexical scope of the error triggering code. Adding type annotations as assertions helps me move the error closer to the source of the problem, so I added this suggestion. The (3)rd error also trips me up. But it is quickly remedied. -- Chris

Hello Simon, Wednesday, September 5, 2007, 11:19:28 AM, you wrote:
when you come across a case where GHC produces an unhelpful message, send it in, along with the program that produced it,
i have put such tickets about year ago :) basically, it was about just changing wording: instead of "inferred" write: Expected type: ... Actual type: ... http://hackage.haskell.org/trac/ghc/ticket/956 -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Simon,
Wednesday, September 5, 2007, 11:19:28 AM, you wrote:
when you come across a case where GHC produces an unhelpful message, send it in, along with the program that produced it,
i have put such tickets about year ago :) basically, it was about just changing wording: instead of "inferred" write:
Expected type: ... Actual type: ...
This doesn't help enough. What is an 'expected' type? How is it not 'actual'? I want it to be immediatly clear which type is which. Say I write
"x" ++ 'y' Right now the error is Couldn't match expected type `[Char]' against inferred type `Char' In the second argument of `(++)', namely 'y'
What always confuses me is which of these two types is the parameter I gave, and which is the one expected by the function? Changing 'infered' to 'actual' is an improvement, but it is not enough. I would suggest: (++) expects second argument to be of type '[Char]' but was given 'y' of type 'Char' Anothing thing that would be useful is *why* (++) expects a certian type, say I enter
"x" ++ [1::Int] Instead of the above, the following would be more useful:
the function (++) has type: [a] -> [a] -> [a] the first argument suggests: a = Char the second argument suggests: a = Int Twan

On Wed, 2007-09-05 at 19:50 +0200, Twan van Laarhoven wrote:
Bulat Ziganshin wrote:
Hello Simon,
Wednesday, September 5, 2007, 11:19:28 AM, you wrote:
when you come across a case where GHC produces an unhelpful message, send it in, along with the program that produced it,
i have put such tickets about year ago :) basically, it was about just changing wording: instead of "inferred" write:
Expected type: ... Actual type: ...
This doesn't help enough. What is an 'expected' type? How is it not 'actual'? I want it to be immediatly clear which type is which.
Say I write
"x" ++ 'y' Right now the error is Couldn't match expected type `[Char]' against inferred type `Char' In the second argument of `(++)', namely 'y'
What always confuses me is which of these two types is the parameter I gave, and which is the one expected by the function? Changing 'infered' to 'actual' is an improvement, but it is not enough.
I would suggest:
(++) expects second argument to be of type '[Char]' but was given 'y' of type 'Char'
Anothing thing that would be useful is *why* (++) expects a certian type, say I enter
"x" ++ [1::Int] Instead of the above, the following would be more useful:
the function (++) has type: [a] -> [a] -> [a] the first argument suggests: a = Char the second argument suggests: a = Int
Maybe: In the expression "x" ++ 'y': (++) :: [a] -> [a] -> [a] "x" :: String 'y' :: Char (I expect the whole thing to have type String) or In the expression "x" ++ [1]: (++) :: [a] -> [a] -> [a] "x" :: String [1] :: [Int] (I expect the whole thing to have a type similar to [a]) jcc
participants (15)
-
Benjamin Franksen
-
Brandon S. Allbery KF8NH
-
Bulat Ziganshin
-
Chaddaï Fouché
-
ChrisK
-
Dan Piponi
-
Henning Thielemann
-
Jonathan Cast
-
Jules Bean
-
Ketil Malde
-
Lennart Augustsson
-
Peter Verswyvelen
-
Simon Peyton-Jones
-
Sterling Clover
-
Twan van Laarhoven