Maurí­cio wrote:
Hi,

Why isn't the last line of this code allowed?

f :: (TestClass a) => a -> Integer
f = const 1
a = (f,f)
g = fst a

Just to make explicit what other folks have brought up in passing. The real type of @f@ (that is without syntactic sugar) is:

    > f :: forall a. TestClass a => a -> Integer

Which in turn means that the type for @a@ is:

    > a :: ( (forall a. TestClass a => a -> Integer)
    >      , (forall a. TestClass a => a -> Integer) )

This signature isn't valid Haskell98 since it embeds the quantification and the contexts, but it's easily transformable into valid syntax.

    == {alpha conversion}
    > a :: ( (forall a. TestClass a => a -> Integer)
    >      , (forall b. TestClass b => b -> Integer) )
    == {scope extension, twice}
    > a :: forall a b. ( (TestClass a => a -> Integer)
    >                  , (TestClass b => b -> Integer) )
    == {context raising, twice}
    > a :: forall a b. (TestClass a, TestClass b) => ( (a -> Integer)
    >                                                , (b -> Integer) )
    == {invisible quantification sugar (optional)}
    > a :: (TestClass a, TestClass b) => ( (a -> Integer)
    >                                    , (b -> Integer) )

The alpha conversion, necessary before doing scope extension, is the step that might not have been apparent. Because @f@ is polymorphic in its argument, the different instances of @f@ can be polymorphic in different ways. This in turn is what leads to the ambiguity in @g@, monomorphism restriction aside.


If you wanted to have @a@ give the same types to both elements of the tuple, then you can use this expression instead:

    > a' = let f' = f in (f',f')

The important difference is that we're making the sharing explicit. This in turn means that, while @fst a'@ and @snd a'@ are still polymorphic, they can only be polymorphic in the same way. Hence,

    > a' :: forall a. TestClass a => ( (a -> Integer)
    >                                , (a -> Integer) )

This transformation is only looking at the type-variable sharing issue. It still runs afoul of the monomorphism restriction unless you resolve it in the ways others have mentioned.

--
Live well,
~wren
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to