Hi Simon,

I've attached a program which exhibits the error. Here is what I get
when compiling with ghc 6.6:

$ ghc6 --version
The Glorious Glasgow Haskell Compilation System, version 6.6
$ ghc6 bar.hs

bar.hs:7:6:
    Couldn't match expected type `[a]' against inferred type `()'
    In the first argument of `a', namely `y'
    In the expression: a y
    In the definition of `c': c = a y

bar.hs:9:6:
    Couldn't match expected type `Bool -> [a]'
           against inferred type `()'
    In the first argument of `a', namely `()'
    In the expression: a ()
    In the definition of `d': d = a ()

As you can see, in the first example, the conflicting types are not
actually types of the quoted expression. 'y' can have type 'Bool ->
()' or 'Bool -> [a]', but not '()' or '[a]'. In the second example,
since the conflict is more severe, I get a sensible error message.

Strangely enough, under version 6.4.2 of ghc, both error messages are
sensible. In other words, the conflicting types given for line 7 are
the actual conflicting types of 'y', not some child type of those
types as above.

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.4.2
$ ghc bar.hs    

bar.hs:7:6:
    Couldn't match `[a]' against `()'
      Expected type: Bool -> [a]
      Inferred type: Bool -> ()
    In the first argument of `a', namely `y'
    In the definition of `c': c = a y

bar.hs:9:6:
    Expecting a function type, but found `()'
      Expected type: Bool -> [a]
      Inferred type: ()
    In the first argument of `a', namely `()'
    In the definition of `d': d = a ()

So perhaps some recent changes to the ghc type checker have made the
error messages less informative?

Thanks,

Frederik

On Mon, Mar 12, 2007 at 11:40:11AM +0000, Simon Peyton-Jones wrote:
> I kind of see what you are saying, but I'm having trouble with the details.  
> Can you give a standalone program that elicits the unhelpful message?  The 
> easiest way to do this is to say
>         _withInitRSV :: <whatever>
>         _withInitRSV = erorr "urk"
> 
> That gives a nice small program.
> 
> thanks
> 
> Simon
> 
> | -----Original Message-----
> | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On
> | Behalf Of Frederik Eaton
> | Sent: 11 March 2007 20:44
> | To: glasgow-haskell-bugs@haskell.org
> | Subject: question about expected and inferred types in error messages
> |
> | Hello,
> |
> | I hope that this isn't again something which has been fixed recently,
> | I am looking at version 6.6. (is there a newer one in Debian?)
> |
> | I am making an observation about error messages.
> |
> | For example, I recently fixed a bug by changing a line:
> |
> |     (xR, _) <- _withInitRSV Nothing (const ()) xRP
> |
> | to read:
> |
> |     (xR, _) <- _withInitRSV Nothing (const $ return ()) xRP
> |
> | The error message from the compiler was:
> |
> | Stream.hs:106:37:
> |     Couldn't match expected type `IO t' against inferred type `()'
> |     In the second argument of `_withInitRSV', namely `(const ())'
> |     In a 'do' expression:
> |         (xR, _) <- _withInitRSV Nothing (const ()) xRP
> |     In the expression:
> |         do RSVWriter c xRP <- takeMVar wm
> |            wsFinish c
> |            free c
> |            (xR, _) <- _withInitRSV Nothing (const ()) xRP
> |            return xR
> |
> | I am assuming that the "expected type" is the type inferred for the
> | context in which the expression occurs, and the "inferred type" is the
> | type inferred for the expression from the already-accepted judgments
> | of other contexts.
> |
> | The thing which is confusing to me is that the expression which the
> | error message refers to, "(const ())", doesn't have either the type
> | named in the expected type, or the inferred type. Rather the context
> | of that expression expects:
> |
> | something -> IO b
> |
> | while the type inferred from other contexts (e.g. definitions of
> | "const" and "()") for that expression is:
> |
> | anything -> ()
> |
> | Presumably the compiler unifies 'something' with 'anything', proceeds,
> | gets stuck on unifying 'IO b' with '()', and spits out the error
> | message for these subnodes. If I had made a more serious mistake, for
> | instance by changing the line to:
> |
> |     (xR, _) <- _withInitRSV Nothing () xRP
> |
> | then the error message would be more informative:
> |
> | Stream.hs:106:37:
> |     Couldn't match expected type `Ptr (RSV e i) -> IO t'
> |            against inferred type `()'
> |     In the second argument of `_withInitRSV', namely `()'
> |     In a 'do' expression: (xR, _) <- _withInitRSV Nothing (()) xRP
> |     In the expression:
> |         do RSVWriter c xRP <- takeMVar wm
> |            wsFinish c
> |            free c
> |            (xR, _) <- _withInitRSV Nothing () xRP
> |            return xR
> |
> | In this case, the given expression "()" actually has the two
> | alternative typings which are displayed in the message, presumably
> | because here the type incompatibility was at the top node of the type.
> | I think this makes fixing the error much easier, since one doesn't
> | have to guess what the relationship between the expression and the two
> | given types is.
> |
> | I should think that it would be useful if, every time the compiler
> | gave an expression and two alternative typings, those typings were
> | typings of the given expression. Would this be too difficult to
> | implement for the case of the first example, where it was possible to
> | partially unify the function types? Or is there some other reason to
> | avoid making such a change to the compiler?
> |
> | Many thanks,
> |
> | Frederik Eaton
> |
> | --
> | http://ofb.net/~frederik/
> | _______________________________________________
> | Glasgow-haskell-bugs mailing list
> | Glasgow-haskell-bugs@haskell.org
> | http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs
> 

-- 
http://ofb.net/~frederik/
a x = x True ++ [1]

-- ok
b = a (const [2])
-- uninformative error message
c = a y
-- more informative
d = a ()

y = const ()
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to