Modern Scoped Type Variables #448: recommendation (mostly) accept

Dear all, Let me bring to your attention the Modern Scoped Type Variables proposal, by our own Richard https://github.com/ghc-proposals/ghc-proposals/pull/448 . The proposal is a touch intimidating, because the text is large. But most of it comes from other, already accepted, proposals that this proposal is tidying up and tying together. What this proposal tries to achieve is to make a consistent text about all the recent changes to binding type variables. The proposal adds new principles to the `principles.rst` files which inform the changes proposed, of these, I have the following comments: - The Visibility Orthogonality Principle doesn't seem to have a very clear definition. It may be a sign that it's not something that is so important - The Explicit Binding Principle says that we need to be able to enforce that all type variables have a binding site. I think it's a bit strong: I would like Haskell to let me write a binding site for every type variable, but not necessarily to error out when that doesn't happen. That being said, I'm happy with warnings to help me along the way, but I don't think that this Explicit Binding Principle should be phrased in a way that requires adding extensions to control this behaviour. - The Contiguous Scoping Principle, which states that a binder binds in one contiguous region sounds dubious to me. I don't see a particular reason for this to be. --- In the proposed changes themselves: up to Section 5, the proposed changes are mostly existing accepted proposals, cleaned up with what was learnt since they were written, as well as to adhere to the new principles. These are mostly uncontroversial and the specification makes sense to me. I'm in favour of accepting all that. With the caveat that this proposal introduces quite a few extensions. And at this point, I'm still not quite sure what Richard recommends is the set of extensions that I should use (and I'm slightly dismayed that I believe that it will be a set of cardinal more than 1). I think this reflects a vision of extensions as switches to customise the behaviour of GHC. This vision, as I've stated before, is very alien to me: I see extensions as staging areas for features to become an integral part of Haskell. So I don't know what to think of all these extensions. I'm definitely not against splitting -XScopedTypeVariables into smaller components, if it is done so that they are reassembled in a different way in an alternative extension that would now be the recommended default (or at least is to become the next recommended default). Finally, there are Sections 6 to 8. These are entirely new. Though they are working towards the new principles (well, as far as I can tell, Section 6 doesn't contribute to the principles, but it is a stepping stone for both Sections 7 and 8). These sections are concerned with adding local let-bindings of type variables, in particular inside types and patterns. By the way, Section 7 proposes two syntaxes for let binders in patterns, and I *strongly* prefer the second syntax, which reads something like `f (let b = Bool) (True :: Bool) = …`. Anyway, these are new, I feel that they are a bit out of place in a proposal that is about tidying up the existing designs. That being said, they are here, and they seem like fairly uncontroversial to me, (except, probably the syntax `(let b = _)` to bind a variable to a type to be filled by the compiler). I'm fine with accepting these, though they may require a bit more scrutiny than the rest. Best, Arnaud

