ANNOUNCE: GHC 6.6 Release Candidate

Simon Peyton-Jones simonpj at microsoft.com
Mon Sep 18 19:35:01 EDT 2006


Excellent example.  It's very hard to give good error messages for
impredicative polymorphism.  I've tried to improve this one a bit.
(Test is tcfail165.hs)

Simon

| -----Original Message-----
| From: glasgow-haskell-users-bounces at haskell.org
[mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Tomasz Zielonka
| Sent: 01 September 2006 19:55
| To: Simon Marlow
| Cc: glasgow-haskell-users at haskell.org
| Subject: Re: ANNOUNCE: GHC 6.6 Release Candidate
| 
| On Fri, Sep 01, 2006 at 11:03:09AM +0100, Simon Marlow wrote:
| > Please test as much as possible, bugs are much cheaper if we find
them
| > before the release!
| 
| I was playing with impredicativity, when I got this strange error
| message:
| 
|     Prelude> :l Imp
|     [1 of 1] Compiling Imp              ( Imp.hs, interpreted )
| 
|     Imp.hs:15:17:
|         Couldn't match expected type `forall a. (Show a) => a ->
String'
|                against inferred type `a -> String'
|           Expected type: forall a1. (Show a1) => a1 -> String
|           Inferred type: forall a1. (Show a1) => a1 -> String
|         In the second argument of `putMVar', namely
|             `(show :: forall a. (Show a) => a -> String)'
|         In the expression:
|             putMVar var (show :: forall a. (Show a) => a -> String)
|     Failed, modules loaded: none.
| 
| I am still trying to understand this extension, so my code probably
| makes not much sense, but it's alarming that the compiler cannot unify
| two types that are even equal. Maybe the bug is in the error message?
| 
| Here is the code:
| 
|     module Imp where
| 
|     import Control.Concurrent
| 
|     main = do
|         var <- newEmptyMVar :: IO (MVar (forall a. Show a => a ->
String))
|         let thread x = do
|                 forkIO $ sequence_ $ repeat $ do
|                     f <- takeMVar var
|                     putStrLn (f x)
|                     threadDelay 100000
|         thread (1 :: Integer)
|         thread "abcdef"
|         putMVar var (show :: forall a. Show a => a -> String)
|         threadDelay 10000000
| 
| I am using ghc-6.5.20060831 with -fglasgow-exts
| 
| Best regards
| Tomasz
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


More information about the Glasgow-haskell-users mailing list