FlexibleContexts and FlexibleInstances

Dear all, This post is partly a gripe about how poor the formal documentation for various GHC extensions is, partly a gripe about how GHC blurs the lines between syntactic and type-level issues as well as between various extensions, and partly a gripe about how the Haskell 98 report is sometimes similarly blurred where syntax is concerned (or not). All these things make the life of a poor parser implementor quite miserable at times. All in good jest of course, but with an edge of truth, especially regarding (lack of) formal documentation. The issue at hand which has caused my frustration is the FlexibleContexts [1] and FlexibleInstances [2] extensions, which lift restrictions imposed by Haskell 98 on the forms of contexts and instances that may be defined. Great extensions both of them - but what do they do, really really? The following toy program requires MultiParamTypeClasses OR FlexibleContexts in order to be accepted by GHC(i):
f :: (T a b) => a -> Int f _ = 0
This of course assumes that we import the definition of T, we *must* have MultiParamTypeClasses enabled if we want to declare T. Both extensions thus enable classes with more than one argument to appear in contexts. Changing the program to
f :: (T a ()) => a -> Int f _ = 0
i.e. changing the second argument to T to () instead, means we now *must* have FlexibleInstances, in order to allow the non-tyvar argument. This is nothing surprising, this is what FlexibleInstances are supposed to do. But the question is, is this a syntactic issue or a typing issue? In GHC proper this doesn't really matter much, as long as it is caught *somewhere* then all is dandy. GHC's parser lets everything pass, and it's the type checker that balks at this program. But for someone like me with *only* a parser, this is a question that needs a clear answer. Looking at the online report, the productions regarding contexts are context -> class | ( class1 , ... , classn ) (n>=0) class -> qtycls tyvar | qtycls ( tyvar atype1 ... atypen ) (n>=1) qtycls -> [ modid . ] tycls tycls -> conid tyvar -> varid Ok, so clearly the () is a syntactic extension enabled by FlexibleContexts, as it is not a tyvar nor a tyvar applied to a sequence of types. So this is something that a parser should handle. FlexibleContexts also enables similar parses of contexts in other places, for instance in class declarations, for which the Haskell 98 report says topdecl -> class [scontext =>] tycls tyvar [where cdecls] scontext -> simpleclass | ( simpleclass1 , ... , simpleclassn ) (n>=0) simpleclass -> qtycls tyvar The difference here is that the simpleclass doesn't allow the tyvar applied to a sequence of types bit. FlexibleContexts lifts that restriction too, so there should be no difference between the two kinds of contexts. So the new formal productions for flexible contexts should be something like fcontext -> fclass | ( fclass1 , ... , fclassn ) (n>=0) fclass -> qtycls type1 ... typen (n>=1) topdecl -> data [fcontext =>] simpletype = constrs [deriving] | newtype [fcontext =>] simpletype = newconstr [deriving] | class [fcontext =>] tycls tyvar [where cdecls] | instance [fcontext =>] qtycls inst [where idecls] gendecl -> vars :: [fcontext =>] type Does this seem correct? Now let's turn to FlexibleInstances, which similarly lifts restrictions, only to instance declarations instead of contexts. The Haskell 98 report says on instance declarations: topdecl -> instance [scontext =>] qtycls inst [where idecls] inst -> gtycon | ( gtycon tyvar1 ... tyvark ) (k>=0, tyvars distinct) | ( tyvar1 , ... , tyvark ) (k>=2, tyvars distinct) | [ tyvar ] | ( tyvar1 -> tyvar2 ) (tyvar1 and tyvar2 distinct) Note the re-appearance of scontext, which is the same as above. The instance head must be a type constructor, possibly applied to a number of type variables, or one of three built-in syntactic cases. This is where I consider the Haskell 98 report blurry - the fact that the tyvars must be distinct, is that truly a syntactic issue? It might be, it's certainly something that could be checked syntactically. But when you take into account that with the proper extensions, they no longer need to be distinct, at what level would we expect such a check to happen? My gut feeling is that this check for distinctness is something that a type checker might do better than a parser, though it's not clear cut by any means. But since I don't do any other kind of name resolution or checking in my parser even if it would be possible (e.g. multiple declarations of the same symbol), I would find it a bit anomalous to check this too. Turning on FlexibleInstances, we shouldn't need to follow any of the above restrictions on inst. In other words, the flexible production should simply be something like finst -> type Right? Now, FlexibleInstances *also* lifts the restriction on contexts, just like FlexibleContexts - but *only* for the contexts of instance declarations. This may seem like a reasonable thing, but it certainly gives me some headaches. It means I could not treat the contexts uniformly, but would need to have separate syntactic categories (or rather post-parse checks) that look different between instance contexts and other contexts (including class). So with FlexibleInstances on, there are *three* different kinds of contexts allowed: scontext for class declaration, fcontext for instance declarations, and context for all other uses of contexts (type signatures, data/newtype declarations). Just a small headache, since I already apparently needed two categories from Haskell 98, but still. I'm not sure I find it reasonable, that flexible instances are enabled just for instance declarations but not elsewhere, but I'm sure a lot of thought was given to that. If it was up to *me* though, I would leave the flexible contexts with FlexibleContexts entirely, which means you would have to use both flags if you wanted both in your instance declarations. Would that be a bad thing? Separation of concern seems desirable to me (and no, I'm not saying that just because it would be easier to implement in the parser)... At any rate, to make a long rant short: * Are my interpretations of the lifted restrictions by FlexibleContexts and FlexibleInstances correct? * Is it reasonable that the issue of checking that tyvars are distinct should not be considered syntactic? * Would it also be reasonable to make the separation of concern between FlexibleContexts and FlexibleInstances more clean? Thanks for reading, and please give me input! Cheers, /Niklas [1] http://www.haskell.org/ghc/docs/latest/html/users_guide/other-type-extension... [2] http://www.haskell.org/ghc/docs/latest/html/users_guide/type-class-extension...