Thanks Arnaud,
I have responded on the GitHub discussion
Simon
On Tue, 29 Mar 2022 at 16:02, Spiwack, Arnaud
Dear all,
Let me bring to your attention the Modern Scoped Type Variables proposal, by our own Richard https://github.com/ghc-proposals/ghc-proposals/pull/448 .
The proposal is a touch intimidating, because the text is large. But most of it comes from other, already accepted, proposals that this proposal is tidying up and tying together.
What this proposal tries to achieve is to make a consistent text about all the recent changes to binding type variables.
The proposal adds new principles to the `principles.rst` files which inform the changes proposed, of these, I have the following comments: - The Visibility Orthogonality Principle doesn't seem to have a very clear definition. It may be a sign that it's not something that is so important - The Explicit Binding Principle says that we need to be able to enforce that all type variables have a binding site. I think it's a bit strong: I would like Haskell to let me write a binding site for every type variable, but not necessarily to error out when that doesn't happen. That being said, I'm happy with warnings to help me along the way, but I don't think that this Explicit Binding Principle should be phrased in a way that requires adding extensions to control this behaviour. - The Contiguous Scoping Principle, which states that a binder binds in one contiguous region sounds dubious to me. I don't see a particular reason for this to be.
---
In the proposed changes themselves: up to Section 5, the proposed changes are mostly existing accepted proposals, cleaned up with what was learnt since they were written, as well as to adhere to the new principles.
These are mostly uncontroversial and the specification makes sense to me. I'm in favour of accepting all that.
With the caveat that this proposal introduces quite a few extensions. And at this point, I'm still not quite sure what Richard recommends is the set of extensions that I should use (and I'm slightly dismayed that I believe that it will be a set of cardinal more than 1). I think this reflects a vision of extensions as switches to customise the behaviour of GHC. This vision, as I've stated before, is very alien to me: I see extensions as staging areas for features to become an integral part of Haskell. So I don't know what to think of all these extensions. I'm definitely not against splitting -XScopedTypeVariables into smaller components, if it is done so that they are reassembled in a different way in an alternative extension that would now be the recommended default (or at least is to become the next recommended default).
Finally, there are Sections 6 to 8. These are entirely new. Though they are working towards the new principles (well, as far as I can tell, Section 6 doesn't contribute to the principles, but it is a stepping stone for both Sections 7 and 8). These sections are concerned with adding local let-bindings of type variables, in particular inside types and patterns.
By the way, Section 7 proposes two syntaxes for let binders in patterns, and I *strongly* prefer the second syntax, which reads something like `f (let b = Bool) (True :: Bool) = …`.
Anyway, these are new, I feel that they are a bit out of place in a proposal that is about tidying up the existing designs. That being said, they are here, and they seem like fairly uncontroversial to me, (except, probably the syntax `(let b = _)` to bind a variable to a type to be filled by the compiler). I'm fine with accepting these, though they may require a bit more scrutiny than the rest.
Best, Arnaud
_______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

In the spirit of not accepting proposals that lead to language forks, it
would be great to get some clarification on the concerns that Arnaud raises
here:
On Tue, 29 Mar 2022 at 16:02, Spiwack, Arnaud
With the caveat that this proposal introduces quite a few extensions. And at this point, I'm still not quite sure what Richard recommends is the set of extensions that I should use (and I'm slightly dismayed that I believe that it will be a set of cardinal more than 1). I think this reflects a vision of extensions as switches to customise the behaviour of GHC. This vision, as I've stated before, is very alien to me: I see extensions as staging areas for features to become an integral part of Haskell. So I don't know what to think of all these extensions. I'm definitely not against splitting -XScopedTypeVariables into smaller components, if it is done so that they are reassembled in a different way in an alternative extension that would now be the recommended default (or at least is to become the next recommended default).
I think we should express an opinion about the intended direction. Are we advising that ExtendedForallScope is a dead end, because we want TypeAbstraction? Cheers Simon
Finally, there are Sections 6 to 8. These are entirely new. Though they are working towards the new principles (well, as far as I can tell, Section 6 doesn't contribute to the principles, but it is a stepping stone for both Sections 7 and 8). These sections are concerned with adding local let-bindings of type variables, in particular inside types and patterns.
By the way, Section 7 proposes two syntaxes for let binders in patterns, and I *strongly* prefer the second syntax, which reads something like `f (let b = Bool) (True :: Bool) = …`.
Anyway, these are new, I feel that they are a bit out of place in a proposal that is about tidying up the existing designs. That being said, they are here, and they seem like fairly uncontroversial to me, (except, probably the syntax `(let b = _)` to bind a variable to a type to be filled by the compiler). I'm fine with accepting these, though they may require a bit more scrutiny than the rest.
Best, Arnaud
_______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

Of course, I think we all understand that all these extensions are opt-in, and the behaviour of GHC would not change, for existing modules, would not change if this proposal was accepted.
I think we should express an opinion about the intended direction. Are we advising that ExtendedForallScope is a dead end, because we want TypeAbstraction?
One way to think of it is this: if Haskell had type-abstraction from Day 1,
would we ever have introduced ExtendedForAllScope? I'm sure we would not.
Even at the time we introduced it, I remember we were concerned that it was
a very strange (non-nested) scoping construct.
We bind term variables in patterns on the LHS; it makes sense to do the
same for type variables.
So yes, in that sense the story is that we recommend TypeAbstraction for
introducing a scoped type variable. Thus, instead of
```
id :: forall a. a -> a
id x = (x :: a)
```
we would have
```
id :: forall a. a -> a
id @b x = (x::b) -- I have used a different name only for illustrative
purposes; could also be 'a'.
```
We have to repeat that type-variable pattern in each equation for the
function. But we also have to repeat the term variables, and we just take
that for granted.
But as a "recommendation", it's a pretty weak one. You are still free to
use either ExtendedForAllScope or TypeAbstraction or both at once in a
particular module (subject to point 5 of 5.2). So it's a bit like
let-vs-where, or H98 data decls vs GADTs. Do we even need a firm
"recommendation"?
Simon
On Fri, 1 Apr 2022 at 08:27, Simon Marlow
In the spirit of not accepting proposals that lead to language forks, it would be great to get some clarification on the concerns that Arnaud raises here:
On Tue, 29 Mar 2022 at 16:02, Spiwack, Arnaud
wrote: With the caveat that this proposal introduces quite a few extensions. And at this point, I'm still not quite sure what Richard recommends is the set of extensions that I should use (and I'm slightly dismayed that I believe that it will be a set of cardinal more than 1). I think this reflects a vision of extensions as switches to customise the behaviour of GHC. This vision, as I've stated before, is very alien to me: I see extensions as staging areas for features to become an integral part of Haskell. So I don't know what to think of all these extensions. I'm definitely not against splitting -XScopedTypeVariables into smaller components, if it is done so that they are reassembled in a different way in an alternative extension that would now be the recommended default (or at least is to become the next recommended default).
I think we should express an opinion about the intended direction. Are we advising that ExtendedForallScope is a dead end, because we want TypeAbstraction?
Cheers Simon
Finally, there are Sections 6 to 8. These are entirely new. Though they are working towards the new principles (well, as far as I can tell, Section 6 doesn't contribute to the principles, but it is a stepping stone for both Sections 7 and 8). These sections are concerned with adding local let-bindings of type variables, in particular inside types and patterns.
By the way, Section 7 proposes two syntaxes for let binders in patterns, and I *strongly* prefer the second syntax, which reads something like `f (let b = Bool) (True :: Bool) = …`.
Anyway, these are new, I feel that they are a bit out of place in a proposal that is about tidying up the existing designs. That being said, they are here, and they seem like fairly uncontroversial to me, (except, probably the syntax `(let b = _)` to bind a variable to a type to be filled by the compiler). I'm fine with accepting these, though they may require a bit more scrutiny than the rest.
Best, Arnaud
_______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
_______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

On Mon, Apr 4, 2022 at 9:33 AM Simon Peyton Jones < simon.peytonjones@gmail.com> wrote:
So it's a bit like let-vs-where, or H98 data decls vs GADTs. Do we even need a firm "recommendation"?
I think that there are two aspects to consider here, which make me think that: yes, we probably want a stronger form of recommendation (even in the extensions-are-switches-to-tune-GHC's-behaviour worldview) 1. Let and where, as well as the two syntaxes for data types are perfectly compatible with one another. You can use both at the same time, and people do. While ExtendedForAllScope and TypeAbstractions are at odds with each other. Granted, the proposal gives a semantics to having both of them on. But still, they are not good friends. So you probably actually don't want to mix them. This point is highlighted by the fact that the proposal makes ExtendedForAllScope an extension with the explicit purpose of being able to deactivate this behaviour. Nobody ever asked to deactivate lets or the Haskell 98 syntax for data types. 2. As the proposal stands it's easier to use ExtendedForAllScope than to use TypeAbstraction. Because you will usually use it in conjunction with ScopedTypeVariables, and ScopedTypeVariables implies the former but not the latter. Therefore, ExtendedForAllScope requires turning a single extension while TypeAbstractions requires two. Therefore, from the point of view of the programmer, ExtendedForAllScope will feel like more of a default choice. If we think that TypeAbstractions ought to be the default choice, then we need to make it at least as easy as ExtendedForAllScope. /Arnaud

Thanks for kicking off this conversation, Arnaud! To be clear in this thread: I'm fine delaying the discussion of section 6-8 until later. Arnaud brings up my new principles in his initial email. Do please consider these principles as part of the deliberations, as they will become principles that we, as a committee, will have adopted. About extensions: We, as a community and as a committee, have not come to terms with the two possible interpretations of extensions. I would like to say that, ideally, extensions are candidates for eventual inclusion. However, that is neither the current practice nor our trendline. Examples: - any flags included in Haskell98 (including, for example, MonomorphismRestriction). These are definitely settings that one can choose per module. If they were candidates for inclusion, they wouldn't exist (because they're already included!). - RebindableSyntax (though this is not one to mimic) - MagicHash. My interpretation is that this extension is meant to allow users to explicitly opt into low-level code. - Recently accepted #285 https://github.com/ghc-proposals/ghc-proposals/pull/285, which introduces two new -XNo... extensions (both also included in #448). As a practical matter, then, extensions are means of customization. We might imagine a debate where we try to change this, and then come up with a way to get from where we are to that changed future. Very specifically answering Simon M's concern: I see ExtendedForAllScope as a dead end, yes. It's included as a way of supporting the gobs and gobs and gobs of code that use today's ScopedTypeVariables, but at t=∞, we should get rid of it. Note that an optional extra https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04... introduces a @(..) syntax that makes TypeAbstractions significantly less repetitive, and thus about as easy to use as ExtendedForAllScope (which, recall, requires an explicit forall where there might otherwise be none). Richard PS: I'm on holiday starting tomorrow and so may not respond for about two weeks. Back in action on the 15th, but expect a few days of digging out.

On Mon, 4 Apr 2022 at 18:17, Richard Eisenberg
Thanks for kicking off this conversation, Arnaud!
To be clear in this thread: I'm fine delaying the discussion of section 6-8 until later.
Arnaud brings up my new principles in his initial email. Do please consider these principles as part of the deliberations, as they will become principles that we, as a committee, will have adopted.
About extensions: We, as a community and as a committee, have not come to terms with the two possible interpretations of extensions. I would like to say that, ideally, extensions are candidates for eventual inclusion. However, that is neither the current practice nor our trendline. Examples: - any flags included in Haskell98 (including, for example, MonomorphismRestriction). These are definitely settings that one can choose per module. If they were candidates for inclusion, they wouldn't exist (because they're already included!). - RebindableSyntax (though this is not one to mimic) - MagicHash. My interpretation is that this extension is meant to allow users to explicitly opt into low-level code. - Recently accepted #285 https://github.com/ghc-proposals/ghc-proposals/pull/285, which introduces two new -XNo... extensions (both also included in #448). As a practical matter, then, extensions are means of customization. We might imagine a debate where we try to change this, and then come up with a way to get from where we are to that changed future.
I think we actually did come to some agreement on the interpretation of extensions, it's in our review criteria under "does not create a language fork": https://github.com/ghc-proposals/ghc-proposals#review-criteria . Yes there are plenty of extensions that don't fit this criteria, but they tend to be either special-purpose extensions for things like low-level programming, building DSLs, or for backwards compatibility, rather than extensions we would expect people to routinely enable. Does that apply in this case? Well, perhaps the extensions are not technically incompatible, but they're "at odds" as Arnaud puts it. Another way to frame the original question might be: which of these extensions do we expect to include in GHC2023 (or GHC2024 or whatever it ends up being)? GHC2021 already has ScopedTypeVariables. We did decide (if I recall correctly) that we might remove things from future GHCXXXX sets, so are we going to remove ExtendedForAllScope and add TypeAbstractions from some future GHCXXXX, or just add TypeAbstractions? I'm not expressing a preference one way or the other, just that we should decide where this is going. Cheers Simon Very specifically answering Simon M's concern: I see ExtendedForAllScope as
a dead end, yes. It's included as a way of supporting the gobs and gobs and gobs of code that use today's ScopedTypeVariables, but at t=∞, we should get rid of it. Note that an optional extra https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04... introduces a @(..) syntax that makes TypeAbstractions significantly less repetitive, and thus about as easy to use as ExtendedForAllScope (which, recall, requires an explicit forall where there might otherwise be none).
Richard
PS: I'm on holiday starting tomorrow and so may not respond for about two weeks. Back in action on the 15th, but expect a few days of digging out. _______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

Thanks for reminding us of that definition in our review criteria -- it's helpful. I would say that every extension in this proposal fits the standard, except for ExtendedForAllScope. That is, I would be happy for the following extensions (as described in this proposal) to be part of a standard: - PatternSignatures - PatternSignatureBinds - MethodTypeVariables (though John Ericson makes a comment on GitHub which suggests that this, too, may want revision -- I'm not fully convinced yet) - ImplicitForAll - TypeAbstractions (and ExtendedLet, but that's not being debated at the moment) Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions. That logic might suggest revisiting #285 (which introduced NoImplicitForAll and NoPatternSignatureBinds), instead wishing for these to become warnings, rather than language extensions. (NB: #285 is accepted, but not implemented.) Regarding GHCXXXX: Yes, I think we would end up removing ExtendedForAllScope from it -- or at least I would advocate for doing so. Indeed, when we considered ScopedTypeVariables as a candidate for GHCXXXX, I was worried about getting stuck with it, and I believe it was important to me that we had the option to remove, later. Richard
On Apr 4, 2022, at 3:38 PM, Simon Marlow
wrote: On Mon, 4 Apr 2022 at 18:17, Richard Eisenberg
mailto:lists@richarde.dev> wrote: Thanks for kicking off this conversation, Arnaud! To be clear in this thread: I'm fine delaying the discussion of section 6-8 until later.
Arnaud brings up my new principles in his initial email. Do please consider these principles as part of the deliberations, as they will become principles that we, as a committee, will have adopted.
About extensions: We, as a community and as a committee, have not come to terms with the two possible interpretations of extensions. I would like to say that, ideally, extensions are candidates for eventual inclusion. However, that is neither the current practice nor our trendline. Examples: - any flags included in Haskell98 (including, for example, MonomorphismRestriction). These are definitely settings that one can choose per module. If they were candidates for inclusion, they wouldn't exist (because they're already included!). - RebindableSyntax (though this is not one to mimic) - MagicHash. My interpretation is that this extension is meant to allow users to explicitly opt into low-level code. - Recently accepted #285 https://github.com/ghc-proposals/ghc-proposals/pull/285, which introduces two new -XNo... extensions (both also included in #448). As a practical matter, then, extensions are means of customization. We might imagine a debate where we try to change this, and then come up with a way to get from where we are to that changed future.
I think we actually did come to some agreement on the interpretation of extensions, it's in our review criteria under "does not create a language fork": https://github.com/ghc-proposals/ghc-proposals#review-criteria https://github.com/ghc-proposals/ghc-proposals#review-criteria . Yes there are plenty of extensions that don't fit this criteria, but they tend to be either special-purpose extensions for things like low-level programming, building DSLs, or for backwards compatibility, rather than extensions we would expect people to routinely enable.
Does that apply in this case? Well, perhaps the extensions are not technically incompatible, but they're "at odds" as Arnaud puts it.
Another way to frame the original question might be: which of these extensions do we expect to include in GHC2023 (or GHC2024 or whatever it ends up being)? GHC2021 already has ScopedTypeVariables. We did decide (if I recall correctly) that we might remove things from future GHCXXXX sets, so are we going to remove ExtendedForAllScope and add TypeAbstractions from some future GHCXXXX, or just add TypeAbstractions?
I'm not expressing a preference one way or the other, just that we should decide where this is going.
Cheers Simon
Very specifically answering Simon M's concern: I see ExtendedForAllScope as a dead end, yes. It's included as a way of supporting the gobs and gobs and gobs of code that use today's ScopedTypeVariables, but at t=∞, we should get rid of it. Note that an optional extra https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04... introduces a @(..) syntax that makes TypeAbstractions significantly less repetitive, and thus about as easy to use as ExtendedForAllScope (which, recall, requires an explicit forall where there might otherwise be none).
Richard
PS: I'm on holiday starting tomorrow and so may not respond for about two weeks. Back in action on the 15th, but expect a few days of digging out. _______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org mailto:ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

That all sounds reasonable to me. I suggest: * Let's mention in the proposal that ExtendedForAllScope exists for legacy reasons and that we intend to recommend TypeAbstractions as the canonical way to bind type variables in the future (is that the right wording? we're not ready to actually recommend it yet?). * When this is implemented, let's have wording to the same effect in the manual. Someone writing new code would want to know which way is likely to be the more future-proof alternative.
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
Definitely - warnings and/or HLint for stylistic choices is the right way
to do it.
Cheers
Simon
On Mon, 4 Apr 2022 at 21:15, Richard Eisenberg
Thanks for reminding us of that definition in our review criteria -- it's helpful.
I would say that every extension in this proposal fits the standard, except for ExtendedForAllScope. That is, I would be happy for the following extensions (as described in this proposal) to be part of a standard: - PatternSignatures - PatternSignatureBinds - MethodTypeVariables (though John Ericson makes a comment on GitHub which suggests that this, too, may want revision -- I'm not fully convinced yet) - ImplicitForAll - TypeAbstractions (and ExtendedLet, but that's not being debated at the moment)
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
That logic might suggest revisiting #285 (which introduced NoImplicitForAll and NoPatternSignatureBinds), instead wishing for these to become warnings, rather than language extensions. (NB: #285 is accepted, but not implemented.)
Regarding GHCXXXX: Yes, I think we would end up removing ExtendedForAllScope from it -- or at least I would advocate for doing so. Indeed, when we considered ScopedTypeVariables as a candidate for GHCXXXX, I was worried about getting stuck with it, and I believe it was important to me that we had the option to remove, later.
Richard
On Apr 4, 2022, at 3:38 PM, Simon Marlow
wrote: On Mon, 4 Apr 2022 at 18:17, Richard Eisenberg
wrote: Thanks for kicking off this conversation, Arnaud!
To be clear in this thread: I'm fine delaying the discussion of section 6-8 until later.
Arnaud brings up my new principles in his initial email. Do please consider these principles as part of the deliberations, as they will become principles that we, as a committee, will have adopted.
About extensions: We, as a community and as a committee, have not come to terms with the two possible interpretations of extensions. I would like to say that, ideally, extensions are candidates for eventual inclusion. However, that is neither the current practice nor our trendline. Examples: - any flags included in Haskell98 (including, for example, MonomorphismRestriction). These are definitely settings that one can choose per module. If they were candidates for inclusion, they wouldn't exist (because they're already included!). - RebindableSyntax (though this is not one to mimic) - MagicHash. My interpretation is that this extension is meant to allow users to explicitly opt into low-level code. - Recently accepted #285 https://github.com/ghc-proposals/ghc-proposals/pull/285, which introduces two new -XNo... extensions (both also included in #448). As a practical matter, then, extensions are means of customization. We might imagine a debate where we try to change this, and then come up with a way to get from where we are to that changed future.
I think we actually did come to some agreement on the interpretation of extensions, it's in our review criteria under "does not create a language fork": https://github.com/ghc-proposals/ghc-proposals#review-criteria . Yes there are plenty of extensions that don't fit this criteria, but they tend to be either special-purpose extensions for things like low-level programming, building DSLs, or for backwards compatibility, rather than extensions we would expect people to routinely enable.
Does that apply in this case? Well, perhaps the extensions are not technically incompatible, but they're "at odds" as Arnaud puts it.
Another way to frame the original question might be: which of these extensions do we expect to include in GHC2023 (or GHC2024 or whatever it ends up being)? GHC2021 already has ScopedTypeVariables. We did decide (if I recall correctly) that we might remove things from future GHCXXXX sets, so are we going to remove ExtendedForAllScope and add TypeAbstractions from some future GHCXXXX, or just add TypeAbstractions?
I'm not expressing a preference one way or the other, just that we should decide where this is going.
Cheers Simon
Very specifically answering Simon M's concern: I see ExtendedForAllScope
as a dead end, yes. It's included as a way of supporting the gobs and gobs and gobs of code that use today's ScopedTypeVariables, but at t=∞, we should get rid of it. Note that an optional extra https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04... introduces a @(..) syntax that makes TypeAbstractions significantly less repetitive, and thus about as easy to use as ExtendedForAllScope (which, recall, requires an explicit forall where there might otherwise be none).
Richard
PS: I'm on holiday starting tomorrow and so may not respond for about two weeks. Back in action on the 15th, but expect a few days of digging out. _______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

