Type Inference Infelicity

Simon Peyton-Jones simonpj@microsoft.com
Tue, 8 Apr 2003 14:07:29 +0100


Interesting example, right on the borderline.   I've jiggled the type
inference for applications a bit so that it works (HEAD only of course).
Thanks for the test case.

Simon

|  -----Original Message-----
|  From: Ashley Yakeley [mailto:ashley@semantic.org]
|  Sent: 19 March 2003 09:43
|  To: glasgow-haskell-users@haskell.org
| =20
|  This should compile, shouldn't it?
| =20
|  -- ghc -c -fglasgow-exts TestInfer.hs
|  module TestInfer where
|      {
|      class C t a b | t a -> b;
|      instance C Char a Bool;
| =20
|      data P t a =3D forall b. (C t a b) =3D> MkP b;
| =20
|      data Q t =3D MkQ (forall a. P t a);
| =20
|      f' :: Q Char;
|      f' =3D MkQ (MkP True :: forall a. P Char a);
| =20
|      f :: Q Char;
|      f =3D MkQ (MkP True);
|      }
| =20
|  GHC 5.04.2 for MacOS X complains about f, but not about f':
| =20
|  TestInfer.hs:15:
|      Could not deduce (C t a Bool) from the context ()
|      Probable fix:
|          Add (C t a Bool) to the When generalising the type of an
|  expression
|          Or add an instance declaration for (C t a Bool)
|      arising from use of `MkP' at TestInfer.hs:15
|      In the first argument of `MkQ', namely `(MkP True)'
|      In the definition of `f': MkQ (MkP True)
| =20
|  --
|  Ashley Yakeley, Seattle WA
| =20
|  _______________________________________________
|  Glasgow-haskell-users mailing list
|  Glasgow-haskell-users@haskell.org
|  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users