Is this related to monomorphism restriction?

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 The only thing I can think about is monomorphism restriction, but it's allowed (or even the third line would not be accepted). Is there something I could read to understand that? Thanks, Maurício

On Sat, Dec 20, 2008 at 4:28 PM, Maurício
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
Yep, monomorphism restriction. a, because it is syntactically not a function, must not be typeclass polymorphic (without a type signature). So it tries to default, and TestClass probably doesn't have any defaults. Luke
The only thing I can think about is monomorphism restriction, but it's allowed (or even the third line would not be accepted). Is there something I could read to understand that?
Thanks, Maurício
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, Dec 21, 2008 at 10:28 AM, Maurício
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
The only thing I can think about is monomorphism restriction, but it's allowed (or even the third line would not be accepted). Is there something I could read to understand that?
Thanks, Maurício
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
The monomorphism restriction refuses to accept the definition of a. However, even if we turn the monomorphism restriction off there is still a problem.
{-# LANGUAGE NoMonomorphismRestriction #-}
f :: (TestClass a) => a -> Integer f = const 1 a = (f,f) g = fst a
In this case, the definition of a is accepted, but not the definition of g. The reason is that a has type a :: (TestClass a, TestClass b) => (a,b) and then when we take 'fst' of this value (as in g) we get g :: (TestClass a, TestClass b) => a which is an ambiguous type, since there is no way to tell the compiler what 'b' is when running g. Cheers, Reiner

Why isn't the last line of this code allowed? f :: (TestClass a) => a -> Integer f = const 1 a = (f,f) g = fst a The only thing I can think about is monomorphism restriction, but it's allowed (...)
(...) The reason is that a has type a :: (TestClass a, TestClass b) => (a,b) and then when we take 'fst' of this value (as in g) we get
g :: (TestClass a, TestClass b) => a which is an ambiguous type, (...)
Is there some version (i.e., set of extensions) of Haskell where this would be allowed?

You have a few options.
In Haskell98 (no extensions):
a () = (f,f)
g () = fst (a ())
-- alternatively
g x = fst (a ()) x
Here you make it explicit that "a" and "g" are functions; the
monomorphism restriction is there to stop things that look like values
(and therefore you expect to only get evaluated once) from being
functions (which get evaluated every time they are used).
Alternatively, you are allowed to tell the compiler "This value should
be polymorphic" with a type signature:
a :: TestClass a => (a -> Integer, a -> Integer)
a = (f,f)
g :: TestClass a => a -> Integer
g = fst a
The non-haskell98 solution:
{-# LANGUAGE NoMonomorphismRestriction #-}
But beware that it is really there to protect you; code that uses g
will compile to something very similar to the first operation I
showed, re-evaluating "fst a" and doing dictionary selection at every
use of g.
-- ryan
On Sun, Dec 21, 2008 at 9:21 AM, Maurício
Why isn't the last line of this code allowed? f :: (TestClass a) => a -> Integer f = const 1 a = (f,f) g = fst a The only thing I can think about is monomorphism restriction, but it's allowed (...)
(...) The reason is that a has type a :: (TestClass a, TestClass b) => (a,b) and then when we take 'fst' of this value (as in g) we get
g :: (TestClass a, TestClass b) => a which is an ambiguous type, (...)
Is there some version (i.e., set of extensions) of Haskell where this would be allowed?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello,
You can work around the monomorphism restriction with extensions but
to fix the ambiguity in your program that Reiner pointed out you'll
have to change the program to specify how you'd like to instantiate
"a".
here are all the types once again:
f :: (TestClass a) => a -> Integer
f = const 1
a :: (TestClass a, TestClass b) => (a -> Integer, b -> Integer)
a = (f,f)
g :: (TestClass a, TestClass b) => a -> Integer -- ambiguous
g = fst a
Note that the type of 'g' to the right of '=>' does not mention 'b'.
This means that the type of 'g' is ambiguos because the type checker
does not know how to pick a type for 'b'. To fix that, you could:
1. Give 'a' a less general type, for example: a :: (TestClass a) =>
(a -> Integer, a -> Integer)
2. Write a type signature on the use of 'a':
g :: TestClass a => a -> Integer
g = fst (a :: (a -> Integer, a -> Integer))
Here we are using another GHC extension called "scoped type variables"
to associate the "a" in the type signature of "g" with the "a" in the
type annotation for the value "a".
Hope that this helps,
Iavor
On Sun, Dec 21, 2008 at 9:21 AM, Maurício
Why isn't the last line of this code allowed? f :: (TestClass a) => a -> Integer f = const 1 a = (f,f) g = fst a The only thing I can think about is monomorphism restriction, but it's allowed (...)
(...) The reason is that a has type a :: (TestClass a, TestClass b) => (a,b) and then when we take 'fst' of this value (as in g) we get
g :: (TestClass a, TestClass b) => a which is an ambiguous type, (...)
Is there some version (i.e., set of extensions) of Haskell where this would be allowed?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2008/12/21 Iavor Diatchki
g :: TestClass a => a -> Integer g = fst (a :: (a -> Integer, a -> Integer))
Which I believe needs to be written: g :: forall a. TestClass a => a -> Integer g = fst (a :: (a -> Integer, a -> Integer))
Here we are using another GHC extension called "scoped type variables" to associate the "a" in the type signature of "g" with the "a" in the type annotation for the value "a".
Hope that this helps, Iavor
On Sun, Dec 21, 2008 at 9:21 AM, Maurício
wrote: Why isn't the last line of this code allowed? f :: (TestClass a) => a -> Integer f = const 1 a = (f,f) g = fst a The only thing I can think about is monomorphism restriction, but it's allowed (...)
(...) The reason is that a has type a :: (TestClass a, TestClass b) => (a,b) and then when we take 'fst' of this value (as in g) we get
g :: (TestClass a, TestClass b) => a which is an ambiguous type, (...)
Is there some version (i.e., set of extensions) of Haskell where this would be allowed?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi,
On Sun, Dec 21, 2008 at 11:45 AM, Luke Palmer
2008/12/21 Iavor Diatchki
g :: TestClass a => a -> Integer g = fst (a :: (a -> Integer, a -> Integer))
Which I believe needs to be written:
g :: forall a. TestClass a => a -> Integer g = fst (a :: (a -> Integer, a -> Integer))
quite right! sorry for not testing my code. -iavor
Here we are using another GHC extension called "scoped type variables" to associate the "a" in the type signature of "g" with the "a" in the type annotation for the value "a".
Hope that this helps, Iavor
On Sun, Dec 21, 2008 at 9:21 AM, Maurício
wrote: Why isn't the last line of this code allowed? f :: (TestClass a) => a -> Integer f = const 1 a = (f,f) g = fst a The only thing I can think about is monomorphism restriction, but it's allowed (...)
(...) The reason is that a has type a :: (TestClass a, TestClass b) => (a,b) and then when we take 'fst' of this value (as in g) we get
g :: (TestClass a, TestClass b) => a which is an ambiguous type, (...)
Is there some version (i.e., set of extensions) of Haskell where this would be allowed?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
participants (6)
-
Iavor Diatchki
-
Luke Palmer
-
Maurício
-
Reiner Pope
-
Ryan Ingram
-
wren ng thornton