Dear all, There has been no discussion of the principles so far. May I ask you what you think of the principles introduced by the proposal (I recommend reading the diff of `principles.rst` in raw form, the visual diff doesn't seem to work properly for me). Here is what I said about them in my initial email The proposal adds new principles to the `principles.rst` files which inform
the changes proposed, of these, I have the following comments: - The Visibility Orthogonality Principle doesn't seem to have a very clear definition. It may be a sign that it's not something that is so important - The Explicit Binding Principle says that we need to be able to enforce that all type variables have a binding site. I think it's a bit strong: I would like Haskell to let me write a binding site for every type variable, but not necessarily to error out when that doesn't happen. That being said, I'm happy with warnings to help me along the way, but I don't think that this Explicit Binding Principle should be phrased in a way that requires adding extensions to control this behaviour. - The Contiguous Scoping Principle, which states that a binder binds in one contiguous region sounds dubious to me. I don't see a particular reason for this to be.
I think that the Explicit Binding Principle has implicitly been discussed
in the thread about warnings above. There are other principles that Richard
proposes, which I all find I agree with.
Best,
Arnaud
On Tue, Apr 5, 2022 at 3:43 PM Simon Marlow
That all sounds reasonable to me. I suggest:
* Let's mention in the proposal that ExtendedForAllScope exists for legacy reasons and that we intend to recommend TypeAbstractions as the canonical way to bind type variables in the future (is that the right wording? we're not ready to actually recommend it yet?). * When this is implemented, let's have wording to the same effect in the manual. Someone writing new code would want to know which way is likely to be the more future-proof alternative.
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
Definitely - warnings and/or HLint for stylistic choices is the right way to do it.
Cheers Simon
On Mon, 4 Apr 2022 at 21:15, Richard Eisenberg
wrote: Thanks for reminding us of that definition in our review criteria -- it's helpful.
I would say that every extension in this proposal fits the standard, except for ExtendedForAllScope. That is, I would be happy for the following extensions (as described in this proposal) to be part of a standard: - PatternSignatures - PatternSignatureBinds - MethodTypeVariables (though John Ericson makes a comment on GitHub which suggests that this, too, may want revision -- I'm not fully convinced yet) - ImplicitForAll - TypeAbstractions (and ExtendedLet, but that's not being debated at the moment)
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
That logic might suggest revisiting #285 (which introduced NoImplicitForAll and NoPatternSignatureBinds), instead wishing for these to become warnings, rather than language extensions. (NB: #285 is accepted, but not implemented.)
Regarding GHCXXXX: Yes, I think we would end up removing ExtendedForAllScope from it -- or at least I would advocate for doing so. Indeed, when we considered ScopedTypeVariables as a candidate for GHCXXXX, I was worried about getting stuck with it, and I believe it was important to me that we had the option to remove, later.
Richard
On Apr 4, 2022, at 3:38 PM, Simon Marlow
wrote: On Mon, 4 Apr 2022 at 18:17, Richard Eisenberg
wrote: Thanks for kicking off this conversation, Arnaud!
To be clear in this thread: I'm fine delaying the discussion of section 6-8 until later.
Arnaud brings up my new principles in his initial email. Do please consider these principles as part of the deliberations, as they will become principles that we, as a committee, will have adopted.
About extensions: We, as a community and as a committee, have not come to terms with the two possible interpretations of extensions. I would like to say that, ideally, extensions are candidates for eventual inclusion. However, that is neither the current practice nor our trendline. Examples: - any flags included in Haskell98 (including, for example, MonomorphismRestriction). These are definitely settings that one can choose per module. If they were candidates for inclusion, they wouldn't exist (because they're already included!). - RebindableSyntax (though this is not one to mimic) - MagicHash. My interpretation is that this extension is meant to allow users to explicitly opt into low-level code. - Recently accepted #285 https://github.com/ghc-proposals/ghc-proposals/pull/285, which introduces two new -XNo... extensions (both also included in #448). As a practical matter, then, extensions are means of customization. We might imagine a debate where we try to change this, and then come up with a way to get from where we are to that changed future.
I think we actually did come to some agreement on the interpretation of extensions, it's in our review criteria under "does not create a language fork": https://github.com/ghc-proposals/ghc-proposals#review-criteria . Yes there are plenty of extensions that don't fit this criteria, but they tend to be either special-purpose extensions for things like low-level programming, building DSLs, or for backwards compatibility, rather than extensions we would expect people to routinely enable.
Does that apply in this case? Well, perhaps the extensions are not technically incompatible, but they're "at odds" as Arnaud puts it.
Another way to frame the original question might be: which of these extensions do we expect to include in GHC2023 (or GHC2024 or whatever it ends up being)? GHC2021 already has ScopedTypeVariables. We did decide (if I recall correctly) that we might remove things from future GHCXXXX sets, so are we going to remove ExtendedForAllScope and add TypeAbstractions from some future GHCXXXX, or just add TypeAbstractions?
I'm not expressing a preference one way or the other, just that we should decide where this is going.
Cheers Simon
Very specifically answering Simon M's concern: I see ExtendedForAllScope
as a dead end, yes. It's included as a way of supporting the gobs and gobs and gobs of code that use today's ScopedTypeVariables, but at t=∞, we should get rid of it. Note that an optional extra https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04... introduces a @(..) syntax that makes TypeAbstractions significantly less repetitive, and thus about as easy to use as ExtendedForAllScope (which, recall, requires an explicit forall where there might otherwise be none).
Richard
PS: I'm on holiday starting tomorrow and so may not respond for about two weeks. Back in action on the 15th, but expect a few days of digging out. _______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

