GHC 6.10.1 type puzzler

Dave Bayer bayer at cpw.math.columbia.edu
Wed Nov 19 11:40:39 EST 2008


Here is an example illustrating a type problem I've having with GHC  
6.10.1:

> module Main where
>
> newtype Box a = B a
>
> make :: a -> Box a
> make x = B x
>
> val :: Box a -> a
> val (B x) = x
>
> test1 :: Box a -> a -> [a]
> test1 box x = go box x
>  where
>    go :: Box a -> a -> [a]
>    go b y = [(val b), y]
>
> test2 :: Box a -> a -> [a]
> test2 box x = go x
>  where
> --  go :: a -> [a]
>    go y = [(val box), y]
>
> main :: IO ()
> main = do
>  print $ test1 (make 1) 2

If I uncomment the commented type declaration, I get the familiar error

> Couldn't match expected type `a1' against inferred type `a'

On the other hand, the earlier code is identical except that it passes  
an extra argument, and GHC matches the types without complaint.

This is a toy example to isolate the issue; in the actual code one  
wants a machine-checkable type declaration to help understand the  
function, which is local to save passing an argument. To the best of  
my understanding, I've given the correct type, but GHC won't make the  
inference to unify the type variables.

I wonder if I found a GHC blind spot. However, it is far more likely  
that my understanding is faulty here. Any thoughts?

Thanks,
Dave
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20081119/e4e56af8/attachment.htm


More information about the Glasgow-haskell-users mailing list