just a few comments from a user (who would really, really, like to be able to define pragma collections, so that he doesn't have to switch on half a dozen separate extensions every time;-).
The following toy program requires MultiParamTypeClasses OR FlexibleContexts in order to be accepted by GHC(i):
f :: (T a b) => a -> Int f _ = 0
This of course assumes that we import the definition of T, we *must* have MultiParamTypeClasses enabled if we want to declare T. Both extensions thus enable classes with more than one argument to appear in contexts.
Only MultiParamTypeClasses does (and neither extension is needed in the module defining 'f', if 'T' is imported, which suggests that MultiParamTypeClasses is propagated to importers - this isn't true for most other extensions). The documentation still points to -fglasgow-exts, so it doesn't seem to answer these questions..
f :: (T a ()) => a -> Int f _ = 0
i.e. changing the second argument to T to () instead, means we now *must* have FlexibleInstances, in order to allow the non-tyvar argument. This is nothing surprising, this is what FlexibleInstances are supposed to do.
You mean FlexibleContexts.
But the question is, is this a syntactic issue or a typing issue?
FlexibleContexts has both syntax and static semantics implications.
Now, FlexibleInstances *also* lifts the restriction on contexts, just like FlexibleContexts - but *only* for the contexts of instance declarations.
No. FlexibleInstances is about instance *heads*, FlexibleContexts is about contexts everywhere (in practice, there are some bugs;-). class T a b -- requires MultiParamTypeClasses instance T a a -- requires FlexibleInstances instance Eq () => T a [b] -- requires FlexibleContexts instance Eq [a] => T a b -- requires UndecidableInstances (if you actually wanted to use 'T's methods, you'd then need OverlappingInstances, but that, UndecidableInstances, and the static semantics aspects of FlexibleContexts are beyond parsing) I also seem to recall more dependencies between flags than I can find documented. Hth, Claus

Hi Claus,
What you describe is exactly how I would *want* things to work. It's
nice to hear my wishes echoed from a user perspective. :-)
On Wed, Jun 10, 2009 at 4:43 PM, Claus Reinke
just a few comments from a user (who would really, really, like to be able to define pragma collections, so that he doesn't have to switch on half a dozen separate extensions every time;-).
The following toy program requires MultiParamTypeClasses OR FlexibleContexts in order to be accepted by GHC(i):
f :: (T a b) => a -> Int f _ = 0
This of course assumes that we import the definition of T, we *must* have MultiParamTypeClasses enabled if we want to declare T. Both extensions thus enable classes with more than one argument to appear in contexts.
Only MultiParamTypeClasses does (and neither extension is needed in the module defining 'f', if 'T' is imported, which suggests that MultiParamTypeClasses is propagated to importers - this isn't true for most other extensions). The documentation still points to -fglasgow-exts, so it doesn't seem to answer these questions..
Right you are - which seems very strange to me. GHC accepts the module defining 'f' with no flags at all, even though it is clearly not Haskell 98. I'd go so far as to say that's a bug (as opposed to just unwanted/unexpected behavior).
f :: (T a ()) => a -> Int f _ = 0
i.e. changing the second argument to T to () instead, means we now *must* have FlexibleInstances, in order to allow the non-tyvar argument. This is nothing surprising, this is what FlexibleInstances are supposed to do.
You mean FlexibleContexts.
Indeed I do.
Now, FlexibleInstances *also* lifts the restriction on contexts, just like FlexibleContexts - but *only* for the contexts of instance declarations.
No. FlexibleInstances is about instance *heads*, FlexibleContexts is about contexts everywhere (in practice, there are some bugs;-).
Right, this is exactly what I *want* should happen, both as a user and as an implementor, but that's not how GHC does it. FlexibleInstances do enable FlexibleContexts for contexts in instance declarations - which I think is a wart.
class T a b -- requires MultiParamTypeClasses instance T a a -- requires FlexibleInstances instance Eq () => T a [b] -- requires FlexibleContexts instance Eq [a] => T a b -- requires UndecidableInstances
Agreed - but here you avoid the tricky cases like my 'f' above. ;-) What I would want, and what I believe you want as well, is the following: ======================================== ** MultiParamTypeClasses: Enables more than one parameter in class declarations, instance heads and more than one argument to class assertions in contexts everywhere. Formally, it would mean the following changes to the Haskell 98 syntax: topdecl -> class [scontext =>] tycls tyvar1 ... tyvarn [where cdecls] (n >=1) | instance [scontext =>] qtycls inst1 ... instn [where idecls] (n >=1) context -> class | ( class1 , ... , classn ) (n>=0) class -> qtycls cls1 ... clsn (n>=1) cls -> tyvar | ( tyvar atype1 ... atypen ) (n>=1) scontext -> simpleclass | ( simpleclass1 , ... , simpleclassn ) (n>=0) simpleclass -> qtycls scls1 ... sclsn (n>=1) scls -> tyvar ** FlexibleContexts: Enables the use of non-tyvar (or tyvar applied to types) arguments to class assertions in contexts everywhere (orthogonal to whether there can be several arguments or just one). Formally it means the following syntactic changes to Haskell 98: fcontext -> fclass | ( fclass1 , ... , fclassn ) (n>=0) fclass -> qtycls atype1 ... atypen (n>=1) topdecl -> data [fcontext =>] simpletype = constrs [deriving] | newtype [fcontext =>] simpletype = newconstr [deriving] | class [fcontext =>] tycls tyvar [where cdecls] | instance [fcontext =>] qtycls inst [where idecls] gendecl -> vars :: [fcontext =>] type for the single-argument case. (Note that I wrote type in my proposal in the OP, but it should of course be atype.) ** FlexibleInstances: Enables the use of arguments other than type constructors (possibly applied to tyvars) in instances *heads* (orthogonal to whether there can be one or more arguments, and what the context may look like). Formally it means the following syntactic changes to Haskell 98: topdecl -> instance [scontext =>] qtycls inst [where idecls] inst -> atype for the single-parameter standard-context case. (Note again that it should be atype and not type as I wrote in the OP.) ======================================== This of course only touches the syntactic part. It doesn't attempt to track things like 'instance (T a a) => R a b' that would be enabled by FlexibleContexts, nor does it attempt to track things like the Paterson conditions, but the syntax is all I'm interested in at the moment. This is the stance I will use for haskell-src-exts, unless someone protests wildly. If there is any interest, I can also propose these cases as bug reports to GHC. I hesitate to make formal proposals (e.g. for Haskell') regarding these extensions since I'm not sure I have the full story regarding the non-syntactic parts. But if there is a particular interest in that then I might go the extra mile there too. Cheers, /Niklas

|What you describe is exactly how I would *want* things to work. It's |nice to hear my wishes echoed from a user perspective. :-) actually, I was describing how things seem to work right now. |> Only MultiParamTypeClasses does (and neither extension is needed in the |> module defining 'f', if 'T' is imported, which suggests that |> MultiParamTypeClasses is propagated to importers - this isn't true for |> most other extensions). The documentation still points to -fglasgow-exts, so |> it doesn't seem to answer these questions.. | |Right you are - which seems very strange to me. GHC accepts the module |defining 'f' with no flags at all, even though it is clearly not |Haskell 98. I'd go so far as to say that's a bug (as opposed to just |unwanted/unexpected behavior). It is not that strange, really (it ought to be documented, but the fan- out from glasgow-exts/hugs mode to more detailed extensions has been fairly recent, compared to the lifetime of these features): if module 'A' exports multiparameter type classes, importers of those classes have to have MultiParamTypeClasses on - there are no legal uses of those imports otherwise (while FlexibleInstances/Contexts can just affect a subset of use sites). |> No. FlexibleInstances is about instance *heads*, FlexibleContexts is about |> contexts everywhere (in practice, there are some bugs;-). | |Right, this is exactly what I *want* should happen, both as a user and |as an implementor, but that's not how GHC does it. FlexibleInstances |do enable FlexibleContexts for contexts in instance declarations - |which I think is a wart. | |> class T a b -- requires MultiParamTypeClasses instance T a a -- requires |> FlexibleInstances instance Eq () => T a [b] -- requires FlexibleContexts |> instance Eq [a] => T a b -- requires UndecidableInstances Perhaps I should have been more explicit, but if you try that example by adding one line after the other, starting from zero extensions, you'll find that FlexibleInstances does not enable FlexibleContexts (at least not in my versions of GHC, which always stop at the first class of language errors and force me into an iterative cycle of code, error, add one pragma, error, add another pragma, ..). Claus

Claus Reinke wrote:
if module 'A' exports multiparameter type classes, importers of those classes have to have MultiParamTypeClasses on - there are no legal uses of those imports otherwise (while FlexibleInstances/Contexts can just affect a subset of use sites).
say we have module A where { class Coerce a b where coerce :: a -> b } module B where { import A ; co a = coerce a } Syntactically, module B doesn't require MultiParamTypeClasses because the signature that's involved is only discovered during type inference. Something to beware of if those restrictions need to be implemented somehow in GHC. Niklas Broberg wrote:
If there is any interest, I can also propose these cases as bug reports to GHC.
please do! -Isaac

On Thu, Jun 11, 2009 at 4:16 AM, Claus Reinke
|What you describe is exactly how I would *want* things to work. It's |nice to hear my wishes echoed from a user perspective. :-)
actually, I was describing how things seem to work right now.
|> Only MultiParamTypeClasses does (and neither extension is needed in the |> module defining 'f', if 'T' is imported, which suggests that |> MultiParamTypeClasses is propagated to importers - this isn't true for |> most other extensions). The documentation still points to -fglasgow-exts, so |> it doesn't seem to answer these questions.. | |Right you are - which seems very strange to me. GHC accepts the module |defining 'f' with no flags at all, even though it is clearly not |Haskell 98. I'd go so far as to say that's a bug (as opposed to just |unwanted/unexpected behavior).
It is not that strange, really (it ought to be documented, but the fan- out from glasgow-exts/hugs mode to more detailed extensions has been fairly recent, compared to the lifetime of these features):
if module 'A' exports multiparameter type classes, importers of those classes have to have MultiParamTypeClasses on - there are no legal uses of those imports otherwise (while FlexibleInstances/Contexts can just affect a subset of use sites).
It's more complicated than that. If you have two modules A and B,
defined like so:
{-# LANGUAGE MultiParamTypeClasses #-}
module A where
class Foo a b where
foo :: a -> b
instance Foo Bool Int where
foo True = 1
foo False = 0
--
module B where
import A
bar :: (Foo a b) => [a] -> [b]
bar = map foo
I can load B.hs into GHCi and call bar without problems. So the import
of Foo is fine. But you still get an error if you try to declare an
instance of Foo in B.hs.
instance Foo Bool Integer where
foo True = 1
foo False = 0
B.hs:8:0:
Illegal instance declaration for `Foo Bool Integer'
(Only one type can be given in an instance head.
Use -XMultiParamTypeClasses if you want to allow more.)
In the instance declaration for `Foo Bool Integer'
Failed, modules loaded: A.
--
Dave Menendez

{-# LANGUAGE MultiParamTypeClasses #-} module A where class Foo a b where foo :: a -> b
instance Foo Bool Int where foo True = 1 foo False = 0
module B where import A
bar :: (Foo a b) => [a] -> [b] bar = map foo
I can load B.hs into GHCi and call bar without problems. So the import of Foo is fine. But you still get an error if you try to declare an instance of Foo in B.hs.
instance Foo Bool Integer where foo True = 1 foo False = 0
B.hs:8:0: Illegal instance declaration for `Foo Bool Integer' (Only one type can be given in an instance head. Use -XMultiParamTypeClasses if you want to allow more.) In the instance declaration for `Foo Bool Integer' Failed, modules loaded: A.
Ah, that is one definite bug waiting for a ticket, then: - inheritance of MultiParamTypeClasses is not specified - if it is inherited, the instance in B should be permitted - if it is not inherited, the context in B should not be permitted Claus
participants (4)
-
Claus Reinke
-
David Menendez
-
Isaac Dupree
-
Niklas Broberg