Re: incompatible signatur syntax within instance definition

Fergus Henderson wrote:
I think the issue here is that in ghc (with -fglasgow-exts), the "a" here refers to the same type variable "a" in the top of the instance declaration, which has already been constained, and cannot be constrained again.
Is that a bug or a feature?
With Haskell 98, it is a fresh type variable, for which the constraint is necessary.
Ok, if I view the local function as a new/independent function, I accept to add the Constraint, but that should be acceptable for ghc -fglasgow-exts as well (as is for hugs with extensions).
Try renaming the type variable as "b" in the inner declaration: the following should work both with and without -fglasgow-exts.
showsl :: Show b => List b -> ShowS
Yes, this works, but I never thought that the choice of "a" or "b" would matter. Christian
instance Show a => Show (List a) where showsPrec _ Nil = showString "[]" showsPrec _ l = showString "[" . showsl l . showString "]" where -- showsl :: List a -> ShowS -- for ghc -- showsl :: Show a => List a -> ShowS -- for hugs

Christian Maeder
Fergus Henderson wrote:
I think the issue here is that in ghc (with -fglasgow-exts), the "a" here refers to the same type variable "a" in the top of the instance declaration, which has already been constained, and cannot be constrained again.
Is that a bug or a feature?
It is a feature called "scoped type variables". Regards, Malcolm

On 08-Dec-2003, Christian Maeder
Fergus Henderson wrote:
I think the issue here is that in ghc (with -fglasgow-exts), the "a" here refers to the same type variable "a" in the top of the instance declaration, which has already been constained, and cannot be constrained again.
Is that a bug or a feature?
A feature. It's called "scoped type variables". See
http://www.haskell.org/ghc/docs/6.2/html/users_guide/type-extensions.html#SC...:
"The type variables in the head of a class or instance declaration scope
over the methods defined in the where part.".
Or were you referring to the fact that variables which are already
constrained can't be constrained again? IMHO that is a feature too.
It doesn't make sense to constrain a variable at any point other than
the point where that variable is introduced.
--
Fergus Henderson

Fergus Henderson wrote:
Or were you referring to the fact that variables which are already constrained can't be constrained again? IMHO that is a feature too. It doesn't make sense to constrain a variable at any point other than the point where that variable is introduced.
Indeed, repeating a constraint should be no error (at most a warning) and be it only to let "ghc -fglasgow-exts" except more programs than ghc does without extensions. (I once even argued, that keywords for extensions should also be reserved for Haskell98 in order to always allow for switching extensions on without changes.) /home/maeder/haskell/examples/MyList.hs:10: Warning: Duplicate class assertion `Show a' in the context: (Show a, Show a) => ... Cheers Christian

On 09-Dec-2003, Christian Maeder
Fergus Henderson wrote:
Or were you referring to the fact that variables which are already constrained can't be constrained again? IMHO that is a feature too. It doesn't make sense to constrain a variable at any point other than the point where that variable is introduced.
Indeed, repeating a constraint should be no error (at most a warning) and be it only to let "ghc -fglasgow-exts" except [accept] more programs than ghc does without extensions.
Allowing repeated constraints would not be sufficient for that. The fact
that the two type variables in the case originally posted happened to have
the same constraint is somewhat coincidental; in Haskell 98, the inner
variable might have absolutely no relationship with the outer variable.
Consider the following example:
data MyType a = MkMyType a
class Foo a where
foo :: a -> Int
instance Foo (MyType a) where
foo _ = bar (42::Int) where
bar :: a -> a
bar x = x
This is legal in Haskell 98, because the `a' in the inner declaration is
implicitly universally quantified. But if the scope of the outer type
variable `a' extends over the inner type declaration, then the inner `a'
will not be locally universally quantified, and the call to `bar' will
be a type error, because the `a' in the head of the instance declaration
will in general be different than `Int'.
data MyType a = MkMyType a
class Foo a where
foo :: a -> Int
instance Foo (MyType a) where
foo _ = bar (42::Int) where
bar :: a -> a
bar x = x
Indeed, the scoping of type variables can affect the meaning
of programs, not just their legality. Consider the following
variation:
data MyType a = MkMyType a
class Foo a where
foo :: a -> String
instance Num a => Foo (MyType a) where
foo _ = bar 42 where
bar :: Num a => a -> String
bar x = show x
If the scope over the outer `a' does not extend over the inner `a',
then the implicit `fromInteger 42' will be resolved by the defaulting
rules to `fromInteger 42 :: Int'. But if the outer `a' extends over
the inner `a', then it will be `fromInteger 42 :: a'. These could
have different semantics, e.g. if called in the following context.
data MyNum = MyNum
instance Eq MyNum where
_ == _ = True
instance Num MyNum where
fromInteger _ = MyNum
instance Show MyNum where
show MyNum = "MyNum"
main = print (foo (MkMyType MyNum))
With Haskell 98, this program will print "42". With ghc and your
proposed change to allow multiple qualifications, it would print "MyNum".
With ghc as it stands, you get an error, because the variable `a' is
qualified multiple times.
So, to summarize, this particular ghc extension is not a pure extension.
It can change the legality or even the semantics of Haskell 98 code.
Allowing repeated constraints won't change that.
Given that allowing repeated constraints isn't sufficient to solve
that problem, I don't think it is a good idea to allow them.
P.S. I note that ghc 5.02.2 enables this extension always, regardless
of the setting of -fglasgow-exts. That seems like a bug to me.
--
Fergus Henderson

Fergus Henderson wrote:
Allowing repeated constraints would not be sufficient for that.
Yes, you're right. A true (but senseless) constraint like "Show Int" is rejected as well. (The same applies to "Show a" if "a" is a scoped type variable, that is when "a" is monomorph.) So a function with type "a -> a" in Haskell98 is always polymorphic, whereas it may be a monomorphic function in Haskell with glasgow-exts (iff "a" is a scoped type variable). The compatibility problem between Haskell98 and glasgow-exts is thus moved to the place where scoped typed variables can be introduced. Since type annotations of patterns are illegal in Haskell98 the only problem was the introduction of scoped type variables through the "instance" line. So why was this done (except to shorten notation)?
Consider the following example:
data MyType a = MkMyType a class Foo a where foo :: a -> Int
Since the type "a" usually occurs in every method it is no problem to introduce scoped type variables via patterns (that are illegal in Haskell98): instance Foo (MyType a) where foo (_ :: MyType a) = ...
So, to summarize, this particular ghc extension is not a pure extension. It can change the legality or even the semantics of Haskell 98 code. Allowing repeated constraints won't change that. Given that allowing repeated constraints isn't sufficient to solve that problem, I don't think it is a good idea to allow them.
I entirely agree with this. The first point would be to make the extension "pure". Allowing or disallowing repeated constraints is then a mere (unimportant) design option.
P.S. I note that ghc 5.02.2 enables this extension always, regardless of the setting of -fglasgow-exts. That seems like a bug to me.
I would not worry about bugs in older versions. Cheers Christian
participants (3)
-
Christian Maeder
-
Fergus Henderson
-
Malcolm Wallace