I'm OK with them provided we do not get into later discussions like "this
proposal violates the X principle, so we should reject it". The principles
doc says only "Proposals following these principles are more likely to be
accepted" which is fine. I just don't want them to bind us completely in
future.
I agree that having the principles gives a us a language and framework for
debate, and so is useful.
Simon
On Fri, 15 Apr 2022 at 15:01, Spiwack, Arnaud
Dear all,
There has been no discussion of the principles so far. May I ask you what you think of the principles introduced by the proposal (I recommend reading the diff of `principles.rst` in raw form, the visual diff doesn't seem to work properly for me).
Here is what I said about them in my initial email
The proposal adds new principles to the `principles.rst` files which
inform the changes proposed, of these, I have the following comments: - The Visibility Orthogonality Principle doesn't seem to have a very clear definition. It may be a sign that it's not something that is so important - The Explicit Binding Principle says that we need to be able to enforce that all type variables have a binding site. I think it's a bit strong: I would like Haskell to let me write a binding site for every type variable, but not necessarily to error out when that doesn't happen. That being said, I'm happy with warnings to help me along the way, but I don't think that this Explicit Binding Principle should be phrased in a way that requires adding extensions to control this behaviour. - The Contiguous Scoping Principle, which states that a binder binds in one contiguous region sounds dubious to me. I don't see a particular reason for this to be.
I think that the Explicit Binding Principle has implicitly been discussed in the thread about warnings above. There are other principles that Richard proposes, which I all find I agree with.
Best, Arnaud
On Tue, Apr 5, 2022 at 3:43 PM Simon Marlow
wrote: That all sounds reasonable to me. I suggest:
* Let's mention in the proposal that ExtendedForAllScope exists for legacy reasons and that we intend to recommend TypeAbstractions as the canonical way to bind type variables in the future (is that the right wording? we're not ready to actually recommend it yet?). * When this is implemented, let's have wording to the same effect in the manual. Someone writing new code would want to know which way is likely to be the more future-proof alternative.
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
Definitely - warnings and/or HLint for stylistic choices is the right way to do it.
Cheers Simon
On Mon, 4 Apr 2022 at 21:15, Richard Eisenberg
wrote: Thanks for reminding us of that definition in our review criteria -- it's helpful.
I would say that every extension in this proposal fits the standard, except for ExtendedForAllScope. That is, I would be happy for the following extensions (as described in this proposal) to be part of a standard: - PatternSignatures - PatternSignatureBinds - MethodTypeVariables (though John Ericson makes a comment on GitHub which suggests that this, too, may want revision -- I'm not fully convinced yet) - ImplicitForAll - TypeAbstractions (and ExtendedLet, but that's not being debated at the moment)
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
That logic might suggest revisiting #285 (which introduced NoImplicitForAll and NoPatternSignatureBinds), instead wishing for these to become warnings, rather than language extensions. (NB: #285 is accepted, but not implemented.)
Regarding GHCXXXX: Yes, I think we would end up removing ExtendedForAllScope from it -- or at least I would advocate for doing so. Indeed, when we considered ScopedTypeVariables as a candidate for GHCXXXX, I was worried about getting stuck with it, and I believe it was important to me that we had the option to remove, later.
Richard
On Apr 4, 2022, at 3:38 PM, Simon Marlow
wrote: On Mon, 4 Apr 2022 at 18:17, Richard Eisenberg
wrote: Thanks for kicking off this conversation, Arnaud!
To be clear in this thread: I'm fine delaying the discussion of section 6-8 until later.
Arnaud brings up my new principles in his initial email. Do please consider these principles as part of the deliberations, as they will become principles that we, as a committee, will have adopted.
About extensions: We, as a community and as a committee, have not come to terms with the two possible interpretations of extensions. I would like to say that, ideally, extensions are candidates for eventual inclusion. However, that is neither the current practice nor our trendline. Examples: - any flags included in Haskell98 (including, for example, MonomorphismRestriction). These are definitely settings that one can choose per module. If they were candidates for inclusion, they wouldn't exist (because they're already included!). - RebindableSyntax (though this is not one to mimic) - MagicHash. My interpretation is that this extension is meant to allow users to explicitly opt into low-level code. - Recently accepted #285 https://github.com/ghc-proposals/ghc-proposals/pull/285, which introduces two new -XNo... extensions (both also included in #448). As a practical matter, then, extensions are means of customization. We might imagine a debate where we try to change this, and then come up with a way to get from where we are to that changed future.
I think we actually did come to some agreement on the interpretation of extensions, it's in our review criteria under "does not create a language fork": https://github.com/ghc-proposals/ghc-proposals#review-criteria . Yes there are plenty of extensions that don't fit this criteria, but they tend to be either special-purpose extensions for things like low-level programming, building DSLs, or for backwards compatibility, rather than extensions we would expect people to routinely enable.
Does that apply in this case? Well, perhaps the extensions are not technically incompatible, but they're "at odds" as Arnaud puts it.
Another way to frame the original question might be: which of these extensions do we expect to include in GHC2023 (or GHC2024 or whatever it ends up being)? GHC2021 already has ScopedTypeVariables. We did decide (if I recall correctly) that we might remove things from future GHCXXXX sets, so are we going to remove ExtendedForAllScope and add TypeAbstractions from some future GHCXXXX, or just add TypeAbstractions?
I'm not expressing a preference one way or the other, just that we should decide where this is going.
Cheers Simon
Very specifically answering Simon M's concern: I see ExtendedForAllScope
as a dead end, yes. It's included as a way of supporting the gobs and gobs and gobs of code that use today's ScopedTypeVariables, but at t=∞, we should get rid of it. Note that an optional extra https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04... introduces a @(..) syntax that makes TypeAbstractions significantly less repetitive, and thus about as easy to use as ExtendedForAllScope (which, recall, requires an explicit forall where there might otherwise be none).
Richard
PS: I'm on holiday starting tomorrow and so may not respond for about two weeks. Back in action on the 15th, but expect a few days of digging out. _______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
_______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

Any other opinion? Only a few of us have participated in this thread: Tom, Joachim, Vlad, Eric, Chris, and Baldur, I'd love to hear from you. Do these principles make sense to you, or should they be rephrased? Do you agree with all of them? On Mon, Apr 18, 2022 at 9:51 AM Simon Peyton Jones < simon.peytonjones@gmail.com> wrote:
I'm OK with them provided we do not get into later discussions like "this proposal violates the X principle, so we should reject it". The principles doc says only "Proposals following these principles are more likely to be accepted" which is fine. I just don't want them to bind us completely in future.
I agree that having the principles gives a us a language and framework for debate, and so is useful.
Simon
On Fri, 15 Apr 2022 at 15:01, Spiwack, Arnaud
wrote: Dear all,
There has been no discussion of the principles so far. May I ask you what you think of the principles introduced by the proposal (I recommend reading the diff of `principles.rst` in raw form, the visual diff doesn't seem to work properly for me).
Here is what I said about them in my initial email
The proposal adds new principles to the `principles.rst` files which
inform the changes proposed, of these, I have the following comments: - The Visibility Orthogonality Principle doesn't seem to have a very clear definition. It may be a sign that it's not something that is so important - The Explicit Binding Principle says that we need to be able to enforce that all type variables have a binding site. I think it's a bit strong: I would like Haskell to let me write a binding site for every type variable, but not necessarily to error out when that doesn't happen. That being said, I'm happy with warnings to help me along the way, but I don't think that this Explicit Binding Principle should be phrased in a way that requires adding extensions to control this behaviour. - The Contiguous Scoping Principle, which states that a binder binds in one contiguous region sounds dubious to me. I don't see a particular reason for this to be.
I think that the Explicit Binding Principle has implicitly been discussed in the thread about warnings above. There are other principles that Richard proposes, which I all find I agree with.
Best, Arnaud
On Tue, Apr 5, 2022 at 3:43 PM Simon Marlow
wrote: That all sounds reasonable to me. I suggest:
* Let's mention in the proposal that ExtendedForAllScope exists for legacy reasons and that we intend to recommend TypeAbstractions as the canonical way to bind type variables in the future (is that the right wording? we're not ready to actually recommend it yet?). * When this is implemented, let's have wording to the same effect in the manual. Someone writing new code would want to know which way is likely to be the more future-proof alternative.
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
Definitely - warnings and/or HLint for stylistic choices is the right way to do it.
Cheers Simon
On Mon, 4 Apr 2022 at 21:15, Richard Eisenberg
wrote: Thanks for reminding us of that definition in our review criteria -- it's helpful.
I would say that every extension in this proposal fits the standard, except for ExtendedForAllScope. That is, I would be happy for the following extensions (as described in this proposal) to be part of a standard: - PatternSignatures - PatternSignatureBinds - MethodTypeVariables (though John Ericson makes a comment on GitHub which suggests that this, too, may want revision -- I'm not fully convinced yet) - ImplicitForAll - TypeAbstractions (and ExtendedLet, but that's not being debated at the moment)
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
That logic might suggest revisiting #285 (which introduced NoImplicitForAll and NoPatternSignatureBinds), instead wishing for these to become warnings, rather than language extensions. (NB: #285 is accepted, but not implemented.)
Regarding GHCXXXX: Yes, I think we would end up removing ExtendedForAllScope from it -- or at least I would advocate for doing so. Indeed, when we considered ScopedTypeVariables as a candidate for GHCXXXX, I was worried about getting stuck with it, and I believe it was important to me that we had the option to remove, later.
Richard
On Apr 4, 2022, at 3:38 PM, Simon Marlow
wrote: On Mon, 4 Apr 2022 at 18:17, Richard Eisenberg
wrote: Thanks for kicking off this conversation, Arnaud!
To be clear in this thread: I'm fine delaying the discussion of section 6-8 until later.
Arnaud brings up my new principles in his initial email. Do please consider these principles as part of the deliberations, as they will become principles that we, as a committee, will have adopted.
About extensions: We, as a community and as a committee, have not come to terms with the two possible interpretations of extensions. I would like to say that, ideally, extensions are candidates for eventual inclusion. However, that is neither the current practice nor our trendline. Examples: - any flags included in Haskell98 (including, for example, MonomorphismRestriction). These are definitely settings that one can choose per module. If they were candidates for inclusion, they wouldn't exist (because they're already included!). - RebindableSyntax (though this is not one to mimic) - MagicHash. My interpretation is that this extension is meant to allow users to explicitly opt into low-level code. - Recently accepted #285 https://github.com/ghc-proposals/ghc-proposals/pull/285, which introduces two new -XNo... extensions (both also included in #448). As a practical matter, then, extensions are means of customization. We might imagine a debate where we try to change this, and then come up with a way to get from where we are to that changed future.
I think we actually did come to some agreement on the interpretation of extensions, it's in our review criteria under "does not create a language fork": https://github.com/ghc-proposals/ghc-proposals#review-criteria . Yes there are plenty of extensions that don't fit this criteria, but they tend to be either special-purpose extensions for things like low-level programming, building DSLs, or for backwards compatibility, rather than extensions we would expect people to routinely enable.
Does that apply in this case? Well, perhaps the extensions are not technically incompatible, but they're "at odds" as Arnaud puts it.
Another way to frame the original question might be: which of these extensions do we expect to include in GHC2023 (or GHC2024 or whatever it ends up being)? GHC2021 already has ScopedTypeVariables. We did decide (if I recall correctly) that we might remove things from future GHCXXXX sets, so are we going to remove ExtendedForAllScope and add TypeAbstractions from some future GHCXXXX, or just add TypeAbstractions?
I'm not expressing a preference one way or the other, just that we should decide where this is going.
Cheers Simon
Very specifically answering Simon M's concern: I see
ExtendedForAllScope as a dead end, yes. It's included as a way of supporting the gobs and gobs and gobs of code that use today's ScopedTypeVariables, but at t=∞, we should get rid of it. Note that an optional extra https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04... introduces a @(..) syntax that makes TypeAbstractions significantly less repetitive, and thus about as easy to use as ExtendedForAllScope (which, recall, requires an explicit forall where there might otherwise be none).
Richard
PS: I'm on holiday starting tomorrow and so may not respond for about two weeks. Back in action on the 15th, but expect a few days of digging out. _______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org
https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
_______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

Dear all,
I feel blocked here. I don't know how to make progress. Part of the goal of
this proposal is to elicit debate, and so far it has failed to.
Simon PJ says that the principles “bind us completely in future”. But I'd
argue that we still advertise them as desirable. Things we want to get
better at in the future. So a proposal saying “it makes GHC better at
the Contiguous
Scoping Principle” is well-justified enough. Is it what we want? That's the
question.
On Fri, Apr 22, 2022 at 8:37 AM Spiwack, Arnaud
Any other opinion? Only a few of us have participated in this thread: Tom, Joachim, Vlad, Eric, Chris, and Baldur, I'd love to hear from you. Do these principles make sense to you, or should they be rephrased? Do you agree with all of them?
On Mon, Apr 18, 2022 at 9:51 AM Simon Peyton Jones < simon.peytonjones@gmail.com> wrote:
I'm OK with them provided we do not get into later discussions like "this proposal violates the X principle, so we should reject it". The principles doc says only "Proposals following these principles are more likely to be accepted" which is fine. I just don't want them to bind us completely in future.
I agree that having the principles gives a us a language and framework for debate, and so is useful.
Simon
On Fri, 15 Apr 2022 at 15:01, Spiwack, Arnaud
wrote: Dear all,
There has been no discussion of the principles so far. May I ask you what you think of the principles introduced by the proposal (I recommend reading the diff of `principles.rst` in raw form, the visual diff doesn't seem to work properly for me).
Here is what I said about them in my initial email
The proposal adds new principles to the `principles.rst` files which
inform the changes proposed, of these, I have the following comments: - The Visibility Orthogonality Principle doesn't seem to have a very clear definition. It may be a sign that it's not something that is so important - The Explicit Binding Principle says that we need to be able to enforce that all type variables have a binding site. I think it's a bit strong: I would like Haskell to let me write a binding site for every type variable, but not necessarily to error out when that doesn't happen. That being said, I'm happy with warnings to help me along the way, but I don't think that this Explicit Binding Principle should be phrased in a way that requires adding extensions to control this behaviour. - The Contiguous Scoping Principle, which states that a binder binds in one contiguous region sounds dubious to me. I don't see a particular reason for this to be.
I think that the Explicit Binding Principle has implicitly been discussed in the thread about warnings above. There are other principles that Richard proposes, which I all find I agree with.
Best, Arnaud
On Tue, Apr 5, 2022 at 3:43 PM Simon Marlow
wrote: That all sounds reasonable to me. I suggest:
* Let's mention in the proposal that ExtendedForAllScope exists for legacy reasons and that we intend to recommend TypeAbstractions as the canonical way to bind type variables in the future (is that the right wording? we're not ready to actually recommend it yet?). * When this is implemented, let's have wording to the same effect in the manual. Someone writing new code would want to know which way is likely to be the more future-proof alternative.
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
Definitely - warnings and/or HLint for stylistic choices is the right way to do it.
Cheers Simon
On Mon, 4 Apr 2022 at 21:15, Richard Eisenberg
wrote: Thanks for reminding us of that definition in our review criteria -- it's helpful.
I would say that every extension in this proposal fits the standard, except for ExtendedForAllScope. That is, I would be happy for the following extensions (as described in this proposal) to be part of a standard: - PatternSignatures - PatternSignatureBinds - MethodTypeVariables (though John Ericson makes a comment on GitHub which suggests that this, too, may want revision -- I'm not fully convinced yet) - ImplicitForAll - TypeAbstractions (and ExtendedLet, but that's not being debated at the moment)
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
That logic might suggest revisiting #285 (which introduced NoImplicitForAll and NoPatternSignatureBinds), instead wishing for these to become warnings, rather than language extensions. (NB: #285 is accepted, but not implemented.)
Regarding GHCXXXX: Yes, I think we would end up removing ExtendedForAllScope from it -- or at least I would advocate for doing so. Indeed, when we considered ScopedTypeVariables as a candidate for GHCXXXX, I was worried about getting stuck with it, and I believe it was important to me that we had the option to remove, later.
Richard
On Apr 4, 2022, at 3:38 PM, Simon Marlow
wrote: On Mon, 4 Apr 2022 at 18:17, Richard Eisenberg
wrote: Thanks for kicking off this conversation, Arnaud!
To be clear in this thread: I'm fine delaying the discussion of section 6-8 until later.
Arnaud brings up my new principles in his initial email. Do please consider these principles as part of the deliberations, as they will become principles that we, as a committee, will have adopted.
About extensions: We, as a community and as a committee, have not come to terms with the two possible interpretations of extensions. I would like to say that, ideally, extensions are candidates for eventual inclusion. However, that is neither the current practice nor our trendline. Examples: - any flags included in Haskell98 (including, for example, MonomorphismRestriction). These are definitely settings that one can choose per module. If they were candidates for inclusion, they wouldn't exist (because they're already included!). - RebindableSyntax (though this is not one to mimic) - MagicHash. My interpretation is that this extension is meant to allow users to explicitly opt into low-level code. - Recently accepted #285 https://github.com/ghc-proposals/ghc-proposals/pull/285, which introduces two new -XNo... extensions (both also included in #448). As a practical matter, then, extensions are means of customization. We might imagine a debate where we try to change this, and then come up with a way to get from where we are to that changed future.
I think we actually did come to some agreement on the interpretation of extensions, it's in our review criteria under "does not create a language fork": https://github.com/ghc-proposals/ghc-proposals#review-criteria . Yes there are plenty of extensions that don't fit this criteria, but they tend to be either special-purpose extensions for things like low-level programming, building DSLs, or for backwards compatibility, rather than extensions we would expect people to routinely enable.
Does that apply in this case? Well, perhaps the extensions are not technically incompatible, but they're "at odds" as Arnaud puts it.
Another way to frame the original question might be: which of these extensions do we expect to include in GHC2023 (or GHC2024 or whatever it ends up being)? GHC2021 already has ScopedTypeVariables. We did decide (if I recall correctly) that we might remove things from future GHCXXXX sets, so are we going to remove ExtendedForAllScope and add TypeAbstractions from some future GHCXXXX, or just add TypeAbstractions?
I'm not expressing a preference one way or the other, just that we should decide where this is going.
Cheers Simon
Very specifically answering Simon M's concern: I see
ExtendedForAllScope as a dead end, yes. It's included as a way of supporting the gobs and gobs and gobs of code that use today's ScopedTypeVariables, but at t=∞, we should get rid of it. Note that an optional extra https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04... introduces a @(..) syntax that makes TypeAbstractions significantly less repetitive, and thus about as easy to use as ExtendedForAllScope (which, recall, requires an explicit forall where there might otherwise be none).
Richard
PS: I'm on holiday starting tomorrow and so may not respond for about two weeks. Back in action on the 15th, but expect a few days of digging out. _______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org
https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
_______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

I feel blocked here. I don't know how to make progress. Part of the goal
of this proposal is to elicit debate, and so far it has failed to
I think that:
1. Section 6-8 (about let in types etc) are controversial, and
explicitly not under debate. *Action*:* @rae *would you like to remove
them to another proposal?
2. The rest of the main proposal
https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04...seems
to have broad support, modulo some concerns about flags and forks. *Action:
Tom, Joachim, Vlad, Eric, Chris, and Baldur*: please express an opinion.
Can you do so this week please? You don't need to wait for (1); just
ignore section 6-8.
3. The proposal *also *makes a significant diff to the principles.rst
document
https://github.com/goldfirere/ghc-proposals/blob/type-variables/principles.r...,
mostly expanding and clarifying points that were previously just a sentence
or two. (Here's the old version
https://github.com/goldfirere/ghc-proposals/blob/principles/principles.rst.)
*Action: Tom, Joachim, Vlad, Eric, Chris, and Baldur*: please express an
opinion.
4. *Action @rae*: there has been some discussion about flags and forks.
Would you like to make whatever resolution you think is appropriate, in the
light of this conversation, and let us know what is?
Let's get this over the line. I don't think there is any serious
disagreement, and we have an obligation to authors to give their work our
timely attention.
Simon
On Wed, 1 Jun 2022 at 10:53, Spiwack, Arnaud
Dear all,
I feel blocked here. I don't know how to make progress. Part of the goal of this proposal is to elicit debate, and so far it has failed to.
Simon PJ says that the principles “bind us completely in future”. But I'd argue that we still advertise them as desirable. Things we want to get better at in the future. So a proposal saying “it makes GHC better at the Contiguous Scoping Principle” is well-justified enough. Is it what we want? That's the question.
On Fri, Apr 22, 2022 at 8:37 AM Spiwack, Arnaud
wrote: Any other opinion? Only a few of us have participated in this thread: Tom, Joachim, Vlad, Eric, Chris, and Baldur, I'd love to hear from you. Do these principles make sense to you, or should they be rephrased? Do you agree with all of them?
On Mon, Apr 18, 2022 at 9:51 AM Simon Peyton Jones < simon.peytonjones@gmail.com> wrote:
I'm OK with them provided we do not get into later discussions like "this proposal violates the X principle, so we should reject it". The principles doc says only "Proposals following these principles are more likely to be accepted" which is fine. I just don't want them to bind us completely in future.
I agree that having the principles gives a us a language and framework for debate, and so is useful.
Simon
On Fri, 15 Apr 2022 at 15:01, Spiwack, Arnaud
wrote: Dear all,
There has been no discussion of the principles so far. May I ask you what you think of the principles introduced by the proposal (I recommend reading the diff of `principles.rst` in raw form, the visual diff doesn't seem to work properly for me).
Here is what I said about them in my initial email
The proposal adds new principles to the `principles.rst` files which
inform the changes proposed, of these, I have the following comments: - The Visibility Orthogonality Principle doesn't seem to have a very clear definition. It may be a sign that it's not something that is so important - The Explicit Binding Principle says that we need to be able to enforce that all type variables have a binding site. I think it's a bit strong: I would like Haskell to let me write a binding site for every type variable, but not necessarily to error out when that doesn't happen. That being said, I'm happy with warnings to help me along the way, but I don't think that this Explicit Binding Principle should be phrased in a way that requires adding extensions to control this behaviour. - The Contiguous Scoping Principle, which states that a binder binds in one contiguous region sounds dubious to me. I don't see a particular reason for this to be.
I think that the Explicit Binding Principle has implicitly been discussed in the thread about warnings above. There are other principles that Richard proposes, which I all find I agree with.
Best, Arnaud
On Tue, Apr 5, 2022 at 3:43 PM Simon Marlow
wrote: That all sounds reasonable to me. I suggest:
* Let's mention in the proposal that ExtendedForAllScope exists for legacy reasons and that we intend to recommend TypeAbstractions as the canonical way to bind type variables in the future (is that the right wording? we're not ready to actually recommend it yet?). * When this is implemented, let's have wording to the same effect in the manual. Someone writing new code would want to know which way is likely to be the more future-proof alternative.
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
Definitely - warnings and/or HLint for stylistic choices is the right way to do it.
Cheers Simon
On Mon, 4 Apr 2022 at 21:15, Richard Eisenberg
wrote: Thanks for reminding us of that definition in our review criteria -- it's helpful.
I would say that every extension in this proposal fits the standard, except for ExtendedForAllScope. That is, I would be happy for the following extensions (as described in this proposal) to be part of a standard: - PatternSignatures - PatternSignatureBinds - MethodTypeVariables (though John Ericson makes a comment on GitHub which suggests that this, too, may want revision -- I'm not fully convinced yet) - ImplicitForAll - TypeAbstractions (and ExtendedLet, but that's not being debated at the moment)
Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
That logic might suggest revisiting #285 (which introduced NoImplicitForAll and NoPatternSignatureBinds), instead wishing for these to become warnings, rather than language extensions. (NB: #285 is accepted, but not implemented.)
Regarding GHCXXXX: Yes, I think we would end up removing ExtendedForAllScope from it -- or at least I would advocate for doing so. Indeed, when we considered ScopedTypeVariables as a candidate for GHCXXXX, I was worried about getting stuck with it, and I believe it was important to me that we had the option to remove, later.
Richard
On Apr 4, 2022, at 3:38 PM, Simon Marlow
wrote: On Mon, 4 Apr 2022 at 18:17, Richard Eisenberg
wrote: > Thanks for kicking off this conversation, Arnaud! > > To be clear in this thread: I'm fine delaying the discussion of > section 6-8 until later. > > Arnaud brings up my new principles in his initial email. Do please > consider these principles as part of the deliberations, as they will become > principles that we, as a committee, will have adopted. > > About extensions: We, as a community and as a committee, have not > come to terms with the two possible interpretations of extensions. I would > like to say that, ideally, extensions are candidates for eventual > inclusion. However, that is neither the current practice nor our trendline. > Examples: > - any flags included in Haskell98 (including, for example, > MonomorphismRestriction). These are definitely settings that one can choose > per module. If they were candidates for inclusion, they wouldn't exist > (because they're already included!). > - RebindableSyntax (though this is not one to mimic) > - MagicHash. My interpretation is that this extension is meant to > allow users to explicitly opt into low-level code. > - Recently accepted #285 > https://github.com/ghc-proposals/ghc-proposals/pull/285, which > introduces two new -XNo... extensions (both also included in #448). > As a practical matter, then, extensions are means of customization. > We might imagine a debate where we try to change this, and then come up > with a way to get from where we are to that changed future. >
I think we actually did come to some agreement on the interpretation of extensions, it's in our review criteria under "does not create a language fork": https://github.com/ghc-proposals/ghc-proposals#review-criteria . Yes there are plenty of extensions that don't fit this criteria, but they tend to be either special-purpose extensions for things like low-level programming, building DSLs, or for backwards compatibility, rather than extensions we would expect people to routinely enable.
Does that apply in this case? Well, perhaps the extensions are not technically incompatible, but they're "at odds" as Arnaud puts it.
Another way to frame the original question might be: which of these extensions do we expect to include in GHC2023 (or GHC2024 or whatever it ends up being)? GHC2021 already has ScopedTypeVariables. We did decide (if I recall correctly) that we might remove things from future GHCXXXX sets, so are we going to remove ExtendedForAllScope and add TypeAbstractions from some future GHCXXXX, or just add TypeAbstractions?
I'm not expressing a preference one way or the other, just that we should decide where this is going.
Cheers Simon
Very specifically answering Simon M's concern: I see > ExtendedForAllScope as a dead end, yes. It's included as a way of > supporting the gobs and gobs and gobs of code that use today's > ScopedTypeVariables, but at t=∞, we should get rid of it. Note that an optional > extra > https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04... introduces > a @(..) syntax that makes TypeAbstractions significantly less repetitive, > and thus about as easy to use as ExtendedForAllScope (which, recall, > requires an explicit forall where there might otherwise be none). > > Richard > > PS: I'm on holiday starting tomorrow and so may not respond for > about two weeks. Back in action on the 15th, but expect a few days of > digging out. > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee@haskell.org > > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
_______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

I have left a few comments and questions about the changes to the Principles on GitHub. I think I agree with the changes in spirit, my comments are mostly around clarifying and tightening the Principles. I also strongly agree with SPJ's stance that the Principles are guidelines, not laws. They should provide a framework for us to discuss and compare proposed changes, but they are not foolproof and they do not absolve us of our responsibility to exercise our judgment when deciding which proposals to accept. I will take a closer look at the main proposal this week, but Sections 1-5 look fine to me. On Mon, Jun 6, 2022, at 04:35, Simon Peyton Jones wrote:
I feel blocked here. I don't know how to make progress. Part of the goal of this proposal is to elicit debate, and so far it has failed to
I think that: 1. Section 6-8 (about let in types etc) are controversial, and explicitly not under debate. *Action*:* @rae *would you like to remove them to another proposal?
2. The rest of the main proposal https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04...seems to have broad support, modulo some concerns about flags and forks. *Action: Tom, Joachim, Vlad, Eric, Chris, and Baldur*: please express an opinion. Can you do so this week please? You don't need to wait for (1); just ignore section 6-8.
3. The proposal *also *makes a significant diff to the principles.rst document https://github.com/goldfirere/ghc-proposals/blob/type-variables/principles.r..., mostly expanding and clarifying points that were previously just a sentence or two. (Here's the old version https://github.com/goldfirere/ghc-proposals/blob/principles/principles.rst.) *Action: Tom, Joachim, Vlad, Eric, Chris, and Baldur*: please express an opinion.
4. *Action @rae*: there has been some discussion about flags and forks. Would you like to make whatever resolution you think is appropriate, in the light of this conversation, and let us know what is? Let's get this over the line. I don't think there is any serious disagreement, and we have an obligation to authors to give their work our timely attention.
Simon
On Wed, 1 Jun 2022 at 10:53, Spiwack, Arnaud
wrote: Dear all,
I feel blocked here. I don't know how to make progress. Part of the goal of this proposal is to elicit debate, and so far it has failed to.
Simon PJ says that the principles “bind us completely in future”. But I'd argue that we still advertise them as desirable. Things we want to get better at in the future. So a proposal saying “it makes GHC better at the Contiguous Scoping Principle” is well-justified enough. Is it what we want? That's the question.
On Fri, Apr 22, 2022 at 8:37 AM Spiwack, Arnaud
wrote: Any other opinion? Only a few of us have participated in this thread: Tom, Joachim, Vlad, Eric, Chris, and Baldur, I'd love to hear from you. Do these principles make sense to you, or should they be rephrased? Do you agree with all of them?
On Mon, Apr 18, 2022 at 9:51 AM Simon Peyton Jones
wrote: I'm OK with them provided we do not get into later discussions like "this proposal violates the X principle, so we should reject it". The principles doc says only "Proposals following these principles are more likely to be accepted" which is fine. I just don't want them to bind us completely in future.
I agree that having the principles gives a us a language and framework for debate, and so is useful.
Simon
On Fri, 15 Apr 2022 at 15:01, Spiwack, Arnaud
wrote: Dear all,
There has been no discussion of the principles so far. May I ask you what you think of the principles introduced by the proposal (I recommend reading the diff of `principles.rst` in raw form, the visual diff doesn't seem to work properly for me).
Here is what I said about them in my initial email
The proposal adds new principles to the `principles.rst` files which inform the changes proposed, of these, I have the following comments: - The Visibility Orthogonality Principle doesn't seem to have a very clear definition. It may be a sign that it's not something that is so important - The Explicit Binding Principle says that we need to be able to enforce that all type variables have a binding site. I think it's a bit strong: I would like Haskell to let me write a binding site for every type variable, but not necessarily to error out when that doesn't happen. That being said, I'm happy with warnings to help me along the way, but I don't think that this Explicit Binding Principle should be phrased in a way that requires adding extensions to control this behaviour. - The Contiguous Scoping Principle, which states that a binder binds in one contiguous region sounds dubious to me. I don't see a particular reason for this to be.
I think that the Explicit Binding Principle has implicitly been discussed in the thread about warnings above. There are other principles that Richard proposes, which I all find I agree with.
Best, Arnaud
On Tue, Apr 5, 2022 at 3:43 PM Simon Marlow
wrote: That all sounds reasonable to me. I suggest:
* Let's mention in the proposal that ExtendedForAllScope exists for legacy reasons and that we intend to recommend TypeAbstractions as the canonical way to bind type variables in the future (is that the right wording? we're not ready to actually recommend it yet?). * When this is implemented, let's have wording to the same effect in the manual. Someone writing new code would want to know which way is likely to be the more future-proof alternative.
> Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions.
Definitely - warnings and/or HLint for stylistic choices is the right way to do it.
Cheers Simon
On Mon, 4 Apr 2022 at 21:15, Richard Eisenberg
wrote: > Thanks for reminding us of that definition in our review criteria -- it's helpful. > > I would say that every extension in this proposal fits the standard, except for ExtendedForAllScope. That is, I would be happy for the following extensions (as described in this proposal) to be part of a standard: > - PatternSignatures > - PatternSignatureBinds > - MethodTypeVariables (though John Ericson makes a comment on GitHub which suggests that this, too, may want revision -- I'm not fully convinced yet) > - ImplicitForAll > - TypeAbstractions > (and ExtendedLet, but that's not being debated at the moment) > > Complicating this story is that some users (including me, at times) wish for GHC to do less for us: we would prefer not to have implicit foralls or to permit pattern-signature bindings. However, I suppose this desire could be accommodated by warnings and -Werror instead of language extensions. > > That logic might suggest revisiting #285 (which introduced NoImplicitForAll and NoPatternSignatureBinds), instead wishing for these to become warnings, rather than language extensions. (NB: #285 is accepted, but not implemented.) > > Regarding GHCXXXX: Yes, I think we would end up removing ExtendedForAllScope from it -- or at least I would advocate for doing so. Indeed, when we considered ScopedTypeVariables as a candidate for GHCXXXX, I was worried about getting stuck with it, and I believe it was important to me that we had the option to remove, later. > > Richard > >> On Apr 4, 2022, at 3:38 PM, Simon Marlow wrote: >> >> On Mon, 4 Apr 2022 at 18:17, Richard Eisenberg wrote: >>> Thanks for kicking off this conversation, Arnaud! >>> >>> To be clear in this thread: I'm fine delaying the discussion of section 6-8 until later. >>> >>> Arnaud brings up my new principles in his initial email. Do please consider these principles as part of the deliberations, as they will become principles that we, as a committee, will have adopted. >>> >>> About extensions: We, as a community and as a committee, have not come to terms with the two possible interpretations of extensions. I would like to say that, ideally, extensions are candidates for eventual inclusion. However, that is neither the current practice nor our trendline. Examples: >>> - any flags included in Haskell98 (including, for example, MonomorphismRestriction). These are definitely settings that one can choose per module. If they were candidates for inclusion, they wouldn't exist (because they're already included!). >>> - RebindableSyntax (though this is not one to mimic) >>> - MagicHash. My interpretation is that this extension is meant to allow users to explicitly opt into low-level code. >>> - Recently accepted #285 https://github.com/ghc-proposals/ghc-proposals/pull/285, which introduces two new -XNo... extensions (both also included in #448). >>> As a practical matter, then, extensions are means of customization. We might imagine a debate where we try to change this, and then come up with a way to get from where we are to that changed future. >> >> I think we actually did come to some agreement on the interpretation of extensions, it's in our review criteria under "does not create a language fork": https://github.com/ghc-proposals/ghc-proposals#review-criteria . Yes there are plenty of extensions that don't fit this criteria, but they tend to be either special-purpose extensions for things like low-level programming, building DSLs, or for backwards compatibility, rather than extensions we would expect people to routinely enable. >> >> Does that apply in this case? Well, perhaps the extensions are not technically incompatible, but they're "at odds" as Arnaud puts it. >> >> Another way to frame the original question might be: which of these extensions do we expect to include in GHC2023 (or GHC2024 or whatever it ends up being)? GHC2021 already has ScopedTypeVariables. We did decide (if I recall correctly) that we might remove things from future GHCXXXX sets, so are we going to remove ExtendedForAllScope and add TypeAbstractions from some future GHCXXXX, or just add TypeAbstractions? >> >> I'm not expressing a preference one way or the other, just that we should decide where this is going. >> >> Cheers >> Simon >> >>> Very specifically answering Simon M's concern: I see ExtendedForAllScope as a dead end, yes. It's included as a way of supporting the gobs and gobs and gobs of code that use today's ScopedTypeVariables, but at t=∞, we should get rid of it. Note that an optional extra https://github.com/goldfirere/ghc-proposals/blob/type-variables/proposals/04... introduces a @(..) syntax that makes TypeAbstractions significantly less repetitive, and thus about as easy to use as ExtendedForAllScope (which, recall, requires an explicit forall where there might otherwise be none). >>> >>> Richard >>> >>> PS: I'm on holiday starting tomorrow and so may not respond for about two weeks. Back in action on the 15th, but expect a few days of digging out. >>> _______________________________________________ >>> ghc-steering-committee mailing list >>> ghc-steering-committee@haskell.org >>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >
ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee
ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

Hi, it looks like there is a problem with the mailinglist and my email provider, and I did not receive all emails. Luckily we have the archive at https://mail.haskell.org/pipermail/ghc-steering-committee/2022-June/date.htm... and I noticed that Simon was nudging me personally to comment on #448.
2. The rest of the main proposal to have broad support, modulo some concerns about flags and forks. *Action: Tom, Joachim, Vlad, Eric, Chris, and Baldur*: please express an opinion. Can you do so this week please? You don't need to wait for (1); just ignore section 6-8.
I’m in favor of these things. They appear to be thought through, and move Haskell in a direction I’m in favor of, while catering for existing code. I hope we don’t block our way too much for a future where
It may be useful to write a variable occurrence to instantiate a universal argument
but I’ll accept that we’ll have to find syntax for that then, and that the way we approached it in #126 wasn’t great, because it didn’t uphold some of the principles we have identified since then. I would not mind making -XTypeAbstractions and -XExtendedForAllScope mutually exclusive, I think, but I guess the proposed heuristics which one applies works as well, and maybe it is easier for people to migrate if they can do it per-function, and not just per-module. So I’m ok with this. Also in favor of holding off @(..).
3. The proposal *also *makes a significant diff to the principles.rst document https://github.com/goldfirere/ghc-proposals/blob/type-variables/principles.r..., mostly expanding and clarifying points that were previously just a sentence or two. (Here's the old version https://github.com/goldfirere/ghc-proposals/blob/principles/principles.rst.) *Action: Tom, Joachim, Vlad, Eric, Chris, and Baldur*: please express an opinion.
Looks good to me. About the Contiguous Scoping Principle, the examples involving patterns (do-notation for example) feel different (and less bad) than the -XScopedTypeVariables example. Can’t really put my finger on why. But since we state that the Contiguous Scoping Principle is not a goal, merely something to be aware of, that’s fine Cheers, Joachim -- Joachim Breitner mail@joachim-breitner.de http://www.joachim-breitner.de/

Arnaud
We've had this "Scoped type variables" proposal on our table for too long.
Is there anything stopping us from making a decision?
Simon
On Tue, 29 Mar 2022 at 16:02, Spiwack, Arnaud
Dear all,
Let me bring to your attention the Modern Scoped Type Variables proposal, by our own Richard https://github.com/ghc-proposals/ghc-proposals/pull/448 .
The proposal is a touch intimidating, because the text is large. But most of it comes from other, already accepted, proposals that this proposal is tidying up and tying together.
What this proposal tries to achieve is to make a consistent text about all the recent changes to binding type variables.
The proposal adds new principles to the `principles.rst` files which inform the changes proposed, of these, I have the following comments: - The Visibility Orthogonality Principle doesn't seem to have a very clear definition. It may be a sign that it's not something that is so important - The Explicit Binding Principle says that we need to be able to enforce that all type variables have a binding site. I think it's a bit strong: I would like Haskell to let me write a binding site for every type variable, but not necessarily to error out when that doesn't happen. That being said, I'm happy with warnings to help me along the way, but I don't think that this Explicit Binding Principle should be phrased in a way that requires adding extensions to control this behaviour. - The Contiguous Scoping Principle, which states that a binder binds in one contiguous region sounds dubious to me. I don't see a particular reason for this to be.
---
In the proposed changes themselves: up to Section 5, the proposed changes are mostly existing accepted proposals, cleaned up with what was learnt since they were written, as well as to adhere to the new principles.
These are mostly uncontroversial and the specification makes sense to me. I'm in favour of accepting all that.
With the caveat that this proposal introduces quite a few extensions. And at this point, I'm still not quite sure what Richard recommends is the set of extensions that I should use (and I'm slightly dismayed that I believe that it will be a set of cardinal more than 1). I think this reflects a vision of extensions as switches to customise the behaviour of GHC. This vision, as I've stated before, is very alien to me: I see extensions as staging areas for features to become an integral part of Haskell. So I don't know what to think of all these extensions. I'm definitely not against splitting -XScopedTypeVariables into smaller components, if it is done so that they are reassembled in a different way in an alternative extension that would now be the recommended default (or at least is to become the next recommended default).
Finally, there are Sections 6 to 8. These are entirely new. Though they are working towards the new principles (well, as far as I can tell, Section 6 doesn't contribute to the principles, but it is a stepping stone for both Sections 7 and 8). These sections are concerned with adding local let-bindings of type variables, in particular inside types and patterns.
By the way, Section 7 proposes two syntaxes for let binders in patterns, and I *strongly* prefer the second syntax, which reads something like `f (let b = Bool) (True :: Bool) = …`.
Anyway, these are new, I feel that they are a bit out of place in a proposal that is about tidying up the existing designs. That being said, they are here, and they seem like fairly uncontroversial to me, (except, probably the syntax `(let b = _)` to bind a variable to a type to be filled by the compiler). I'm fine with accepting these, though they may require a bit more scrutiny than the rest.
Best, Arnaud
_______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

Yes, we did. And that's largely on me: I got lost in the debates. Reading back, my feeling is that: there is broad agreement on the proposed changes, as long as we move the “let” bits to another proposal (they have barely been discussed anyway). There are discussions on the precise meaning and wording of the principles (as far as I'm aware, I am the only one that questions the existence of one of the principle (the Contiguous Scoping Principle), there is a discussion on whether the Local Lexical Scoping Principle and the Explicit Binding Principle are really to be distinct. Considering all this, I think that the best move is to accept the proposal, as soon as the “let”-related changes have been removed from the proposal. If the wording or details of the principles turn out to need tuning, we can always amend in a future proposal. Richard, do you agree? /Arnaud On Mon, Jul 4, 2022 at 6:41 PM Simon Peyton Jones < simon.peytonjones@gmail.com> wrote:
Arnaud
We've had this "Scoped type variables" proposal on our table for too long. Is there anything stopping us from making a decision?
Simon
On Tue, 29 Mar 2022 at 16:02, Spiwack, Arnaud
wrote: Dear all,
Let me bring to your attention the Modern Scoped Type Variables proposal, by our own Richard https://github.com/ghc-proposals/ghc-proposals/pull/448 .
The proposal is a touch intimidating, because the text is large. But most of it comes from other, already accepted, proposals that this proposal is tidying up and tying together.
What this proposal tries to achieve is to make a consistent text about all the recent changes to binding type variables.
The proposal adds new principles to the `principles.rst` files which inform the changes proposed, of these, I have the following comments: - The Visibility Orthogonality Principle doesn't seem to have a very clear definition. It may be a sign that it's not something that is so important - The Explicit Binding Principle says that we need to be able to enforce that all type variables have a binding site. I think it's a bit strong: I would like Haskell to let me write a binding site for every type variable, but not necessarily to error out when that doesn't happen. That being said, I'm happy with warnings to help me along the way, but I don't think that this Explicit Binding Principle should be phrased in a way that requires adding extensions to control this behaviour. - The Contiguous Scoping Principle, which states that a binder binds in one contiguous region sounds dubious to me. I don't see a particular reason for this to be.
---
In the proposed changes themselves: up to Section 5, the proposed changes are mostly existing accepted proposals, cleaned up with what was learnt since they were written, as well as to adhere to the new principles.
These are mostly uncontroversial and the specification makes sense to me. I'm in favour of accepting all that.
With the caveat that this proposal introduces quite a few extensions. And at this point, I'm still not quite sure what Richard recommends is the set of extensions that I should use (and I'm slightly dismayed that I believe that it will be a set of cardinal more than 1). I think this reflects a vision of extensions as switches to customise the behaviour of GHC. This vision, as I've stated before, is very alien to me: I see extensions as staging areas for features to become an integral part of Haskell. So I don't know what to think of all these extensions. I'm definitely not against splitting -XScopedTypeVariables into smaller components, if it is done so that they are reassembled in a different way in an alternative extension that would now be the recommended default (or at least is to become the next recommended default).
Finally, there are Sections 6 to 8. These are entirely new. Though they are working towards the new principles (well, as far as I can tell, Section 6 doesn't contribute to the principles, but it is a stepping stone for both Sections 7 and 8). These sections are concerned with adding local let-bindings of type variables, in particular inside types and patterns.
By the way, Section 7 proposes two syntaxes for let binders in patterns, and I *strongly* prefer the second syntax, which reads something like `f (let b = Bool) (True :: Bool) = …`.
Anyway, these are new, I feel that they are a bit out of place in a proposal that is about tidying up the existing designs. That being said, they are here, and they seem like fairly uncontroversial to me, (except, probably the syntax `(let b = _)` to bind a variable to a type to be filled by the compiler). I'm fine with accepting these, though they may require a bit more scrutiny than the rest.
Best, Arnaud
_______________________________________________ ghc-steering-committee mailing list ghc-steering-committee@haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee

On Jul 5, 2022, at 2:58 AM, Spiwack, Arnaud
wrote: Richard, do you agree?
Yes, if the committee wishes to accept the proposal without the "let" bits, I'll remove them and move them to a separate proposal. But I would be dismayed if I do this work and then have the committee not accept or ask for yet another restructuring of this. Richard

Very well, if nobody objects by the end of the week, I'll make this
decision final.
On Tue, Jul 5, 2022 at 4:59 PM Richard Eisenberg
On Jul 5, 2022, at 2:58 AM, Spiwack, Arnaud
wrote: Richard, do you agree?
Yes, if the committee wishes to accept the proposal without the "let" bits, I'll remove them and move them to a separate proposal. But I would be dismayed if I do this work and then have the committee not accept or ask for yet another restructuring of this.
Richard

I've now made the decision final.
On Wed, Jul 6, 2022 at 9:32 AM Spiwack, Arnaud
Very well, if nobody objects by the end of the week, I'll make this decision final.
On Tue, Jul 5, 2022 at 4:59 PM Richard Eisenberg
wrote: On Jul 5, 2022, at 2:58 AM, Spiwack, Arnaud
wrote: Richard, do you agree?
Yes, if the committee wishes to accept the proposal without the "let" bits, I'll remove them and move them to a separate proposal. But I would be dismayed if I do this work and then have the committee not accept or ask for yet another restructuring of this.
Richard
participants (6)
-
Eric Seidel
-
Joachim Breitner
-
Richard Eisenberg
-
Simon Marlow
-
Simon Peyton Jones
-
Spiwack, Arnaud