From marlowsd at gmail.com Tue Jun 1 12:12:23 2021 From: marlowsd at gmail.com (Simon Marlow) Date: Tue, 1 Jun 2021 13:12:23 +0100 Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept In-Reply-To: <6288B96E-9699-4CDC-BF1E-112BA952D4EE@gmail.com> References: <010f0179b44f4afa-768644d0-1b2f-4138-8016-17f0a0236dfd-000000@us-east-2.amazonses.com> <6288B96E-9699-4CDC-BF1E-112BA952D4EE@gmail.com> Message-ID: On Sat, 29 May 2021 at 14:19, Vladislav Zavialov (int-index) < vlad.z.4096 at gmail.com> wrote: > Both of your suggestions (regarding lists and regarding Proxy) seem to > require type information in order to resolve the meaning of an expression. > Given `f e`, I’m assuming you want to parse/rename ‘e’ as an expression if > ‘f’ is an ordinary function, and as a type if `f :: forall a -> …`. > > However, that would violate the Lexical Scoping Principle described in > section 4.3.1 of the "Design for Dependent Types” proposal (#378), which > states: "For every occurrence of an identifier, it is possible to uniquely > identify its binding site, without involving the type system.” > > This principle is useful both in the implementation (it enables a clear > delineation between renaming/typechecking) and when reasoning about > programs. While it’s possible to violate it, I believe that writing `f > (List Int)` is the lesser evil. Also, I don’t think that you’d need to > "write `List Int` when it's a visible type argument, but `[Int]` everywhere > else”. If consistency is an explicit goal, one can write `List Int` > everywhere. > Admittedly I might be unfamiliar with a lot of the finer details here (I haven't been tracking the dependent types proposal closely), but I'm hoping that what I'm suggesting could be done while still doing renaming strictly before typechecking. It's a kind of lazy name resolution - a name can resolve to a set of entities, and whether that is actually ambiguous or not is decided later during type checking, when we know whether we need to resolve the name in a value or a type context. Does that make sense? Not being able to use `[Int]` where a type is expected would be a serious drawback in my opinion, and I don't like the other alternative either: use `List Int` everywhere (rewrite all the Haskell textbooks!). Cheers Simon > > - Vlad > > > On 29 May 2021, at 14:15, Simon Marlow wrote: > > > > I support the goal of this proposal; indeed I would immediately use it > in several places that I can think of off the top of my head. > > > > But the name resolution aspects concern me. I forsee a lot of confusion > if we can't write `[Int]` as a type argument with the usual meaning. The > error message is likely to be super confusing if it has to talk about the > difference between a promoted list type and the usual list type > constructor, which have the same syntax. I'm not a fan of having to write > `List Int` when it's a visible type argument, but `[Int]` everywhere else. > > > > Would it be possible to require the leading quote to get the promoted > meaning, otherwise defaulting to the usual meaning of `[Int]`? > > > > Also could we defer name resolution until type checking for things like > `Proxy`, so that the obvious thing doesn't require namespace gymnastics? > > > > Cheers > > Simon > > > > ghc-steering-committee mailing list > > ghc-steering-committee at haskell.org > > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vlad.z.4096 at gmail.com Tue Jun 1 14:32:46 2021 From: vlad.z.4096 at gmail.com (Vladislav Zavialov (int-index)) Date: Tue, 1 Jun 2021 17:32:46 +0300 Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept In-Reply-To: References: <010f0179b44f4afa-768644d0-1b2f-4138-8016-17f0a0236dfd-000000@us-east-2.amazonses.com> <6288B96E-9699-4CDC-BF1E-112BA952D4EE@gmail.com> Message-ID: <766D5D34-D76F-4785-BB83-56B4ECE0A239@gmail.com> > On 1 Jun 2021, at 15:12, Simon Marlow wrote: > > I'm hoping that what I'm suggesting could be done while still doing renaming strictly before typechecking. It's a kind of lazy name resolution - a name can resolve to a set of entities, and whether that is actually ambiguous or not is decided later during type checking, when we know whether we need to resolve the name in a value or a type context. Does that make sense? Yes, I see how this can work, but if name resolution returns a set of possible entities rather than one, it means it hasn’t actually done name resolution completely. After all, not doing name resolution at all is also equivalent to having a set of names – if the user refers to a variable by its name “x”, then we already narrowed down the set of possible bindings from “all bindings” to “bindings of variables named ‘x’”. But name resolution is complete only when we find out which “x” exactly is referred to. So this idea of lazy name resolution seems to amount to some name resolution prior to type checking, and then some more during type checking. It might be possible, but it does not strike me as "renaming strictly before typechecking”. I worry that it might cause some trouble in other parts of the compiler. Dependency analysis of declarations comes to mind. Let’s say the user defines: data A = B … data B = A … Currently we can process these declarations independently, there are no mutual dependencies. But if we postpone namespace selection, then this will become a strongly connected component, which will affect kind inference. I conjecture a more realistic example could be produced, but my goal is to simply state that weakening name resolution will have non-negligible impact on the implementation. Implementation aside, the lexical scoping principle to which I referred is also about user expectations. When reading and writing code, I don’t want to inspect types just to figure out which name refers to what binding. It should be deducible from the lexical structure of the program. So, while the idea sounds attractive, and it might be implementable, one would have to abandon the lexical scoping principle to pursue it. > On 1 Jun 2021, at 15:12, Simon Marlow wrote: > > Not being able to use `[Int]` where a type is expected would be a serious drawback in my opinion, and I don't like the other alternative either: use `List Int` everywhere (rewrite all the Haskell textbooks!). > > Cheers > Simon I share your disappointment, but it’s not as bad as rewriting all Haskell books! We continue to support the old syntax in all the old places, so code examples from the books will continue to compile. At the same time, codebases that lean strongly towards intermixing terms and types might adopt a different convention and require writing `List Int` everywhere. It could be part of a project style guide, for example. Also, it is interesting that you say ‘where a type is expected’, because I there are at least three ways to interpret this: 1. Syntactically, a type is what follows after `@`, `::`, etc. 2. Things of kind `… -> Type` are types, things of other kinds are data. So `Bool` is a type, while `True` is data. 3. Erased things are types, so forall-quantified variables stand for types, while lambda-bound variables stand for terms. Interestingly, under the first interpretation, `[Int]` does stand for the type of lists under this proposal, so I imagine it’s not what you meant. The choice between 2 and 3, on the other hand (and if we did lazy name resolution as you suggested earlier), would determine the meaning of programs such as: import Type.Reflection data True kindOf :: forall a -> Typeable a => String kindOf a = show (typeRepKind (typeRep @a)) main = print (kindOf True) Should this program print “Bool” or “Type”? Under (2), it must print “Bool”, because “True” is first of all data. Under (3), it must print “Type”, because the input to ‘kindOf’ is forall-quantified and erased. Even if we partially postpone name resolution until type checking, there’s a lot of design space to explore (and to explain in the User’s Guide! this is not straightforward). Under (1) it prints “Bool”, and name resolution remains blissfully unaware of any types involved. - Vlad From rae at richarde.dev Tue Jun 1 15:50:22 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Tue, 1 Jun 2021 15:50:22 +0000 Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept In-Reply-To: References: <010f0179b44f4afa-768644d0-1b2f-4138-8016-17f0a0236dfd-000000@us-east-2.amazonses.com> Message-ID: <010f0179c844cdc1-ccadd803-2637-4886-af86-464d53177b81-000000@us-east-2.amazonses.com> > On May 29, 2021, at 7:15 AM, Simon Marlow wrote: > > Would it be possible to require the leading quote to get the promoted meaning, otherwise defaulting to the usual meaning of `[Int]`? I would say this is not possible, no, for the reasons Vlad has described. Or, any attempt to do so would (as Vlad has written) require mixing some name resolution in with type-checking and would violate the Lexical Scoping Principle of #378. Instead, this current proposal includes the `type` signifier , which would allow users to write `sizeof (type [Int])`, talking about the usual list type. It would be possible to imagine *requiring* the `type` keyword there at every use of a required type argument, but that seems clutterful, and it would seem to impose a stylistic concern onto programmers who may not want the `type` herald. This is why I think `type` is a nice compromise: it allows people who want their types apart from their terms to keep them so, while allowing people who want to freely intermix them to do so. Of course, the downside to a compromise like this is that we now can have competing styles, and competing styles makes code reading harder. Richard > > Also could we defer name resolution until type checking for things like `Proxy`, so that the obvious thing doesn't require namespace gymnastics? > > Cheers > Simon > > On Fri, 28 May 2021 at 19:49, Richard Eisenberg > wrote: > Hi committee, > > Proposal #281 has been submitted for our consideration. > > Proposal PR: https://github.com/ghc-proposals/ghc-proposals/pull/281 > Proposal text: https://github.com/int-index/ghc-proposals/blob/visible-forall/proposals/0000-visible-forall.rst > > The text of the proposal is long and detailed, but do not be daunted: it is simpler in practice than it appears. > > The main payload of the proposal is: Introduce a new extension -XRequiredTypeArguments. With this extension enabled, the `forall ... ->` syntax, currently in existence in kinds, is now available in types (of ordinary functions). This means that function definitions and call sites are sometimes required to write a type argument. The type argument is *not* preceded by @ or any other syntactic marker. > > This is useful for defining what would otherwise be ambiguous types. Example: > >> sizeof :: forall a -> Sizeable a => Int >> sizeof = ... >> >> intWidth = sizeof Int > > There are further examples and motivation in the proposal. > > The rest of the proposal is simply about dealing with odd corner cases that come up with the main payload. In particular, mixing types in with terms with no syntactic signifier means that we must be careful about parsing and namespaces. If a type argument is written in the syntax that is shared between types and terms (including function application!) and uses identifiers in scope in only one of the two namespaces, nothing unusual can be observed. But, of course, there are corner cases. Here are some of the salient details: > - Define type-syntax and term-syntax, where the choice of syntax is always driven by syntactic markers, such as :: or @. See the dependent types proposal for more details. Parsing and name-resolution are controlled by whether a phrase is in type-syntax or term-syntax. For name resolution, if a lookup fails in the first namespace (the term-level namespace in term-syntax or the type-level namespace in type-syntax), we try the other namespace before failing. > - Because term- vs type-syntax is controlled by syntax, a required type argument is in *term*-syntax and gets name-resolved *as a term*. In the absence of punning, this works out fine, but it is possible that a punned identifier will cause confusion. The proposal includes section 4.3 allowing users to write `type` to signify a switch to type-syntax. > - The proposal also includes a way to avoid punning for the built-in types with privileged syntax: lists and tuples. This method allows users to specify -XNoListTupleTypeSyntax to disable the list and tuple syntax in types (but still allows it for terms). The proposal also suggests exporting type List = [] from Data.List and other synonyms for tuples from Data.Tuple. > > --------------- > > I recommend acceptance. When doing type-level programming, the lack of this feature is strange, leading to ambiguous types and easy-to-forget arguments and easy-to-make type errors. The design space here is difficult, but this proposal is very much in keeping with the design sketch of our recently-accepted #378, in particular its section on this point . I believe the design described here is both backward compatible with what we have today (users who do not use this feature will not notice a difference) and forward compatible with a cohesive design for dependent types. > > There are several optional pieces: > - The `type` herald . I am unsure about this one, but others have felt strongly in favor, and I have no reason to object. > - Types-in-terms . I think this is necessary in order to avoid annoying definitions of type synonyms for one-off usage sites. It is a straightforward extension of the term-level parser to allow previously type-level-only constructs. It is necessary in order for us to achieve the vision of dependent types in #378. The only challenge here is that this requires us to make `forall` an unconditional keyword in terms. This does pose a backward-compatibility problem. I see, for example, that the sbv package exports a function named `forall`, so we may need to think more carefully about how to proceed here -- possibly by guarding the keyword-ness of `forall` behind the extension for some number of transitionary releases. > - Lists and Tuples . This section describes the -XNoListTupleTypeSyntax extension. I am not convinced that this change needs to be part of this proposal (thinking it belongs more in #270), but I do think we'll need it in the end. Is it OK to export new type synonyms from Data.List and Data.Tuple? Not sure, though I'd like these exported from some central place. > > What do others think? > > Thanks, > Richard > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee -------------- next part -------------- An HTML attachment was scrubbed... URL: From marlowsd at gmail.com Tue Jun 1 16:56:57 2021 From: marlowsd at gmail.com (Simon Marlow) Date: Tue, 1 Jun 2021 17:56:57 +0100 Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept In-Reply-To: <766D5D34-D76F-4785-BB83-56B4ECE0A239@gmail.com> References: <010f0179b44f4afa-768644d0-1b2f-4138-8016-17f0a0236dfd-000000@us-east-2.amazonses.com> <6288B96E-9699-4CDC-BF1E-112BA952D4EE@gmail.com> <766D5D34-D76F-4785-BB83-56B4ECE0A239@gmail.com> Message-ID: On Tue, 1 Jun 2021 at 15:32, Vladislav Zavialov (int-index) < vlad.z.4096 at gmail.com> wrote: > > > On 1 Jun 2021, at 15:12, Simon Marlow wrote: > > > > I'm hoping that what I'm suggesting could be done while still doing > renaming strictly before typechecking. It's a kind of lazy name resolution > - a name can resolve to a set of entities, and whether that is actually > ambiguous or not is decided later during type checking, when we know > whether we need to resolve the name in a value or a type context. Does that > make sense? > > > Yes, I see how this can work, but if name resolution returns a set of > possible entities rather than one, it means it hasn’t actually done name > resolution completely. After all, not doing name resolution at all is also > equivalent to having a set of names – if the user refers to a variable by > its name “x”, then we already narrowed down the set of possible bindings > from “all bindings” to “bindings of variables named ‘x’”. But name > resolution is complete only when we find out which “x” exactly is referred > to. > > So this idea of lazy name resolution seems to amount to some name > resolution prior to type checking, and then some more during type checking. > It might be possible, but it does not strike me as "renaming strictly > before typechecking”. > Don't we already do this for DataKinds? The lexical scoping rule is slightly cheating with respect to DataKinds because while we can resolve an identifier to its binding site, the binding site in the case of a promoted constructor is actually two binding sites :) > I worry that it might cause some trouble in other parts of the compiler. > Dependency analysis of declarations comes to mind. Let’s say the user > defines: > > data A = B … > data B = A … > > Currently we can process these declarations independently, there are no > mutual dependencies. But if we postpone namespace selection, then this will > become a strongly connected component, which will affect kind inference. I > conjecture a more realistic example could be produced, but my goal is to > simply state that weakening name resolution will have non-negligible impact > on the implementation. > > Implementation aside, the lexical scoping principle to which I referred is > also about user expectations. When reading and writing code, I don’t want > to inspect types just to figure out which name refers to what binding. It > should be deducible from the lexical structure of the program. > > So, while the idea sounds attractive, and it might be implementable, one > would have to abandon the lexical scoping principle to pursue it. > > > On 1 Jun 2021, at 15:12, Simon Marlow wrote: > > > > Not being able to use `[Int]` where a type is expected would be a > serious drawback in my opinion, and I don't like the other alternative > either: use `List Int` everywhere (rewrite all the Haskell textbooks!). > > > > Cheers > > Simon > > I share your disappointment, but it’s not as bad as rewriting all Haskell > books! We continue to support the old syntax in all the old places, so code > examples from the books will continue to compile. At the same time, > codebases that lean strongly towards intermixing terms and types might > adopt a different convention and require writing `List Int` everywhere. It > could be part of a project style guide, for example. > To clarify what I meant here - if we want consistency, where consistency means referring to the type of lists of Int using the same syntax everywhere, then this leads to List Int and having to rewrite the Haskell textbooks. So all the options are bad: we either have two ways to write list of Int (and in some places only one of them works), or we have consistency but we're changing something fundamental (and to a worse syntax). The third option, namely using the "type" prefix also doesn't seem appealing, because I have to know when to use the "type" prefix. I could use it all the time, but then that's not much better than the current situation (@-prefix) and I also have to read code written by other people who don't adopt this convention. With regard to list syntax in particular, I guess I still don't understand why we can't * require a promoted list to be written '[Int] * change the T2T mapping so that [Int] means "list of Int" rather than the promoted interpretation After all, DataKinds already recommends using the leading quote and not relying on unquoted syntax. or perhaps this is undesirable for some reason? Do you think the promoted interpretation is more useful? Cheers Simon > Also, it is interesting that you say ‘where a type is expected’, because I > there are at least three ways to interpret this: > > 1. Syntactically, a type is what follows after `@`, `::`, etc. > 2. Things of kind `… -> Type` are types, things of other kinds are data. > So `Bool` is a type, while `True` is data. > 3. Erased things are types, so forall-quantified variables stand for > types, while lambda-bound variables stand for terms. > > Interestingly, under the first interpretation, `[Int]` does stand for the > type of lists under this proposal, so I imagine it’s not what you meant. > The choice between 2 and 3, on the other hand (and if we did lazy name > resolution as you suggested earlier), would determine the meaning of > programs such as: > > import Type.Reflection > > data True > > kindOf :: forall a -> Typeable a => String > kindOf a = show (typeRepKind (typeRep @a)) > > main = print (kindOf True) > > Should this program print “Bool” or “Type”? Under (2), it must print > “Bool”, because “True” is first of all data. Under (3), it must print > “Type”, because the input to ‘kindOf’ is forall-quantified and erased. > > Even if we partially postpone name resolution until type checking, there’s > a lot of design space to explore (and to explain in the User’s Guide! this > is not straightforward). > > Under (1) it prints “Bool”, and name resolution remains blissfully unaware > of any types involved. > > - Vlad > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rae at richarde.dev Tue Jun 1 18:09:13 2021 From: rae at richarde.dev (Richard Eisenberg) Date: Tue, 1 Jun 2021 18:09:13 +0000 Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept In-Reply-To: References: <010f0179b44f4afa-768644d0-1b2f-4138-8016-17f0a0236dfd-000000@us-east-2.amazonses.com> <6288B96E-9699-4CDC-BF1E-112BA952D4EE@gmail.com> <766D5D34-D76F-4785-BB83-56B4ECE0A239@gmail.com> Message-ID: <010f0179c8c3ebf8-0dcb304e-fa7f-4b33-9c70-88619a9ddd08-000000@us-east-2.amazonses.com> > So this idea of lazy name resolution seems to amount to some name resolution prior to type checking, and then some more during type checking. It might be possible, but it does not strike me as "renaming strictly before typechecking”. > > Don't we already do this for DataKinds? The lexical scoping rule is slightly cheating with respect to DataKinds because while we can resolve an identifier to its binding site, the binding site in the case of a promoted constructor is actually two binding sites :) I don't think we do. With DataKinds, an occurrence of a capitalized identifier in a type (where "in a type" means in type-syntax ) first looks in the type namespace. If this lookup is successful, stop, returning the type-level name. Otherwise, look in the term namespace. If we know what is in scope (and what is in what namespace), we can still uniquely find the single binding site associated with an occurrence. (I'm not sure what you mean by "two binding sites".) > To clarify what I meant here - if we want consistency, where consistency means referring to the type of lists of Int using the same syntax everywhere, then this leads to List Int and having to rewrite the Haskell textbooks. So all the options are bad: we either have two ways to write list of Int (and in some places only one of them works), or we have consistency but we're changing something fundamental (and to a worse syntax). "worse" is (of course) a matter of opinion. I've had a number of students who, after learning [3] :: [Int], thought that [] :: [] and [3,4] :: [Int, Int]. I actually think that (textbooks/blog posts/history aside -- which is impossible) List Int is better syntax. > The third option, namely using the "type" prefix also doesn't seem appealing, because I have to know when to use the "type" prefix. Precisely! The advantage here is that the author is responsible for figuring out when to put in the "type" prefix, as opposed to the reader. If I write f [Int], what have I passed? Is it a single-element list containing the type Int? or is it the type describing lists of Ints? A reader has no way of knowing -- this is a violation of the LSP. I'd much rather put the disambiguation burden on the author of the code than on the reader. Code is read more often than it is written/revised. > I could use it all the time, but then that's not much better than the current situation (@-prefix) I think it's better than the current situation, because the type argument can now be required, instead of inferred-and-ambiguous. > and I also have to read code written by other people who don't adopt this convention. Yes, that's indeed true. > > With regard to list syntax in particular, I guess I still don't understand why we can't > * require a promoted list to be written '[Int] > * change the T2T mapping so that [Int] means "list of Int" rather than the promoted interpretation Unfortunately, the ' syntax in terms is taken by Template Haskell. So f '[] can be used today to pass the TH Name associated with nil. Ignoring this wrinkle, does your counter-proposal extend to names other than the brackets in [Int]? For example, if I have data T = T and write f T, which T am I passing? There are two, and the LSP suggests that we should be able to answer this question without knowing the type of f. > > After all, DataKinds already recommends using the leading quote and not relying on unquoted syntax. Yes, but I actually think this was a mistake in retrospect -- even though I implemented -Wunticked-promoted-constructors. Better would have been to implement -Wpuns. :) > > or perhaps this is undesirable for some reason? Do you think the promoted interpretation is more useful? In truth, I think the type-level interpretation is more useful. But I'd rather GHC be more predictable (that is, follow the LSP) than try to be clever here. Richard > > Cheers > Simon > > > > Also, it is interesting that you say ‘where a type is expected’, because I there are at least three ways to interpret this: > > 1. Syntactically, a type is what follows after `@`, `::`, etc. > 2. Things of kind `… -> Type` are types, things of other kinds are data. So `Bool` is a type, while `True` is data. > 3. Erased things are types, so forall-quantified variables stand for types, while lambda-bound variables stand for terms. > > Interestingly, under the first interpretation, `[Int]` does stand for the type of lists under this proposal, so I imagine it’s not what you meant. The choice between 2 and 3, on the other hand (and if we did lazy name resolution as you suggested earlier), would determine the meaning of programs such as: > > import Type.Reflection > > data True > > kindOf :: forall a -> Typeable a => String > kindOf a = show (typeRepKind (typeRep @a)) > > main = print (kindOf True) > > Should this program print “Bool” or “Type”? Under (2), it must print “Bool”, because “True” is first of all data. Under (3), it must print “Type”, because the input to ‘kindOf’ is forall-quantified and erased. > > Even if we partially postpone name resolution until type checking, there’s a lot of design space to explore (and to explain in the User’s Guide! this is not straightforward). > > Under (1) it prints “Bool”, and name resolution remains blissfully unaware of any types involved. > > - Vlad -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Jun 1 22:42:27 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 1 Jun 2021 22:42:27 +0000 Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept In-Reply-To: <010f0179b44f4afa-768644d0-1b2f-4138-8016-17f0a0236dfd-000000@us-east-2.amazonses.com> References: <010f0179b44f4afa-768644d0-1b2f-4138-8016-17f0a0236dfd-000000@us-east-2.amazonses.com> Message-ID: I am generally in support. Working out the details in the dependent types proposal was extremely helpful. Like Simon, I'm sad that I have to write f (List Int) or f (type [Int]) but I think the alternative (of requiring the reader to know the type of the function in order to resolve the binding of names in its argument) is much, much worse. The tension here is fundamental if you want to have required type arguments at all. It's not an artefact of GHC's history, or the constraints of the existing language. (I suppose that in a new language you might *only* provide "List Int" and "Pair a b", but I do like [Int] and (a,b) as types, and they will continue to work just fine in types.) So I have made my peace with it; and I really like the option of a "type" herald to switch to type syntax. Simon From: ghc-steering-committee On Behalf Of Richard Eisenberg Sent: 28 May 2021 19:49 To: ghc-steering-committee Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept Hi committee, Proposal #281 has been submitted for our consideration. Proposal PR: https://github.com/ghc-proposals/ghc-proposals/pull/281 Proposal text: https://github.com/int-index/ghc-proposals/blob/visible-forall/proposals/0000-visible-forall.rst The text of the proposal is long and detailed, but do not be daunted: it is simpler in practice than it appears. The main payload of the proposal is: Introduce a new extension -XRequiredTypeArguments. With this extension enabled, the `forall ... ->` syntax, currently in existence in kinds, is now available in types (of ordinary functions). This means that function definitions and call sites are sometimes required to write a type argument. The type argument is *not* preceded by @ or any other syntactic marker. This is useful for defining what would otherwise be ambiguous types. Example: sizeof :: forall a -> Sizeable a => Int sizeof = ... intWidth = sizeof Int There are further examples and motivation in the proposal. The rest of the proposal is simply about dealing with odd corner cases that come up with the main payload. In particular, mixing types in with terms with no syntactic signifier means that we must be careful about parsing and namespaces. If a type argument is written in the syntax that is shared between types and terms (including function application!) and uses identifiers in scope in only one of the two namespaces, nothing unusual can be observed. But, of course, there are corner cases. Here are some of the salient details: - Define type-syntax and term-syntax, where the choice of syntax is always driven by syntactic markers, such as :: or @. See the dependent types proposal for more details. Parsing and name-resolution are controlled by whether a phrase is in type-syntax or term-syntax. For name resolution, if a lookup fails in the first namespace (the term-level namespace in term-syntax or the type-level namespace in type-syntax), we try the other namespace before failing. - Because term- vs type-syntax is controlled by syntax, a required type argument is in *term*-syntax and gets name-resolved *as a term*. In the absence of punning, this works out fine, but it is possible that a punned identifier will cause confusion. The proposal includes section 4.3 allowing users to write `type` to signify a switch to type-syntax. - The proposal also includes a way to avoid punning for the built-in types with privileged syntax: lists and tuples. This method allows users to specify -XNoListTupleTypeSyntax to disable the list and tuple syntax in types (but still allows it for terms). The proposal also suggests exporting type List = [] from Data.List and other synonyms for tuples from Data.Tuple. --------------- I recommend acceptance. When doing type-level programming, the lack of this feature is strange, leading to ambiguous types and easy-to-forget arguments and easy-to-make type errors. The design space here is difficult, but this proposal is very much in keeping with the design sketch of our recently-accepted #378, in particular its section on this point. I believe the design described here is both backward compatible with what we have today (users who do not use this feature will not notice a difference) and forward compatible with a cohesive design for dependent types. There are several optional pieces: - The `type` herald. I am unsure about this one, but others have felt strongly in favor, and I have no reason to object. - Types-in-terms. I think this is necessary in order to avoid annoying definitions of type synonyms for one-off usage sites. It is a straightforward extension of the term-level parser to allow previously type-level-only constructs. It is necessary in order for us to achieve the vision of dependent types in #378. The only challenge here is that this requires us to make `forall` an unconditional keyword in terms. This does pose a backward-compatibility problem. I see, for example, that the sbv package exports a function named `forall`, so we may need to think more carefully about how to proceed here -- possibly by guarding the keyword-ness of `forall` behind the extension for some number of transitionary releases. - Lists and Tuples. This section describes the -XNoListTupleTypeSyntax extension. I am not convinced that this change needs to be part of this proposal (thinking it belongs more in #270), but I do think we'll need it in the end. Is it OK to export new type synonyms from Data.List and Data.Tuple? Not sure, though I'd like these exported from some central place. What do others think? Thanks, Richard -------------- next part -------------- An HTML attachment was scrubbed... URL: From marlowsd at gmail.com Wed Jun 2 09:05:56 2021 From: marlowsd at gmail.com (Simon Marlow) Date: Wed, 2 Jun 2021 10:05:56 +0100 Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept In-Reply-To: References: <010f0179b44f4afa-768644d0-1b2f-4138-8016-17f0a0236dfd-000000@us-east-2.amazonses.com> Message-ID: Thanks Richard and Simon - I think I understand the constraints better now. I still find the conclusion somewhat unsatisfying, and I'm not sure I could convincingly explain to someone why [Int] in a visible type argument means something different from [Int] in a type signature. Intuitively it doesn't seem unreasonable to add a little more magic to the T2T mapping to preserve what (to me) seem to be reasonable expectations. But perhaps it's my expectations that need to be adjusted. Cheers Simon On Tue, 1 Jun 2021 at 23:43, Simon Peyton Jones via ghc-steering-committee < ghc-steering-committee at haskell.org> wrote: > I am generally in support. > > > > Working out the details in the dependent types proposal > > was extremely helpful. > > > > Like Simon, I’m sad that I have to write > > f (List Int) > > or > > f (type [Int]) > > but I think the alternative (of requiring the reader to know the type of > the function in order to resolve the binding of names in its argument) is > much, much worse. > > > > The tension here is fundamental if you want to have required type > arguments at all. *It’s not an artefact of GHC’s history, or the > constraints of the existing language.* (I suppose that in a new language > you might **only** provide “List Int” and “Pair a b”, but I do like [Int] > and (a,b) as types, and they will continue to work just fine in types.) > > > > So I have made my peace with it; and I really like the option of a “type” > herald to switch to type syntax. > > > > Simon > > > > *From:* ghc-steering-committee > *On Behalf Of *Richard Eisenberg > *Sent:* 28 May 2021 19:49 > *To:* ghc-steering-committee > *Subject:* [ghc-steering-committee] Proposal #281: Visible "forall" in > terms; rec: accept > > > > Hi committee, > > > > Proposal #281 has been submitted for our consideration. > > > > Proposal PR: https://github.com/ghc-proposals/ghc-proposals/pull/281 > > > Proposal text: > https://github.com/int-index/ghc-proposals/blob/visible-forall/proposals/0000-visible-forall.rst > > > > > The text of the proposal is long and detailed, but do not be daunted: it > is simpler in practice than it appears. > > > > The main payload of the proposal is: Introduce a new extension > -XRequiredTypeArguments. With this extension enabled, the `forall ... ->` > syntax, currently in existence in kinds, is now available in types (of > ordinary functions). This means that function definitions and call sites > are sometimes required to write a type argument. The type argument is *not* > preceded by @ or any other syntactic marker. > > > > This is useful for defining what would otherwise be ambiguous types. > Example: > > > > sizeof :: forall a -> Sizeable a => Int > > sizeof = ... > > > > intWidth = sizeof Int > > > > There are further examples and motivation in the proposal. > > > > The rest of the proposal is simply about dealing with odd corner cases > that come up with the main payload. In particular, mixing types in with > terms with no syntactic signifier means that we must be careful about > parsing and namespaces. If a type argument is written in the syntax that is > shared between types and terms (including function application!) and uses > identifiers in scope in only one of the two namespaces, nothing unusual can > be observed. But, of course, there are corner cases. Here are some of the > salient details: > > - Define type-syntax and term-syntax, where the choice of syntax is always > driven by syntactic markers, such as :: or @. See the dependent types > proposal > for > more details. Parsing and name-resolution are controlled by whether a > phrase is in type-syntax or term-syntax. For name resolution, if a lookup > fails in the first namespace (the term-level namespace in term-syntax or > the type-level namespace in type-syntax), we try the other namespace before > failing. > > - Because term- vs type-syntax is controlled by syntax, a required type > argument is in *term*-syntax and gets name-resolved *as a term*. In the > absence of punning, this works out fine, but it is possible that a punned > identifier will cause confusion. The proposal includes section 4.3 allowing > users to write `type` to signify a switch to type-syntax. > > - The proposal also includes a way to avoid punning for the built-in types > with privileged syntax: lists and tuples. This method allows users to > specify -XNoListTupleTypeSyntax to disable the list and tuple syntax in > types (but still allows it for terms). The proposal also suggests exporting > type List = [] from Data.List and other synonyms for tuples from Data.Tuple. > > > > --------------- > > > > I recommend acceptance. When doing type-level programming, the lack of > this feature is strange, leading to ambiguous types and easy-to-forget > arguments and easy-to-make type errors. The design space here is difficult, > but this proposal is very much in keeping with the design sketch of our > recently-accepted #378, in particular its section on this point > . > I believe the design described here is both backward compatible with what > we have today (users who do not use this feature will not notice a > difference) and forward compatible with a cohesive design for dependent > types. > > > > There are several optional pieces: > > - The `type` herald > . > I am unsure about this one, but others have felt strongly in favor, and I > have no reason to object. > > - Types-in-terms > . > I think this is necessary in order to avoid annoying definitions of type > synonyms for one-off usage sites. It is a straightforward extension of the > term-level parser to allow previously type-level-only constructs. It is > necessary in order for us to achieve the vision of dependent types in #378. > The only challenge here is that this requires us to make `forall` an > unconditional keyword in terms. This does pose a backward-compatibility > problem. I see, for example, that the sbv package exports a function named > `forall`, so we may need to think more carefully about how to proceed here > -- possibly by guarding the keyword-ness of `forall` behind the extension > for some number of transitionary releases. > > - Lists and Tuples > . > This section describes the -XNoListTupleTypeSyntax extension. I am not > convinced that this change needs to be part of this proposal (thinking it > belongs more in #270), but I do think we'll need it in the end. Is it OK to > export new type synonyms from Data.List and Data.Tuple? Not sure, though > I'd like these exported from some central place. > > > > What do others think? > > > > Thanks, > > Richard > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Wed Jun 2 10:02:30 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 2 Jun 2021 10:02:30 +0000 Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept In-Reply-To: References: <010f0179b44f4afa-768644d0-1b2f-4138-8016-17f0a0236dfd-000000@us-east-2.amazonses.com> Message-ID: Intuitively it doesn't seem unreasonable to add a little more magic to the T2T mapping to preserve what (to me) seem to be reasonable expectations Yes, that was my view to begin with. But I can't come up with any magic! I cleave strongly to the view that given a name like T, I should be able to say what T is meant (the data constructor or the type constructor) without knowing the type of the function applied to T, as in (f T). That is, the renamer can do its work without thinking about types. This is the Lexical Scoping Principle (LSP). Although the LSM makes GHC's implementation much cleaner, it is not driven by implementation considerations. it's to do with user understanding. What if that T isn't the argument to a function, but appears in some other context? What if `f` is polymorphic, so its type in turn depends on its context? It goes on and on. So, if we espouse the LSP and see (f T), we can only say that T is the data constructor. If you want the type constructor you can say (f (type T)). This tension seems fundamental, not driven by implementation considerations, nor by back-compat constraints, nor by GHC's history. There is no room for magic! You might wonder if we could do some magic for built-in syntax like [T]. But it would be terribly strange to treat (f [T]) completely differently from (f [T,T]), say. The only way I can see to add magic is to give up on the LSP. But I really think that would be a Bad Thing. Indeed we recently removed the only bit of GHC that didn't obey the LSP: https://github.com/adamgundry/ghc-proposals/blob/no-ambiguous-selectors/proposals/0000-no-ambiguous-field-access.rst If you have any other ideas, I'm all ears. Simon From: Simon Marlow Sent: 02 June 2021 10:06 To: Simon Peyton Jones Cc: Richard Eisenberg ; ghc-steering-committee Subject: Re: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept Thanks Richard and Simon - I think I understand the constraints better now. I still find the conclusion somewhat unsatisfying, and I'm not sure I could convincingly explain to someone why [Int] in a visible type argument means something different from [Int] in a type signature. Intuitively it doesn't seem unreasonable to add a little more magic to the T2T mapping to preserve what (to me) seem to be reasonable expectations. But perhaps it's my expectations that need to be adjusted. Cheers Simon On Tue, 1 Jun 2021 at 23:43, Simon Peyton Jones via ghc-steering-committee > wrote: I am generally in support. Working out the details in the dependent types proposal was extremely helpful. Like Simon, I'm sad that I have to write f (List Int) or f (type [Int]) but I think the alternative (of requiring the reader to know the type of the function in order to resolve the binding of names in its argument) is much, much worse. The tension here is fundamental if you want to have required type arguments at all. It's not an artefact of GHC's history, or the constraints of the existing language. (I suppose that in a new language you might *only* provide "List Int" and "Pair a b", but I do like [Int] and (a,b) as types, and they will continue to work just fine in types.) So I have made my peace with it; and I really like the option of a "type" herald to switch to type syntax. Simon From: ghc-steering-committee > On Behalf Of Richard Eisenberg Sent: 28 May 2021 19:49 To: ghc-steering-committee > Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept Hi committee, Proposal #281 has been submitted for our consideration. Proposal PR: https://github.com/ghc-proposals/ghc-proposals/pull/281 Proposal text: https://github.com/int-index/ghc-proposals/blob/visible-forall/proposals/0000-visible-forall.rst The text of the proposal is long and detailed, but do not be daunted: it is simpler in practice than it appears. The main payload of the proposal is: Introduce a new extension -XRequiredTypeArguments. With this extension enabled, the `forall ... ->` syntax, currently in existence in kinds, is now available in types (of ordinary functions). This means that function definitions and call sites are sometimes required to write a type argument. The type argument is *not* preceded by @ or any other syntactic marker. This is useful for defining what would otherwise be ambiguous types. Example: sizeof :: forall a -> Sizeable a => Int sizeof = ... intWidth = sizeof Int There are further examples and motivation in the proposal. The rest of the proposal is simply about dealing with odd corner cases that come up with the main payload. In particular, mixing types in with terms with no syntactic signifier means that we must be careful about parsing and namespaces. If a type argument is written in the syntax that is shared between types and terms (including function application!) and uses identifiers in scope in only one of the two namespaces, nothing unusual can be observed. But, of course, there are corner cases. Here are some of the salient details: - Define type-syntax and term-syntax, where the choice of syntax is always driven by syntactic markers, such as :: or @. See the dependent types proposal for more details. Parsing and name-resolution are controlled by whether a phrase is in type-syntax or term-syntax. For name resolution, if a lookup fails in the first namespace (the term-level namespace in term-syntax or the type-level namespace in type-syntax), we try the other namespace before failing. - Because term- vs type-syntax is controlled by syntax, a required type argument is in *term*-syntax and gets name-resolved *as a term*. In the absence of punning, this works out fine, but it is possible that a punned identifier will cause confusion. The proposal includes section 4.3 allowing users to write `type` to signify a switch to type-syntax. - The proposal also includes a way to avoid punning for the built-in types with privileged syntax: lists and tuples. This method allows users to specify -XNoListTupleTypeSyntax to disable the list and tuple syntax in types (but still allows it for terms). The proposal also suggests exporting type List = [] from Data.List and other synonyms for tuples from Data.Tuple. --------------- I recommend acceptance. When doing type-level programming, the lack of this feature is strange, leading to ambiguous types and easy-to-forget arguments and easy-to-make type errors. The design space here is difficult, but this proposal is very much in keeping with the design sketch of our recently-accepted #378, in particular its section on this point. I believe the design described here is both backward compatible with what we have today (users who do not use this feature will not notice a difference) and forward compatible with a cohesive design for dependent types. There are several optional pieces: - The `type` herald. I am unsure about this one, but others have felt strongly in favor, and I have no reason to object. - Types-in-terms. I think this is necessary in order to avoid annoying definitions of type synonyms for one-off usage sites. It is a straightforward extension of the term-level parser to allow previously type-level-only constructs. It is necessary in order for us to achieve the vision of dependent types in #378. The only challenge here is that this requires us to make `forall` an unconditional keyword in terms. This does pose a backward-compatibility problem. I see, for example, that the sbv package exports a function named `forall`, so we may need to think more carefully about how to proceed here -- possibly by guarding the keyword-ness of `forall` behind the extension for some number of transitionary releases. - Lists and Tuples. This section describes the -XNoListTupleTypeSyntax extension. I am not convinced that this change needs to be part of this proposal (thinking it belongs more in #270), but I do think we'll need it in the end. Is it OK to export new type synonyms from Data.List and Data.Tuple? Not sure, though I'd like these exported from some central place. What do others think? Thanks, Richard _______________________________________________ ghc-steering-committee mailing list ghc-steering-committee at haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee -------------- next part -------------- An HTML attachment was scrubbed... URL: From vlad.z.4096 at gmail.com Wed Jun 2 11:16:24 2021 From: vlad.z.4096 at gmail.com (Vladislav Zavialov (int-index)) Date: Wed, 2 Jun 2021 14:16:24 +0300 Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept In-Reply-To: References: <010f0179b44f4afa-768644d0-1b2f-4138-8016-17f0a0236dfd-000000@us-east-2.amazonses.com> Message-ID: <02E6671A-9B49-4B73-B261-9BB1A357FE9F@gmail.com> > On 2 Jun 2021, at 13:02, Simon Peyton Jones via ghc-steering-committee wrote: > > You might wonder if we could do some magic for built-in syntax like [T]. But it would be terribly strange to treat (f [T]) completely differently from (f [T,T]), say. > Indeed it would be strange, although that is a weaker argument than adherence to LSP, as we already do the strange thing with DataKinds (e.g. `f :: Proxy [Int] -> …` is treated differently from `f :: Proxy [Int,Int] -> …`). In fact, -XNoListTupleTypeSyntax is in the proposal exactly to address this. - Vlad From eric at seidel.io Mon Jun 7 03:14:55 2021 From: eric at seidel.io (Eric Seidel) Date: Sun, 06 Jun 2021 23:14:55 -0400 Subject: [ghc-steering-committee] =?utf-8?q?=23409=3A_Exportable_named_def?= =?utf-8?q?aults=2C_Recommendation=3A_Partial_Accept?= In-Reply-To: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> Message-ID: <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> The response to the NamedDefaults extension has been uniformly positive, so I think we can consider that part accepted. However, we still need to make a decision about the ExportedDefaults extension. Since my original recommendation to reject this part of the proposal, I've come around to the argument that defaulting rules don't need global coherence like class instances, so explicit exports are fine. Simon PJ and Richard have also voiced support for explicit exports as suggested in the proposal. So I would like to revise my recommendation for ExportedDefaults to *accept*. That leaves the question of how defaulting rules should be imported. The two options are 1. *implicit*: all defaulting rules exported by a module M are automatically imported by *any* import of M, just like class instances. The proposal suggests doing this, and hiding it behind an `ImportedDefaults` extension, which feels unnecessary to me. 2. *explicit*: defaulting rules must be explicitly imported, using a syntax like `import M (default C)`. If we go this route, we will also need to decide whether a plain `import M` should import defaulting rules. Richard argues on GitHub that it should not, but I think that veers too far from the existing behavior of imports. Between the two, I lean towards (2) for the symmetry between explicit exports and imports, with the `import M` syntax pulling in defaulting rules. Eric On Tue, May 25, 2021, at 16:01, Richard Eisenberg wrote: > I have commented on GitHub with my thoughts here: > https://github.com/ghc-proposals/ghc-proposals/pull/409#issuecomment-848221001 > > Thanks, > Richard > > > On May 20, 2021, at 11:24 AM, Alejandro Serrano Mena wrote: > > > > Hi all, > > > > I agree with the recommendations of accepting (1) and rejecting (2) and (3). The Report here (https://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-790004.3.4) mentions that defaults are local to a module, and I think this is the right move, even more so since we can think of other ways of importing/exporting defaults, like plug-ins. > > > > Alejandro > > > > El 19 may 2021 4:11:48, Eric Seidel escribió: > >> Hi all, > >> > >> Mario has proposed a handful of language extensions around type defaulting. > >> > >> 1. NamedDefaults: this extension simply allows specifying the class to default, instead of it always being Num (or a handful of other hardcoded classes if one enables ExtendedDefaultRules). The rule only applies to the current module, as usual. > >> > >> 2. ExportedDefaults: this extension allows exporting defaulting rules. > >> > >> 3. ImportedDefaults: this extension makes import declarations pull in defaulting rules implicitly, like class instances. > >> > >> Extensions (2) and (3) work together to provide a mechanism for sharing sets of defaulting rules across modules. It is possible to import conflicting sets of defaulting rules from different modules, in that case the conflict must be resolved manually by the importing module, with a new defaulting rule. > >> > >> My recommendation is that we > >> > >> * Accept extension (1), as it is a clear improvement over the status quo and can stand on its own. > >> > >> * Reject (without prejudice) extensions (2) and (3). These extensions bring considerable extra complexity and another orphan-like mechanism. There's an open question here of whether defaulting rules should be globally coherent like type classes, or if they're something different; the discussion has arguments for both sides. I'm not sure, and so I recommend we don't commit ourselves one way or the other for now. > >> > >> Please take a look at the proposal. > >> > >> Discussion: https://github.com/ghc-proposals/ghc-proposals/pull/409 > >> Proposal: https://github.com/blamario/ghc-proposals/blob/exportable-named-default/proposals/0000-exportable-named-default.rst > >> > >> Eric > >> > >> On Sun, Apr 4, 2021, at 06:34, Joachim Breitner wrote: > >>> Dear Committe, > >>> > >>> Exportable named defaults > >>> has been proposed by Mario > >>> https://github.com/ghc-proposals/ghc-proposals/pull/409 > >>> https://github.com/blamario/ghc-proposals/blob/exportable-named-default/proposals/0000-exportable-named-default.rst > >>> > >>> I propose Eric as the Shepherd. > >>> > >>> This did not gather a lot of attention on Github, or rather none, so > >>> Eric, maybe also consider whether this needs to be advertised more, or > >>> maybe who should be pointed to it. > >>> > >>> Please guide us to a conclusion as outlined in > >>> https://github.com/ghc-proposals/ghc-proposals#committee-process > >>> > >>> Thanks, > >>> Joachim > >>> -- > >>> -- > >>> Joachim Breitner > >>> mail at joachim-breitner.de > >>> http://www.joachim-breitner.de/ > >>> > >>> > >>> _______________________________________________ > >>> ghc-steering-committee mailing list > >>> ghc-steering-committee at haskell.org > >>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > >>> > >> _______________________________________________ > >> ghc-steering-committee mailing list > >> ghc-steering-committee at haskell.org > >> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > > _______________________________________________ > > ghc-steering-committee mailing list > > ghc-steering-committee at haskell.org > > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > From trupill at gmail.com Mon Jun 7 07:22:56 2021 From: trupill at gmail.com (Alejandro Serrano Mena) Date: Mon, 7 Jun 2021 07:22:56 +0000 Subject: [ghc-steering-committee] #409: Exportable named defaults, Recommendation: Partial Accept In-Reply-To: <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> Message-ID: Hi everybody, The discussion in the PR has also convinced me about the advantages of being able to import/export defaults. I would like to add that there’s a in-the-middle option discussed somewhere in the PR, which is (1) + a way to hide the defaulting. Something like: > import Module hiding (default Num) which I find quite natural: everything related to type classes is imported automatically, and “defaulting” goes in that “mental bucket” for me. Another concern for me is the requirement of having 3 different extensions. I know being fine-grained is great, but I think we’ve erred sometimes in the “too much” side in the past. I’ve written in the PR on that matter. Regards, Alejandro El 7 jun 2021 5:14:55, Eric Seidel escribió: > The response to the NamedDefaults extension has been uniformly positive, > so I think we can consider that part accepted. > > However, we still need to make a decision about the ExportedDefaults > extension. Since my original recommendation to reject this part of the > proposal, I've come around to the argument that defaulting rules don't need > global coherence like class instances, so explicit exports are fine. Simon > PJ and Richard have also voiced support for explicit exports as suggested > in the proposal. > > So I would like to revise my recommendation for ExportedDefaults to > *accept*. > > That leaves the question of how defaulting rules should be imported. The > two options are > > 1. *implicit*: all defaulting rules exported by a module M are > automatically imported by *any* import of M, just like class instances. The > proposal suggests doing this, and hiding it behind an `ImportedDefaults` > extension, which feels unnecessary to me. > > 2. *explicit*: defaulting rules must be explicitly imported, using a > syntax like `import M (default C)`. If we go this route, we will also need > to decide whether a plain `import M` should import defaulting rules. > Richard argues on GitHub that it should not, but I think that veers too far > from the existing behavior of imports. > > Between the two, I lean towards (2) for the symmetry between explicit > exports and imports, with the `import M` syntax pulling in defaulting rules. > > Eric > > > On Tue, May 25, 2021, at 16:01, Richard Eisenberg wrote: > > I have commented on GitHub with my thoughts here: > > > https://github.com/ghc-proposals/ghc-proposals/pull/409#issuecomment-848221001 > > > Thanks, > > Richard > > > > On May 20, 2021, at 11:24 AM, Alejandro Serrano Mena > wrote: > > > > > > Hi all, > > > > > > I agree with the recommendations of accepting (1) and rejecting (2) and > (3). The Report here ( > https://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-790004.3.4) > mentions that defaults are local to a module, and I think this is the right > move, even more so since we can think of other ways of importing/exporting > defaults, like plug-ins. > > > > > > Alejandro > > > > > > El 19 may 2021 4:11:48, Eric Seidel escribió: > > >> Hi all, > > >> > > >> Mario has proposed a handful of language extensions around type > defaulting. > > >> > > >> 1. NamedDefaults: this extension simply allows specifying the class to > default, instead of it always being Num (or a handful of other hardcoded > classes if one enables ExtendedDefaultRules). The rule only applies to the > current module, as usual. > > >> > > >> 2. ExportedDefaults: this extension allows exporting defaulting rules. > > >> > > >> 3. ImportedDefaults: this extension makes import declarations pull in > defaulting rules implicitly, like class instances. > > >> > > >> Extensions (2) and (3) work together to provide a mechanism for sharing > sets of defaulting rules across modules. It is possible to import > conflicting sets of defaulting rules from different modules, in that case > the conflict must be resolved manually by the importing module, with a new > defaulting rule. > > >> > > >> My recommendation is that we > > >> > > >> * Accept extension (1), as it is a clear improvement over the status > quo and can stand on its own. > > >> > > >> * Reject (without prejudice) extensions (2) and (3). These extensions > bring considerable extra complexity and another orphan-like mechanism. > There's an open question here of whether defaulting rules should be > globally coherent like type classes, or if they're something different; the > discussion has arguments for both sides. I'm not sure, and so I recommend > we don't commit ourselves one way or the other for now. > > >> > > >> Please take a look at the proposal. > > >> > > >> Discussion: https://github.com/ghc-proposals/ghc-proposals/pull/409 > > >> Proposal: > https://github.com/blamario/ghc-proposals/blob/exportable-named-default/proposals/0000-exportable-named-default.rst > > >> > > >> Eric > > >> > > >> On Sun, Apr 4, 2021, at 06:34, Joachim Breitner wrote: > > >>> Dear Committe, > > >>> > > >>> Exportable named defaults > > >>> has been proposed by Mario > > >>> https://github.com/ghc-proposals/ghc-proposals/pull/409 > > >>> > https://github.com/blamario/ghc-proposals/blob/exportable-named-default/proposals/0000-exportable-named-default.rst > > >>> > > >>> I propose Eric as the Shepherd. > > >>> > > >>> This did not gather a lot of attention on Github, or rather none, so > > >>> Eric, maybe also consider whether this needs to be advertised more, or > > >>> maybe who should be pointed to it. > > >>> > > >>> Please guide us to a conclusion as outlined in > > >>> https://github.com/ghc-proposals/ghc-proposals#committee-process > > >>> > > >>> Thanks, > > >>> Joachim > > >>> -- > > >>> -- > > >>> Joachim Breitner > > >>> mail at joachim-breitner.de > > >>> http://www.joachim-breitner.de/ > > >>> > > >>> > > >>> _______________________________________________ > > >>> ghc-steering-committee mailing list > > >>> ghc-steering-committee at haskell.org > > >>> > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > > >>> > > >> _______________________________________________ > > >> ghc-steering-committee mailing list > > >> ghc-steering-committee at haskell.org > > >> > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > > > _______________________________________________ > > > ghc-steering-committee mailing list > > > ghc-steering-committee at haskell.org > > > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > > > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > -------------- next part -------------- An HTML attachment was scrubbed... URL: From trupill at gmail.com Mon Jun 7 07:59:06 2021 From: trupill at gmail.com (Alejandro Serrano Mena) Date: Mon, 7 Jun 2021 07:59:06 +0000 Subject: [ghc-steering-committee] #351: NoIncomplete, rec: accept In-Reply-To: References: Message-ID: I am against this proposal, I would say that even in spirit. There are several reasons for this: - there’s still a lot of work going on on this same topic (there have been several papers on the matter in the last 5 years), so I fear that writing down a spec now would either: (1) deter others from trying, or (2) make those new rules under a flag like `ExtendedIncompletePatterns` which everybody will just blindly enable (like `FlexibleInstances` in the past); - for that reason, I think that incomplete patterns belong to the warning/error mechanism, something which can point to potential problems or unexpected behaviours. As part of the development of GHC those errors and warnings get better; - the extension is “too local”: it tells you that you’ve missed a case in *this* `case` statement. Yet, you can get pattern match errors if you use a function imported somewhere else which doesn’t account for that case. Regards, Alejandro El 29 may 2021 13:31:13, Simon Marlow escribió: > I would support this, but only if > 1. we specify precisely exactly which pattern matches are accepted, and > 2. GHC accepts only those patterns when NoIncomplete is enabled > > That is, it would certainly be a subset of -Wincomplete-patterns. No > cleverness, no adding extra magic to accept more programs with each > release. The point of a spec is to say exactly which programs are accepted, > in such a way that different implementations can implement the feature > consistently - one implementation is not allowed to accept more programs, > otherwise there's no point in having a definition of the feature. > > If we don't want to do this (and I suspect it would be annoying to > implement), then I think -Werror is the best alternative. > > Cheers > Simon > > On Wed, 26 May 2021 at 13:33, Vitaly Bragilevsky > wrote: > >> Dear Committee, >> >> We have been discussing the NoIncomplete pragma proposal by John Ericson >> for quite a long time. I think it's ready for acceptance. >> >> The proposal itself: >> https://github.com/ghc-proposals/ghc-proposals/pull/351 >> The rendered version: >> https://github.com/Ericson2314/ghc-proposals/blob/no-sugared-incompleteness/proposals/0000-no-incomplete.rst >> >> The proposal aims to introduce the NoIncomplete pragma that would >> prohibit programs which have a source of incompleteness (in patterns, in >> methods) in them. There is also the new -fdefer-incompleteness-errors flag. >> >> I think this feature comes quite handy in education. I'd use it all the >> time with my students. >> >> Please comment here or in the GitHub thread if you see any problems with >> this proposal. >> >> Vitaly >> >> _______________________________________________ >> ghc-steering-committee mailing list >> ghc-steering-committee at haskell.org >> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >> > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > -------------- next part -------------- An HTML attachment was scrubbed... URL: From marlowsd at gmail.com Mon Jun 7 08:19:34 2021 From: marlowsd at gmail.com (Simon Marlow) Date: Mon, 7 Jun 2021 09:19:34 +0100 Subject: [ghc-steering-committee] Proposal #281: Visible "forall" in terms; rec: accept In-Reply-To: References: <010f0179b44f4afa-768644d0-1b2f-4138-8016-17f0a0236dfd-000000@us-east-2.amazonses.com> Message-ID: As a user I usually need to know whether I'm looking at a type or a term in the code. For doing renaming in your head, it makes a difference whether you're looking at a type or a term: the namespaces are different. Is it reasonable for that to apply to visible type application too? That is, are we assuming that the user knows they're looking at a type, or are we assuming that the user "shouldn't need to care", or something else? I ask this question because, if we believe that the user should know when they're looking at a type, then it's reasonable to interpret types differently from terms even when they appear naked in the term context, as they do with visible type application. What could we do if we were allowed to treat types differently? Well, we already do various bits of magic in T2T. But we could also use different name resolution rules. That doesn't necessarily mean we have to defer renaming until during type checking: we could resolve each name twice, once for the term context and once for the type context, and then pick one of these later when we apply the T2T mapping. (earlier Vlad objected to this idea on the grounds that it might introduce spurious recursive dependencies, though). Cheers Simon On Wed, 2 Jun 2021 at 11:02, Simon Peyton Jones wrote: > Intuitively it doesn't seem unreasonable to add a little more magic to the > T2T mapping to preserve what (to me) seem to be reasonable expectations > > > > Yes, that was my view to begin with. But I can’t come up with any magic! > > > > I cleave strongly to the view that given a name like T, I should be able > to say what T is meant (the data constructor or the type constructor) > without knowing the type of the function applied to T, as in (f T). That > is, the renamer can do its work without thinking about types. This is the > Lexical Scoping Principle (LSP). > > > > Although the LSM makes GHC’s implementation much cleaner, it is not driven > by implementation considerations. it’s to do with user understanding. What > if that T isn’t the argument to a function, but appears in some other > context? What if `f` is polymorphic, so its type in turn depends on its > context? It goes on and on. > > > > So, if we espouse the LSP and see (f T), we can only say that T is the > data constructor. If you want the type constructor you can say (f (type > T)). This tension seems fundamental, not driven by implementation > considerations, nor by back-compat constraints, nor by GHC’s history. > There is no room for magic! > > > > You might wonder if we could do some magic for built-in syntax like [T]. > But it would be terribly strange to treat (f [T]) completely differently > from (f [T,T]), say. > > > > The only way I can see to add magic is to give up on the LSP. But I > really think that would be a Bad Thing. Indeed we recently removed the > only bit of GHC that didn’t obey the LSP: > https://github.com/adamgundry/ghc-proposals/blob/no-ambiguous-selectors/proposals/0000-no-ambiguous-field-access.rst > > > > If you have any other ideas, I’m all ears. > > > Simon > > > > *From:* Simon Marlow > *Sent:* 02 June 2021 10:06 > *To:* Simon Peyton Jones > *Cc:* Richard Eisenberg ; ghc-steering-committee < > ghc-steering-committee at haskell.org> > *Subject:* Re: [ghc-steering-committee] Proposal #281: Visible "forall" > in terms; rec: accept > > > > Thanks Richard and Simon - I think I understand the constraints better > now. I still find the conclusion somewhat unsatisfying, and I'm not sure I > could convincingly explain to someone why [Int] in a visible type argument > means something different from [Int] in a type signature. Intuitively it > doesn't seem unreasonable to add a little more magic to the T2T mapping to > preserve what (to me) seem to be reasonable expectations. But perhaps it's > my expectations that need to be adjusted. > > > > Cheers > > Simon > > > > On Tue, 1 Jun 2021 at 23:43, Simon Peyton Jones via ghc-steering-committee > wrote: > > I am generally in support. > > > > Working out the details in the dependent types proposal > > was extremely helpful. > > > > Like Simon, I’m sad that I have to write > > f (List Int) > > or > > f (type [Int]) > > but I think the alternative (of requiring the reader to know the type of > the function in order to resolve the binding of names in its argument) is > much, much worse. > > > > The tension here is fundamental if you want to have required type > arguments at all. *It’s not an artefact of GHC’s history, or the > constraints of the existing language.* (I suppose that in a new language > you might **only** provide “List Int” and “Pair a b”, but I do like [Int] > and (a,b) as types, and they will continue to work just fine in types.) > > > > So I have made my peace with it; and I really like the option of a “type” > herald to switch to type syntax. > > > > Simon > > > > *From:* ghc-steering-committee > *On Behalf Of *Richard Eisenberg > *Sent:* 28 May 2021 19:49 > *To:* ghc-steering-committee > *Subject:* [ghc-steering-committee] Proposal #281: Visible "forall" in > terms; rec: accept > > > > Hi committee, > > > > Proposal #281 has been submitted for our consideration. > > > > Proposal PR: https://github.com/ghc-proposals/ghc-proposals/pull/281 > > > Proposal text: > https://github.com/int-index/ghc-proposals/blob/visible-forall/proposals/0000-visible-forall.rst > > > > > The text of the proposal is long and detailed, but do not be daunted: it > is simpler in practice than it appears. > > > > The main payload of the proposal is: Introduce a new extension > -XRequiredTypeArguments. With this extension enabled, the `forall ... ->` > syntax, currently in existence in kinds, is now available in types (of > ordinary functions). This means that function definitions and call sites > are sometimes required to write a type argument. The type argument is *not* > preceded by @ or any other syntactic marker. > > > > This is useful for defining what would otherwise be ambiguous types. > Example: > > > > sizeof :: forall a -> Sizeable a => Int > > sizeof = ... > > > > intWidth = sizeof Int > > > > There are further examples and motivation in the proposal. > > > > The rest of the proposal is simply about dealing with odd corner cases > that come up with the main payload. In particular, mixing types in with > terms with no syntactic signifier means that we must be careful about > parsing and namespaces. If a type argument is written in the syntax that is > shared between types and terms (including function application!) and uses > identifiers in scope in only one of the two namespaces, nothing unusual can > be observed. But, of course, there are corner cases. Here are some of the > salient details: > > - Define type-syntax and term-syntax, where the choice of syntax is always > driven by syntactic markers, such as :: or @. See the dependent types > proposal > for > more details. Parsing and name-resolution are controlled by whether a > phrase is in type-syntax or term-syntax. For name resolution, if a lookup > fails in the first namespace (the term-level namespace in term-syntax or > the type-level namespace in type-syntax), we try the other namespace before > failing. > > - Because term- vs type-syntax is controlled by syntax, a required type > argument is in *term*-syntax and gets name-resolved *as a term*. In the > absence of punning, this works out fine, but it is possible that a punned > identifier will cause confusion. The proposal includes section 4.3 allowing > users to write `type` to signify a switch to type-syntax. > > - The proposal also includes a way to avoid punning for the built-in types > with privileged syntax: lists and tuples. This method allows users to > specify -XNoListTupleTypeSyntax to disable the list and tuple syntax in > types (but still allows it for terms). The proposal also suggests exporting > type List = [] from Data.List and other synonyms for tuples from Data.Tuple. > > > > --------------- > > > > I recommend acceptance. When doing type-level programming, the lack of > this feature is strange, leading to ambiguous types and easy-to-forget > arguments and easy-to-make type errors. The design space here is difficult, > but this proposal is very much in keeping with the design sketch of our > recently-accepted #378, in particular its section on this point > . > I believe the design described here is both backward compatible with what > we have today (users who do not use this feature will not notice a > difference) and forward compatible with a cohesive design for dependent > types. > > > > There are several optional pieces: > > - The `type` herald > . > I am unsure about this one, but others have felt strongly in favor, and I > have no reason to object. > > - Types-in-terms > . > I think this is necessary in order to avoid annoying definitions of type > synonyms for one-off usage sites. It is a straightforward extension of the > term-level parser to allow previously type-level-only constructs. It is > necessary in order for us to achieve the vision of dependent types in #378. > The only challenge here is that this requires us to make `forall` an > unconditional keyword in terms. This does pose a backward-compatibility > problem. I see, for example, that the sbv package exports a function named > `forall`, so we may need to think more carefully about how to proceed here > -- possibly by guarding the keyword-ness of `forall` behind the extension > for some number of transitionary releases. > > - Lists and Tuples > . > This section describes the -XNoListTupleTypeSyntax extension. I am not > convinced that this change needs to be part of this proposal (thinking it > belongs more in #270), but I do think we'll need it in the end. Is it OK to > export new type synonyms from Data.List and Data.Tuple? Not sure, though > I'd like these exported from some central place. > > > > What do others think? > > > > Thanks, > > Richard > > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lists at richarde.dev Tue Jun 8 17:16:23 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Tue, 8 Jun 2021 17:16:23 +0000 Subject: [ghc-steering-committee] #409: Exportable named defaults, Recommendation: Partial Accept In-Reply-To: <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> Message-ID: <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> Thanks for this summary! As I've argued on GitHub, I feel quite strongly against silent importing of defaulting, where "silent" means that code that compiles today might continue to compile tomorrow, but with defaults imported. Route (1) in Eric's email describes the need for a new extension to allow default imports. This avoids my problem with "silent", but I don't really like it. Route (2) is most natural in its "silent" mode (as Eric argues), but I really really don't want silent mode! So my ideas on GitHub are a bit funny-shaped. I would love if someone could come up with a better solution to this all, that avoids silence while still not being as awkward as my ideas on GitHub. All that said, I won't die on this hill, if the rest of the committee opts for a choice that allows silent default imports. Maybe I'd be happy enough with a warning (on by default) that a default was silently imported; users could suppress the warning by making the default import explicit. Perhaps even better (more precise) would be a warning when a default was silently imported and a constraint of the class of the default-import were defaulted. (It might be hard to say whether the import actually changed the defaulting behavior, so I won't ask for that. It would be enough just to know that an import was about the same class as the defaulting was.) Actually, this might be the middle road we can all like. Richard > On Jun 6, 2021, at 11:14 PM, Eric Seidel wrote: > > The response to the NamedDefaults extension has been uniformly positive, so I think we can consider that part accepted. > > However, we still need to make a decision about the ExportedDefaults extension. Since my original recommendation to reject this part of the proposal, I've come around to the argument that defaulting rules don't need global coherence like class instances, so explicit exports are fine. Simon PJ and Richard have also voiced support for explicit exports as suggested in the proposal. > > So I would like to revise my recommendation for ExportedDefaults to *accept*. > > That leaves the question of how defaulting rules should be imported. The two options are > > 1. *implicit*: all defaulting rules exported by a module M are automatically imported by *any* import of M, just like class instances. The proposal suggests doing this, and hiding it behind an `ImportedDefaults` extension, which feels unnecessary to me. > > 2. *explicit*: defaulting rules must be explicitly imported, using a syntax like `import M (default C)`. If we go this route, we will also need to decide whether a plain `import M` should import defaulting rules. Richard argues on GitHub that it should not, but I think that veers too far from the existing behavior of imports. > > Between the two, I lean towards (2) for the symmetry between explicit exports and imports, with the `import M` syntax pulling in defaulting rules. > > Eric > > > On Tue, May 25, 2021, at 16:01, Richard Eisenberg wrote: >> I have commented on GitHub with my thoughts here: >> https://github.com/ghc-proposals/ghc-proposals/pull/409#issuecomment-848221001 >> >> Thanks, >> Richard >> >>> On May 20, 2021, at 11:24 AM, Alejandro Serrano Mena wrote: >>> >>> Hi all, >>> >>> I agree with the recommendations of accepting (1) and rejecting (2) and (3). The Report here (https://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-790004.3.4) mentions that defaults are local to a module, and I think this is the right move, even more so since we can think of other ways of importing/exporting defaults, like plug-ins. >>> >>> Alejandro >>> >>> El 19 may 2021 4:11:48, Eric Seidel escribió: >>>> Hi all, >>>> >>>> Mario has proposed a handful of language extensions around type defaulting. >>>> >>>> 1. NamedDefaults: this extension simply allows specifying the class to default, instead of it always being Num (or a handful of other hardcoded classes if one enables ExtendedDefaultRules). The rule only applies to the current module, as usual. >>>> >>>> 2. ExportedDefaults: this extension allows exporting defaulting rules. >>>> >>>> 3. ImportedDefaults: this extension makes import declarations pull in defaulting rules implicitly, like class instances. >>>> >>>> Extensions (2) and (3) work together to provide a mechanism for sharing sets of defaulting rules across modules. It is possible to import conflicting sets of defaulting rules from different modules, in that case the conflict must be resolved manually by the importing module, with a new defaulting rule. >>>> >>>> My recommendation is that we >>>> >>>> * Accept extension (1), as it is a clear improvement over the status quo and can stand on its own. >>>> >>>> * Reject (without prejudice) extensions (2) and (3). These extensions bring considerable extra complexity and another orphan-like mechanism. There's an open question here of whether defaulting rules should be globally coherent like type classes, or if they're something different; the discussion has arguments for both sides. I'm not sure, and so I recommend we don't commit ourselves one way or the other for now. >>>> >>>> Please take a look at the proposal. >>>> >>>> Discussion: https://github.com/ghc-proposals/ghc-proposals/pull/409 >>>> Proposal: https://github.com/blamario/ghc-proposals/blob/exportable-named-default/proposals/0000-exportable-named-default.rst >>>> >>>> Eric >>>> >>>> On Sun, Apr 4, 2021, at 06:34, Joachim Breitner wrote: >>>>> Dear Committe, >>>>> >>>>> Exportable named defaults >>>>> has been proposed by Mario >>>>> https://github.com/ghc-proposals/ghc-proposals/pull/409 >>>>> https://github.com/blamario/ghc-proposals/blob/exportable-named-default/proposals/0000-exportable-named-default.rst >>>>> >>>>> I propose Eric as the Shepherd. >>>>> >>>>> This did not gather a lot of attention on Github, or rather none, so >>>>> Eric, maybe also consider whether this needs to be advertised more, or >>>>> maybe who should be pointed to it. >>>>> >>>>> Please guide us to a conclusion as outlined in >>>>> https://github.com/ghc-proposals/ghc-proposals#committee-process >>>>> >>>>> Thanks, >>>>> Joachim >>>>> -- >>>>> -- >>>>> Joachim Breitner >>>>> mail at joachim-breitner.de >>>>> http://www.joachim-breitner.de/ >>>>> >>>>> >>>>> _______________________________________________ >>>>> ghc-steering-committee mailing list >>>>> ghc-steering-committee at haskell.org >>>>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >>>>> >>>> _______________________________________________ >>>> ghc-steering-committee mailing list >>>> ghc-steering-committee at haskell.org >>>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >>> _______________________________________________ >>> ghc-steering-committee mailing list >>> ghc-steering-committee at haskell.org >>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >> > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee From eric at seidel.io Wed Jun 9 00:43:27 2021 From: eric at seidel.io (Eric Seidel) Date: Tue, 08 Jun 2021 20:43:27 -0400 Subject: [ghc-steering-committee] =?utf-8?q?=23409=3A_Exportable_named_def?= =?utf-8?q?aults=2C_Recommendation=3A_Partial_Accept?= In-Reply-To: <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> Message-ID: <77209cd3-2da0-4bda-8a09-a7870d7e9d22@www.fastmail.com> On Tue, Jun 8, 2021, at 13:16, Richard Eisenberg wrote: > Perhaps even better (more precise) would be a warning when a > default was silently imported and a constraint of the class of the > default-import were defaulted. I think a warning is very reasonable, but I'm not sure about turning it on by default. IMO, far and away the biggest use case for ExportedDefaults will be the myriad Prelude replacements (and maybe someday even the Prelude itself). For those use cases I think it's quite important that the import be a clean one-liner like import MyPrelude rather than import MyPrelude import MyPrelude (default IsString, default Num, ...) For other random modules that want to export defaults I feel much less strongly about the single import. Maybe that's an argument for a more baked-in way of installing a custom Prelude. Eric From arnaud.spiwack at tweag.io Fri Jun 11 07:05:52 2021 From: arnaud.spiwack at tweag.io (Spiwack, Arnaud) Date: Fri, 11 Jun 2021 09:05:52 +0200 Subject: [ghc-steering-committee] #283: Local modules (again), recommendation: accept In-Reply-To: <010f0179a8ac2bf6-879f696f-a2fa-4772-bc53-49ff9b52078e-000000@us-east-2.amazonses.com> References: <010f0179a585c6e0-378b7052-e39b-43d5-a72b-884ddef10f60-000000@us-east-2.amazonses.com> <010f0179a8ac2bf6-879f696f-a2fa-4772-bc53-49ff9b52078e-000000@us-east-2.amazonses.com> Message-ID: Dear all, Let me raise this proposal again. Very few of us have opined, and while I'd usually be happy to consider silence as assent, this is a rather large proposal which may require a few more pairs of eyes. Please consider giving this one a read and share your thoughts. If you can't do so right now, please let me know when you will be able to, so that we can plan accordingly. This is an important proposal, I'm keen on seeing its design finalised. /Arnaud On Wed, May 26, 2021 at 2:35 PM Richard Eisenberg wrote: > > > On May 26, 2021, at 3:28 AM, Spiwack, Arnaud > wrote: > > I'm realising that I inverted additional options 1 and 3 in my reply. To > spell things out: I'm in favour of the namespace introduced for every > datatype and such; and weakly in favour of anonymous modules, for which I > prefer the `_` syntax than simply omitting the name. > > > Oh, good. I was very confused here, but I decided not to push on it. I'm > similarly weakly in favor of (1), but I can't get myself to decide firmly > on whether to go with alternative (7). Going with (7) is a little more > consistent with other features, but it adds more symbols to the source text > that could otherwise be omitted. So I'm pretty ambivalent. > > Richard > > > On Tue, May 25, 2021 at 11:54 PM Richard Eisenberg > wrote: > >> >> >> On May 25, 2021, at 3:09 PM, Alejandro Serrano Mena >> wrote: >> >> - I am not sure of the benefit of allowing (1), compared with the >> possible surprise of users. >> - I do not fully understand (2). >> - I think (3) would be great, if we ensure that nothing changes if I >> don’t use “qualified”, even if -XLocalModules is on. >> >> >> If in the language, I would use (1) -- anonymous local modules -- >> regularly, when defining a function or class instance with a bunch of >> "local" helper functions. Of course, if we can't omit the module name, I >> will suffer no great harm. >> >> I cannot offer the guarantee you seek in (3), but I don't think you want >> it. (If nothing changes, then the feature has no effect!) Here is a >> scenario where (3) could cause trouble: >> >> import Data.Set as Set ( abcde ) >> >> data Set = Mk { abcdf :: Int } >> >> blah = Set.abcdf >> >> >> Previously, GHC would have suggested that you perhaps misspelled abcde. >> Now, you'll get (presumably) a type error. >> >> Here's another case: >> >> import Data.Set as Set ( Set ) >> >> data Set = Mk >> >> x :: Set.Set >> >> >> Everything is happy today, but with -XLocalModules (and (3)), the type of >> x is an ambiguous name. >> >> Any example that causes trouble, though, will have something in common: >> an imported module name (possibly via an alias) that matches a locally >> defined type name. I would imagine this pattern is rare in practice, and >> that the benefit of (3) would outweigh the number of times that a problem >> like this bites. >> >> I, too, could live without (2). >> >> Richard >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From arnaud.spiwack at tweag.io Fri Jun 11 10:14:50 2021 From: arnaud.spiwack at tweag.io (Spiwack, Arnaud) Date: Fri, 11 Jun 2021 12:14:50 +0200 Subject: [ghc-steering-committee] #409: Exportable named defaults, Recommendation: Partial Accept In-Reply-To: <77209cd3-2da0-4bda-8a09-a7870d7e9d22@www.fastmail.com> References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> <77209cd3-2da0-4bda-8a09-a7870d7e9d22@www.fastmail.com> Message-ID: I’m catching up here. Let me share a few thoughts: - I really want something like this (both for better OverloadedList support, and because it’s super useful in tests) - I’m rather unsure what to think about regarding the non-total priority (the fact that you can have default C (A, B); default D (B, A) and need to default a variable x with (C x, D x)). This sounds like something that must at least be specified. Am I correct that it isn’t? - There is no point in separating NamedDefaults and ExportedDefaults in two extensions - Regarding imports: in a first approximation explicit imports are useless. Having implicit imports lets me, for instance, define default IsList ([]) in the prelude, and then turn OverloadedList on in GHC2023 and not break existing programs. Yay. Explicit default imports just save me one copy-paste. Note by the way that if GHC2023 is the target, then the extension to import defaults would also have to be included in GHC2023, so, basically, ImportedDefaults is practically useless, and we should just import defaults (I don’t think a warning would make much sense for a normal default behaviour; I agree with Simon that this is not worse than importing overloaded instances). Still, there are some dark corners (I have pointed out one above, but I also find the exports and imports kind of difficult to wrap my head around). So I guess the conversation is not over quite yet. On Wed, Jun 9, 2021 at 2:44 AM Eric Seidel wrote: > On Tue, Jun 8, 2021, at 13:16, Richard Eisenberg wrote: > > Perhaps even better (more precise) would be a warning when a > > default was silently imported and a constraint of the class of the > > default-import were defaulted. > > I think a warning is very reasonable, but I'm not sure about turning it on > by default. > > IMO, far and away the biggest use case for ExportedDefaults will be the > myriad Prelude replacements (and maybe someday even the Prelude itself). > For those use cases I think it's quite important that the import be a clean > one-liner like > > import MyPrelude > > rather than > > import MyPrelude > import MyPrelude (default IsString, default Num, ...) > > For other random modules that want to export defaults I feel much less > strongly about the single import. Maybe that's an argument for a more > baked-in way of installing a custom Prelude. > > Eric > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > -------------- next part -------------- An HTML attachment was scrubbed... URL: From arnaud.spiwack at tweag.io Fri Jun 11 12:43:37 2021 From: arnaud.spiwack at tweag.io (Spiwack, Arnaud) Date: Fri, 11 Jun 2021 14:43:37 +0200 Subject: [ghc-steering-committee] #351: NoIncomplete, rec: accept In-Reply-To: References: Message-ID: I find myself in agreement with Richard's comment on Github. Even if we consider that a new language should implement the proposal (I'm not sure that I do, but I'm willing to be convinced), I don't think the difference with the current implementation is worth the change (and, in practice, maintaining both approaches). Vitaly, you initially recommended acceptance, maybe you want to argue further to try and change our minds? John hasn't replied to Richard's comment on Github yet. Let's see what he thinks about this, too. /Arnaud On Mon, Jun 7, 2021 at 9:59 AM Alejandro Serrano Mena wrote: > I am against this proposal, I would say that even in spirit. There are > several reasons for this: > - there’s still a lot of work going on on this same topic (there have been > several papers on the matter in the last 5 years), so I fear that writing > down a spec now would either: (1) deter others from trying, or (2) make > those new rules under a flag like `ExtendedIncompletePatterns` which > everybody will just blindly enable (like `FlexibleInstances` in the past); > - for that reason, I think that incomplete patterns belong to the > warning/error mechanism, something which can point to potential problems or > unexpected behaviours. As part of the development of GHC those errors and > warnings get better; > - the extension is “too local”: it tells you that you’ve missed a case in > *this* `case` statement. Yet, you can get pattern match errors if you use a > function imported somewhere else which doesn’t account for that case. > > Regards, > Alejandro > > El 29 may 2021 13:31:13, Simon Marlow escribió: > >> I would support this, but only if >> 1. we specify precisely exactly which pattern matches are accepted, and >> 2. GHC accepts only those patterns when NoIncomplete is enabled >> >> That is, it would certainly be a subset of -Wincomplete-patterns. No >> cleverness, no adding extra magic to accept more programs with each >> release. The point of a spec is to say exactly which programs are accepted, >> in such a way that different implementations can implement the feature >> consistently - one implementation is not allowed to accept more programs, >> otherwise there's no point in having a definition of the feature. >> >> If we don't want to do this (and I suspect it would be annoying to >> implement), then I think -Werror is the best alternative. >> >> Cheers >> Simon >> >> On Wed, 26 May 2021 at 13:33, Vitaly Bragilevsky >> wrote: >> >>> Dear Committee, >>> >>> We have been discussing the NoIncomplete pragma proposal by John Ericson >>> for quite a long time. I think it's ready for acceptance. >>> >>> The proposal itself: >>> https://github.com/ghc-proposals/ghc-proposals/pull/351 >>> The rendered version: >>> https://github.com/Ericson2314/ghc-proposals/blob/no-sugared-incompleteness/proposals/0000-no-incomplete.rst >>> >>> The proposal aims to introduce the NoIncomplete pragma that would >>> prohibit programs which have a source of incompleteness (in patterns, in >>> methods) in them. There is also the new -fdefer-incompleteness-errors flag. >>> >>> I think this feature comes quite handy in education. I'd use it all the >>> time with my students. >>> >>> Please comment here or in the GitHub thread if you see any problems with >>> this proposal. >>> >>> Vitaly >>> >>> _______________________________________________ >>> ghc-steering-committee mailing list >>> ghc-steering-committee at haskell.org >>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >>> >> _______________________________________________ >> ghc-steering-committee mailing list >> ghc-steering-committee at haskell.org >> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >> > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > -------------- next part -------------- An HTML attachment was scrubbed... URL: From arnaud.spiwack at tweag.io Fri Jun 11 12:55:41 2021 From: arnaud.spiwack at tweag.io (Spiwack, Arnaud) Date: Fri, 11 Jun 2021 14:55:41 +0200 Subject: [ghc-steering-committee] #392: Clarify modifiers design principle (recommendation: acceptance) In-Reply-To: References: Message-ID: I think that my discussion with Richard has come to a conclusion (it should incur a small modification to the proposal). It is a very small (amendment to a) proposal, let's find a consensus on this one quickly. On Wed, May 12, 2021 at 11:26 AM Spiwack, Arnaud wrote: > I've commented on the PR [ > https://github.com/ghc-proposals/ghc-proposals/pull/392#pullrequestreview-657652189 > ] the changes on the syntax of lambda expressions are not motivated at all, > I think at the very least there should be a discussion in the Alternatives > section. > > But mostly, I'm worried about the implications/interactions that these > changes have with linear types. > > (I'll be off for the rest of the week starting tonight, so I'll be back on > this conversation on Monday, most likely) > > On Tue, May 11, 2021 at 10:10 AM Alejandro Serrano Mena > wrote: > >> Dear Committee, >> This proposal seems a natural extension of #370, covering some additional >> cases (modifiers to classes and other declarations) that we’ve found along >> the way. My recommendation is acceptance. >> >> Regards, >> Alejandro >> >> On 4 May 2021 at 09:41:56, Joachim Breitner >> wrote: >> >>> Dear Committe, >>> >>> Clarify modifiers design principle >>> has been proposed by Richard >>> https://github.com/ghc-proposals/ghc-proposals/pull/392 >>> >>> This is an amendmend to #370, see the PR description for links to diffs >>> etc. >>> >>> I propose Alejandro as the shepherd, as he shepherded #370 before. >>> >>> Please guide us to a conclusion as outlined in >>> https://github.com/ghc-proposals/ghc-proposals#committee-process >>> >>> Thanks, >>> Joachim >>> -- >>> -- >>> Joachim Breitner >>> mail at joachim-breitner.de >>> http://www.joachim-breitner.de/ >>> >>> >>> _______________________________________________ >>> ghc-steering-committee mailing list >>> ghc-steering-committee at haskell.org >>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >>> >> _______________________________________________ >> ghc-steering-committee mailing list >> ghc-steering-committee at haskell.org >> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Fri Jun 11 15:15:50 2021 From: mail at joachim-breitner.de (Joachim Breitner) Date: Fri, 11 Jun 2021 17:15:50 +0200 Subject: [ghc-steering-committee] Please review #400: Constrained COMPLETE sets, Shepherd: Vladislav In-Reply-To: References: Message-ID: <14f7d2ffdc4a0f25e5d235e7b98863879f2677f9.camel@joachim-breitner.de> Dear Committee, it looks like Cale will not be able to handle this one, so I’d like to reassign to Vladislav. Vladislav, maybe comment on the Github thread that you are taking over, so that the author knows something is happening now, and ideally don’t let him wait too long here. Cheers, Joachim Am Montag, den 22.02.2021, 12:30 +0100 schrieb Joachim Breitner: > Dear Committee, > > this is your secretary speaking: > > Constrained COMPLETE sets > has been proposed by Sebastian Graph > https://github.com/ghc-proposals/ghc-proposals/pull/400 > https://github.com/sgraf812/ghc-proposals/blob/constrained-complete-sigs/proposals/0000-constrained-complete-sets.rst > > > This proposal tries to solve the same issue as Cale’s #399, and > essentially has slightly different syntax. I therefore suggest that > Cale is the shepherd, and hashes out with Sebastian the details of > syntax so that they can both get behind it, and then makes a > recommendation. > > Please guide us to a conclusion as outlined in > https://github.com/ghc-proposals/ghc-proposals#committee-process > > Thanks, > Joachim -- Joachim Breitner mail at joachim-breitner.de http://www.joachim-breitner.de/ From mail at joachim-breitner.de Fri Jun 11 15:19:29 2021 From: mail at joachim-breitner.de (Joachim Breitner) Date: Fri, 11 Jun 2021 17:19:29 +0200 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> Message-ID: Hi, Am Dienstag, den 27.10.2020, 18:52 +0100 schrieb Joachim Breitner: > Am Donnerstag, den 17.09.2020, 15:22 +0000 schrieb Simon Peyton Jones > via ghc-steering-committee: > > If it was re-cast as \mcase, which is just like \case but allows n- > > ary functions, I’d find it quite acceptable. The two then become > > extremely close, so there’s a very low cognitive load. > > > > GHC’s internals already allow this, and it seems surprisingly non- > > orthogonal that the source language does not. > > > > We could kill off MultiWayIf. > > > > But I don’t feel strongly. If a consensus does not emerge, maybe > > we should just vote. > > Cale, as the shepherd, could you lead us here to a resolution? I see > many voices in favor of rejection, but not really consensus yet. I’d like to reassing shepherding of this one. It seems to be clear that we want “something like this”, there are many ways to skin the cat, so it comes down to opinion and what we need is a decision (or a call to votes). As with anything that’s possibly quite opinionated, it’s good to have an authorative voice, so in this case, Simon PJ. Simon, can you either come up with a “all things considered, I think this variant is the (narrowly) the best” recommendation or, alternative, a “please vote on the following options” verdict? Cheers, Joachim -- Joachim Breitner mail at joachim-breitner.de http://www.joachim-breitner.de/ From vlad.z.4096 at gmail.com Mon Jun 14 14:09:06 2021 From: vlad.z.4096 at gmail.com (Vladislav Zavialov (int-index)) Date: Mon, 14 Jun 2021 17:09:06 +0300 Subject: [ghc-steering-committee] Proposal #412: Explicit Splice Imports; rec: accept Message-ID: Dear Committee, Proposal #412 "Explicit Splice Imports” by Matthew Pickering has been submitted for our consideration. Read it here: https://github.com/mpickering/ghc-proposals/blob/splice-imports/proposals/0000-splice-imports.rst Discussion here: https://github.com/ghc-proposals/ghc-proposals/pull/412 The goals of this proposal are to (1) improve parallel compilation, (2) speed up -fno-code and IDEs that rely on it, (3) reduce binary sizes or at least reduce linking overhead, (4) create phase separation useful for cross-compilation. All of the above are achieved by introducing a new form of import called a splice-import. Compare: import M import splice H Under this proposal, names imported from M can *not* be used in top-level Template Haskell splices, whereas names imported from H can be used *only* in Template Haskell splices. At this point I will note that I do not particularly like the proposed syntax, which looks as if we’re importing a splice rather than importing names for use in splices. In the “Alternatives” section, you will find several other options such as “import {-# SPLICE #-} M”, “import for splice H”, “$(import H)”, and so on. That said, let us not get bogged down in the discussion of syntax before we agree on the semantics. If we choose to accept the proposal, I will organize a vote on the syntax. Regarding the semantics, I believe the general idea behind the proposal is good, and I recommend acceptance. It provides a way for the programmer to specify the intended usage of an import (whether it is for normal programming or metaprogramming), and GHC can use this information to build the program more effectively (more parallelism, less linking). In ways that I do not entirely understand, it is allegedly good for future work on cross-compilation. Let me know what you think. - Vlad From trupill at gmail.com Tue Jun 15 07:01:55 2021 From: trupill at gmail.com (Alejandro Serrano Mena) Date: Tue, 15 Jun 2021 02:01:55 -0500 Subject: [ghc-steering-committee] Proposal #412: Explicit Splice Imports; rec: accept In-Reply-To: References: Message-ID: Dear all, I like the proposal, and I think my life will automatically improve with this. Alejandro El 14 jun 2021 16:09:06, Vladislav Zavialov (int-index) < vlad.z.4096 at gmail.com> escribió: > Dear Committee, > > Proposal #412 "Explicit Splice Imports” by Matthew Pickering has been > submitted for our consideration. > > Read it here: > https://github.com/mpickering/ghc-proposals/blob/splice-imports/proposals/0000-splice-imports.rst > Discussion here: https://github.com/ghc-proposals/ghc-proposals/pull/412 > > The goals of this proposal are to (1) improve parallel compilation, (2) > speed up -fno-code and IDEs that rely on it, (3) reduce binary sizes or at > least reduce linking overhead, (4) create phase separation useful for > cross-compilation. > > All of the above are achieved by introducing a new form of import called a > splice-import. Compare: > > import M > import splice H > > Under this proposal, names imported from M can *not* be used in top-level > Template Haskell splices, whereas names imported from H can be used *only* > in Template Haskell splices. > > At this point I will note that I do not particularly like the proposed > syntax, which looks as if we’re importing a splice rather than importing > names for use in splices. In the “Alternatives” section, you will find > several other options such as “import {-# SPLICE #-} M”, “import for splice > H”, “$(import H)”, and so on. That said, let us not get bogged down in the > discussion of syntax before we agree on the semantics. If we choose to > accept the proposal, I will organize a vote on the syntax. > > Regarding the semantics, I believe the general idea behind the proposal is > good, and I recommend acceptance. It provides a way for the programmer to > specify the intended usage of an import (whether it is for normal > programming or metaprogramming), and GHC can use this information to build > the program more effectively (more parallelism, less linking). In ways that > I do not entirely understand, it is allegedly good for future work on > cross-compilation. > > Let me know what you think. > > - Vlad > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vlad.z.4096 at gmail.com Tue Jun 15 07:01:59 2021 From: vlad.z.4096 at gmail.com (Vladislav Zavialov (int-index)) Date: Tue, 15 Jun 2021 10:01:59 +0300 Subject: [ghc-steering-committee] Please review #400: Constrained COMPLETE sets, Shepherd: Vladislav In-Reply-To: <14f7d2ffdc4a0f25e5d235e7b98863879f2677f9.camel@joachim-breitner.de> References: <14f7d2ffdc4a0f25e5d235e7b98863879f2677f9.camel@joachim-breitner.de> Message-ID: I have read the proposal and sent it back for revision, as I found that the change is underspecified (the interaction with GADTs is unclear). - Vlad > On 11 Jun 2021, at 18:15, Joachim Breitner wrote: > > Dear Committee, > > it looks like Cale will not be able to handle this one, so I’d like to > reassign to Vladislav. > > Vladislav, maybe comment on the Github thread that you are taking over, > so that the author knows something is happening now, and ideally don’t > let him wait too long here. > > Cheers, > Joachim > > Am Montag, den 22.02.2021, 12:30 +0100 schrieb Joachim Breitner: >> Dear Committee, >> >> this is your secretary speaking: >> >> Constrained COMPLETE sets >> has been proposed by Sebastian Graph >> https://github.com/ghc-proposals/ghc-proposals/pull/400 >> https://github.com/sgraf812/ghc-proposals/blob/constrained-complete-sigs/proposals/0000-constrained-complete-sets.rst >> >> >> This proposal tries to solve the same issue as Cale’s #399, and >> essentially has slightly different syntax. I therefore suggest that >> Cale is the shepherd, and hashes out with Sebastian the details of >> syntax so that they can both get behind it, and then makes a >> recommendation. >> >> Please guide us to a conclusion as outlined in >> https://github.com/ghc-proposals/ghc-proposals#committee-process >> >> Thanks, >> Joachim > -- > Joachim Breitner > mail at joachim-breitner.de > http://www.joachim-breitner.de/ > > > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee From simonpj at microsoft.com Tue Jun 15 12:52:11 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 15 Jun 2021 12:52:11 +0000 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> Message-ID: | I'd like to reassing shepherding of this one. | | It seems to be clear that we want "something like this", there are many ways | to skin the cat, so it comes down to opinion and what we need is a decision | (or a call to votes). As with anything that's possibly quite opinionated, | it's good to have an authorative voice, so in this case, Simon PJ. | | Simon, can you either come up with a "all things considered, I think this | variant is the (narrowly) the best" recommendation or, alternative, a | "please vote on the following options" verdict? OK, to remind everyone * Here is the proposal: https://github.com/JakobBruenker/ghc-proposals/blob/patch-1/proposals/0000-lambda-layout.md * Here is the discussion: https://github.com/ghc-proposals/ghc-proposals/pull/302 The basic idea is to extend to lambda all the facilities that you get with function definitions, especially multiple patterns and guards. This seems clearly a good idea, whose only obstacle is syntactic. There are no conceptual or specification challenges. The only point at issue is that of concrete syntax. The proposal offers four possible syntactic options. After reviewing, I propose to discard (2) and (3) leaving these alternatives * Option (1) \cases { p1 p2 -> rhs1; q1 q2 -> rhs2 } * Lives alongside \case, but allows multiple patterns * Other keywords are possible, but I think it must be a variant on \case * Option (4) Same, but use \case as the keyword * Incompatible with existing \case => extended transition period, unhappy users * \case { (Just x) -> rhs1; Nothing -> rhs2 } will require parens forever, which in the common case of a one argument lambda see clunky. * Option (X). Reject the proposal. Personally I favour (1). I'm relaxed about having multiple ways of saying the thing (think of let vs where), and I see no harm provided the two constructs look and behave the same. I've decided I like \cases precisely because it's the plural of \case, which is exactly what is going on. I think we'll end up having to vote on this, which is fine when it's a judgement call about syntax. But first: * Are there any other alternatives you strongly want on the ballot? I say "strongly" because I don't want to open up a big new debate... we at the stage of trying to narrow options. Thanks Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Tue Jun 15 14:25:35 2021 From: mail at joachim-breitner.de (Joachim Breitner) Date: Tue, 15 Jun 2021 16:25:35 +0200 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> Message-ID: <8b6a391317fa63b660c1bd2cfe74ded2c3df1384.camel@joachim-breitner.de> Hi, thanks for narrowing down the option, I am happy with direction, and have nothing urgent to add. Option (3), XExtendedCase, is in a way cute, but probably too playful for its own good. I think (1) is a good way forward, and balances elegance with backward compatibility (by not conflicting with the popular \case) well. We can have some fun coming up with the right name (\cases? \of? \mcase? \function?). My solution to avoid spending too much time on that particular bike shed color is just to include all reasonable variants on the ballot and let ranked voting sort it out for us. Cheers, Joachim Am Dienstag, den 15.06.2021, 12:52 +0000 schrieb Simon Peyton Jones via ghc-steering-committee: > I think we’ll end up having to vote on this, which is fine when it’s a judgement call about syntax. But first: -- Joachim Breitner mail at joachim-breitner.de http://www.joachim-breitner.de/ From marlowsd at gmail.com Wed Jun 16 12:20:51 2021 From: marlowsd at gmail.com (Simon Marlow) Date: Wed, 16 Jun 2021 13:20:51 +0100 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> Message-ID: I'm still in favour of Option (X), reject the proposal, for the same reasons as before (copied below). I think it was Cale who first proposed rejection: https://github.com/ghc-proposals/ghc-proposals/pull/302#issuecomment-666075014 My previous email on this, although it talks about \of, applies equally to \case and \cases: > Cale's rationale chimes with me. A lot - I feel like I might have even made the same point in previous threads on this. I think of the tradeoff like this: > * The lack of \of doesn't really hurt very much. In fact, arguably by forcing the author to type some more characters and give something a name, we get code that's clearer for the reader. (yes this is very subjective, but syntax is). > * The addition of \of *would* hurt new users of the language. Only a bit, but every bit makes things worse, and things are already quite bad. And I also came across this from Richard during the last thread: > Even so, I agree with Cale's recommendation to reject. We just have too much syntax! If someone were to come along and draft a concrete proposal of how we could, for example, use this syntax to replace both \case and if|, with a migration strategy, etc., then I might be in favor. Until then, I think we've spent our budget for cute, obscure bits of syntax. Cheers Simon On Tue, 15 Jun 2021 at 13:52, Simon Peyton Jones via ghc-steering-committee wrote: > | I’d like to reassing shepherding of this one. > > | > > | It seems to be clear that we want “something like this”, there are many > ways > > | to skin the cat, so it comes down to opinion and what we need is a > decision > > | (or a call to votes). As with anything that’s possibly quite > opinionated, > > | it’s good to have an authorative voice, so in this case, Simon PJ. > > | > > | Simon, can you either come up with a “all things considered, I think > this > > | variant is the (narrowly) the best” recommendation or, alternative, a > > | “please vote on the following options” verdict? > > > > OK, to remind everyone > > - Here is the proposal: > https://github.com/JakobBruenker/ghc-proposals/blob/patch-1/proposals/0000-lambda-layout.md > - Here is the discussion: > https://github.com/ghc-proposals/ghc-proposals/pull/302 > > > > The basic idea is to extend to lambda all the facilities that you get with > function definitions, especially multiple patterns and guards. This seems > clearly a good idea, whose only obstacle is syntactic. There are no > conceptual or specification challenges. The only point at issue is that of > concrete syntax. > > > > The proposal offers four possible syntactic options. After reviewing, I > propose to discard (2) and (3) leaving these alternatives > > > > - *Option (1) *\cases { p1 p2 -> rhs1; q1 q2 -> rhs2 } > - Lives alongside \case, but allows multiple patterns > - Other keywords are possible, but I think it must be a variant on > \case > - *Option (4)* Same, but use \case as the keyword > - Incompatible with existing \case => extended transition period, > unhappy users > - \case { (Just x) -> rhs1; Nothing -> rhs2 } will require parens > forever, which in the common case of a one argument lambda see clunky. > - *Option (X).* Reject the proposal. > > > > Personally I favour (1). I’m relaxed about having multiple ways of > saying the thing (think of let vs where), and I see no harm provided the > two constructs look and behave the same. I’ve decided I like \cases > precisely because it’s the plural of \case, which is exactly what is going > on. > > I think we’ll end up having to vote on this, which is fine when it’s a > judgement call about syntax. But first: > > - *Are there any other alternatives you strongly want on the ballot?* > > I say “strongly” because I don’t want to open up a big new debate… we at > the stage of trying to narrow options. > > Thanks > > Simon > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > -------------- next part -------------- An HTML attachment was scrubbed... URL: From eric at seidel.io Thu Jun 17 02:12:52 2021 From: eric at seidel.io (Eric Seidel) Date: Wed, 16 Jun 2021 22:12:52 -0400 Subject: [ghc-steering-committee] =?utf-8?q?=23409=3A_Exportable_named_def?= =?utf-8?q?aults=2C_Recommendation=3A_Partial_Accept?= In-Reply-To: References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> <77209cd3-2da0-4bda-8a09-a7870d7e9d22@www.fastmail.com> Message-ID: <7a913d64-b6a7-4d51-9b6c-7c6e9d2011d6@www.fastmail.com> On Fri, Jun 11, 2021, at 06:14, Spiwack, Arnaud wrote: > * I’m rather unsure what to think about regarding the non-total > priority (the fact that you can have `default C (A, B); default D (B, > A)` and need to default a variable `x` with `(C x, D x)`). This sounds > like something that must at least be specified. Am I correct that it > isn’t? It is specified to be a static error, and the solution is either - define your own, consistent default rules for C and D in the current module, OR - ascribe types to the ambiguous use-sites and bypass default resolution entirely. See sections [2.5] and [5.1] in the proposal. It's a bit of a sharp edge, to be sure. But defaulting rules are anti-modular much like type classes, and I think this is the most sensible thing to do here. [2.5]: https://github.com/blamario/ghc-proposals/blob/exportable-named-default/proposals/0000-exportable-named-default.rst#25rules-for-disambiguation-at-the-use-site [5.1]: https://github.com/blamario/ghc-proposals/blob/exportable-named-default/proposals/0000-exportable-named-default.rst#51use-site-conflicts > * Regarding imports: in a first approximation explicit imports are > useless. Having implicit imports lets me, for instance, define `default > IsList ([])` in the prelude, and then turn `OverloadedList` on in > `GHC2023` and not break existing programs. There's a bit of a subtlety here in the use of "explicit" vs "implicit", and I'm not sure how you're using them here. We have at least three proposals for the behavior of imports. Given ``` module Defaults where default IsString (Text) ``` (A) Fully implicit (like class instances) ``` import Defaults -- imports `default IsString (Text)` import Defaults () -- imports `default IsString (Text)` ``` (B) Fully explicit (Richard's preference, I believe) ``` import Defaults -- does not import `default IsString (Text)` import Defaults () -- does not import `default IsString (Text)` import Defaults (default IsString) -- imports `default IsString (Text)` ``` (C) Like normal values ``` import Defaults -- imports `default IsString (Text)` import Defaults () -- does not import `default IsString (Text)` import Defaults (default IsString) -- imports `default IsString (Text)` ``` Since the Prelude is implicitly imported without an import list, both A and C would let you avoid an extra import. Same goes for Prelude replacements. Eric From arnaud.spiwack at tweag.io Thu Jun 17 13:13:44 2021 From: arnaud.spiwack at tweag.io (Spiwack, Arnaud) Date: Thu, 17 Jun 2021 15:13:44 +0200 Subject: [ghc-steering-committee] Proposal #412: Explicit Splice Imports; rec: accept In-Reply-To: References: Message-ID: I agree with the sentiment so far: this is a well constructed proposal which makes a good case for the fine details of the proposed specification. The goal is also quite desirable (it has been brought up by other before, such as http://blog.ezyang.com/2016/07/what-template-haskell-gets-wrong-and-racket-gets-right/ or https://github.com/ghc-proposals/ghc-proposals/pull/243 ). On Tue, Jun 15, 2021 at 9:02 AM Alejandro Serrano Mena wrote: > Dear all, > I like the proposal, and I think my life will automatically improve with > this. > > Alejandro > > El 14 jun 2021 16:09:06, Vladislav Zavialov (int-index) < > vlad.z.4096 at gmail.com> escribió: > >> Dear Committee, >> >> Proposal #412 "Explicit Splice Imports” by Matthew Pickering has been >> submitted for our consideration. >> >> Read it here: >> https://github.com/mpickering/ghc-proposals/blob/splice-imports/proposals/0000-splice-imports.rst >> Discussion here: https://github.com/ghc-proposals/ghc-proposals/pull/412 >> >> The goals of this proposal are to (1) improve parallel compilation, (2) >> speed up -fno-code and IDEs that rely on it, (3) reduce binary sizes or at >> least reduce linking overhead, (4) create phase separation useful for >> cross-compilation. >> >> All of the above are achieved by introducing a new form of import called >> a splice-import. Compare: >> >> import M >> import splice H >> >> Under this proposal, names imported from M can *not* be used in top-level >> Template Haskell splices, whereas names imported from H can be used *only* >> in Template Haskell splices. >> >> At this point I will note that I do not particularly like the proposed >> syntax, which looks as if we’re importing a splice rather than importing >> names for use in splices. In the “Alternatives” section, you will find >> several other options such as “import {-# SPLICE #-} M”, “import for splice >> H”, “$(import H)”, and so on. That said, let us not get bogged down in the >> discussion of syntax before we agree on the semantics. If we choose to >> accept the proposal, I will organize a vote on the syntax. >> >> Regarding the semantics, I believe the general idea behind the proposal >> is good, and I recommend acceptance. It provides a way for the programmer >> to specify the intended usage of an import (whether it is for normal >> programming or metaprogramming), and GHC can use this information to build >> the program more effectively (more parallelism, less linking). In ways that >> I do not entirely understand, it is allegedly good for future work on >> cross-compilation. >> >> Let me know what you think. >> >> - Vlad >> _______________________________________________ >> ghc-steering-committee mailing list >> ghc-steering-committee at haskell.org >> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >> > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > -------------- next part -------------- An HTML attachment was scrubbed... URL: From arnaud.spiwack at tweag.io Thu Jun 17 14:08:27 2021 From: arnaud.spiwack at tweag.io (Spiwack, Arnaud) Date: Thu, 17 Jun 2021 16:08:27 +0200 Subject: [ghc-steering-committee] #409: Exportable named defaults, Recommendation: Partial Accept In-Reply-To: <7a913d64-b6a7-4d51-9b6c-7c6e9d2011d6@www.fastmail.com> References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> <77209cd3-2da0-4bda-8a09-a7870d7e9d22@www.fastmail.com> <7a913d64-b6a7-4d51-9b6c-7c6e9d2011d6@www.fastmail.com> Message-ID: On Thu, Jun 17, 2021 at 4:13 AM Eric Seidel wrote: > It is specified to be a static error, and the solution is either > > - define your own, consistent default rules for C and D in the current > module, OR > - ascribe types to the ambiguous use-sites and bypass default resolution > entirely. > Indeed. I'm convinced. Since the Prelude is implicitly imported without an import list, both A and > C would let you avoid an extra import. Same goes for Prelude replacements. > I fully agree with this statement. (I don't think that I have a preference between A and C) -------------- next part -------------- An HTML attachment was scrubbed... URL: From eric at seidel.io Mon Jun 21 02:24:24 2021 From: eric at seidel.io (Eric Seidel) Date: Sun, 20 Jun 2021 22:24:24 -0400 Subject: [ghc-steering-committee] =?utf-8?q?=23409=3A_Exportable_named_def?= =?utf-8?q?aults=2C_Recommendation=3A_Partial_Accept?= In-Reply-To: References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> <77209cd3-2da0-4bda-8a09-a7870d7e9d22@www.fastmail.com> <7a913d64-b6a7-4d51-9b6c-7c6e9d2011d6@www.fastmail.com> Message-ID: On Thu, Jun 17, 2021, at 10:08, Spiwack, Arnaud wrote: > > Since the Prelude is implicitly imported without an import list, both A and C would let you avoid an extra import. Same goes for Prelude replacements. > > I fully agree with this statement. (I don't think that I have a > preference between A and C) Great, then I think we have broad support among the committee members who've participated in this discussion for some form of implicit import of defaulting rules. I recommend we treat defaulting rules like any other importable entity to match how the proposal treats them in export lists, ie given ``` module Defaults where default IsString (Text) ``` we have the following import behavior ``` import Defaults -- imports `default IsString (Text)` import Defaults () -- does not import `default IsString (Text)` import Defaults (default IsString) -- imports `default IsString (Text)` import Defaults hiding (default IsString) -- does not import `default IsString (Text)` import Defaults qualified -- imports `default IsString (Text)` ``` By my reading, Simon PJ, Joachim, Alejandro, Arnaud, and Richard (provided we have a warning) should all be happy with this path. I believe we also have broad agreement that imports need not be guarded by any extension. If you disagree please speak up! I have not heard anything from Vitaly, Cale, Tom, Simon M, or Vlad. If you have any thoughts on this proposal, please speak up now. I'll discuss the proposed changes (treating imported defaults like other importable entities, and the warning) with the author. As usual, I'll treat silence from the committee as assent, and will declare the proposal accepted next Sunday 6/27 if there are no objections. Thanks! Eric From arnaud.spiwack at tweag.io Mon Jun 21 06:59:22 2021 From: arnaud.spiwack at tweag.io (Spiwack, Arnaud) Date: Mon, 21 Jun 2021 08:59:22 +0200 Subject: [ghc-steering-committee] #409: Exportable named defaults, Recommendation: Partial Accept In-Reply-To: References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> <77209cd3-2da0-4bda-8a09-a7870d7e9d22@www.fastmail.com> <7a913d64-b6a7-4d51-9b6c-7c6e9d2011d6@www.fastmail.com> Message-ID: Note: Richard, who is the main proponent of the explicit import idea is on holiday this week, so we will not hear from him, and should not consider his silence as approval. > I recommend we treat defaulting rules like any other importable entity to match how the proposal treats them in export lists Sounds reasonable to me. On Mon, Jun 21, 2021 at 4:27 AM Eric Seidel wrote: > On Thu, Jun 17, 2021, at 10:08, Spiwack, Arnaud wrote: > > > Since the Prelude is implicitly imported without an import list, both > A and C would let you avoid an extra import. Same goes for Prelude > replacements. > > > > I fully agree with this statement. (I don't think that I have a > > preference between A and C) > > Great, then I think we have broad support among the committee members > who've participated in this discussion for some form of implicit import of > defaulting rules. I recommend we treat defaulting rules like any other > importable entity to match how the proposal treats them in export lists, ie > given > > ``` > module Defaults where > default IsString (Text) > ``` > > we have the following import behavior > > ``` > import Defaults -- imports `default IsString (Text)` > import Defaults () -- does not import `default IsString (Text)` > import Defaults (default IsString) -- imports `default IsString (Text)` > import Defaults hiding (default IsString) -- does not import `default > IsString (Text)` > import Defaults qualified -- imports `default IsString (Text)` > ``` > > By my reading, Simon PJ, Joachim, Alejandro, Arnaud, and Richard (provided > we have a warning) should all be happy with this path. I believe we also > have broad agreement that imports need not be guarded by any extension. If > you disagree please speak up! > > I have not heard anything from Vitaly, Cale, Tom, Simon M, or Vlad. If you > have any thoughts on this proposal, please speak up now. > > I'll discuss the proposed changes (treating imported defaults like other > importable entities, and the warning) with the author. As usual, I'll treat > silence from the committee as assent, and will declare the proposal > accepted next Sunday 6/27 if there are no objections. > > Thanks! > Eric > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Jun 24 10:52:10 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 24 Jun 2021 10:52:10 +0000 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> Message-ID: Dear Steering committee Simon and Joachim have responded, but only those two . Please reply! Thanks Simon From: ghc-steering-committee On Behalf Of Simon Peyton Jones via ghc-steering-committee Sent: 15 June 2021 13:52 To: Joachim Breitner ; ghc-steering-committee at haskell.org Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) | I'd like to reassing shepherding of this one. | | It seems to be clear that we want "something like this", there are many ways | to skin the cat, so it comes down to opinion and what we need is a decision | (or a call to votes). As with anything that's possibly quite opinionated, | it's good to have an authorative voice, so in this case, Simon PJ. | | Simon, can you either come up with a "all things considered, I think this | variant is the (narrowly) the best" recommendation or, alternative, a | "please vote on the following options" verdict? OK, to remind everyone * Here is the proposal: https://github.com/JakobBruenker/ghc-proposals/blob/patch-1/proposals/0000-lambda-layout.md * Here is the discussion: https://github.com/ghc-proposals/ghc-proposals/pull/302 The basic idea is to extend to lambda all the facilities that you get with function definitions, especially multiple patterns and guards. This seems clearly a good idea, whose only obstacle is syntactic. There are no conceptual or specification challenges. The only point at issue is that of concrete syntax. The proposal offers four possible syntactic options. After reviewing, I propose to discard (2) and (3) leaving these alternatives * Option (1) \cases { p1 p2 -> rhs1; q1 q2 -> rhs2 } * Lives alongside \case, but allows multiple patterns * Other keywords are possible, but I think it must be a variant on \case * Option (4) Same, but use \case as the keyword * Incompatible with existing \case => extended transition period, unhappy users * \case { (Just x) -> rhs1; Nothing -> rhs2 } will require parens forever, which in the common case of a one argument lambda see clunky. * Option (X). Reject the proposal. Personally I favour (1). I'm relaxed about having multiple ways of saying the thing (think of let vs where), and I see no harm provided the two constructs look and behave the same. I've decided I like \cases precisely because it's the plural of \case, which is exactly what is going on. I think we'll end up having to vote on this, which is fine when it's a judgement call about syntax. But first: * Are there any other alternatives you strongly want on the ballot? I say "strongly" because I don't want to open up a big new debate... we at the stage of trying to narrow options. Thanks Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From trupill at gmail.com Thu Jun 24 11:02:58 2021 From: trupill at gmail.com (Alejandro Serrano Mena) Date: Thu, 24 Jun 2021 11:02:58 +0000 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> Message-ID: Dear all, To be honest, I’m still trying to make up my mind about this. If we were to accept the proposal, I think option (1) is the best one, since it otherwise `\case` would have a different behaviour depending on whether you have -XLambdaCase or -XExtendedLambdaCase on. Having said so, the words of Simon M. and Richard resonate with me: do we really want \case, \cases, if|, all in the language? - I would prefer one single way to do stuff, let’s say having a `cases … of` which also works as case, if|… and then a \cases for lambdas; - but this is not the world we live in! We already have those things, and this would be yet another small syntactic addition, so we need to think about whether the language is becoming too big. So right now I’m in favor of option (X), reject the proposal. Regards, Alejandro El 24 jun 2021 12:52:10, Simon Peyton Jones via ghc-steering-committee < ghc-steering-committee at haskell.org> escribió: > Dear Steering committee > > Simon and Joachim have responded, but only those two . Please reply! > > Thanks > > Simon > > > > *From:* ghc-steering-committee > *On Behalf Of *Simon Peyton Jones via ghc-steering-committee > *Sent:* 15 June 2021 13:52 > *To:* Joachim Breitner ; > ghc-steering-committee at haskell.org > *Subject:* Re: [ghc-steering-committee] Proposal #302: `\of` (New > Shepherd: Simon PJ) > > > > | I’d like to reassing shepherding of this one. > > | > > | It seems to be clear that we want “something like this”, there are many > ways > > | to skin the cat, so it comes down to opinion and what we need is a > decision > > | (or a call to votes). As with anything that’s possibly quite > opinionated, > > | it’s good to have an authorative voice, so in this case, Simon PJ. > > | > > | Simon, can you either come up with a “all things considered, I think > this > > | variant is the (narrowly) the best” recommendation or, alternative, a > > | “please vote on the following options” verdict? > > > > OK, to remind everyone > > - Here is the proposal: > https://github.com/JakobBruenker/ghc-proposals/blob/patch-1/proposals/0000-lambda-layout.md > > - Here is the discussion: > https://github.com/ghc-proposals/ghc-proposals/pull/302 > > > > > The basic idea is to extend to lambda all the facilities that you get with > function definitions, especially multiple patterns and guards. This seems > clearly a good idea, whose only obstacle is syntactic. There are no > conceptual or specification challenges. The only point at issue is that of > concrete syntax. > > > > The proposal offers four possible syntactic options. After reviewing, I > propose to discard (2) and (3) leaving these alternatives > > > > - *Option (1) *\cases { p1 p2 -> rhs1; q1 q2 -> rhs2 } > > > - Lives alongside \case, but allows multiple patterns > - Other keywords are possible, but I think it must be a variant on > \case > > > - *Option (4)* Same, but use \case as the keyword > > > - Incompatible with existing \case => extended transition period, > unhappy users > - \case { (Just x) -> rhs1; Nothing -> rhs2 } will require parens > forever, which in the common case of a one argument lambda see clunky. > > > - *Option (X).* Reject the proposal. > > > > Personally I favour (1). I’m relaxed about having multiple ways of > saying the thing (think of let vs where), and I see no harm provided the > two constructs look and behave the same. I’ve decided I like \cases > precisely because it’s the plural of \case, which is exactly what is going > on. > > I think we’ll end up having to vote on this, which is fine when it’s a > judgement call about syntax. But first: > > - *Are there any other alternatives you strongly want on the ballot?* > > I say “strongly” because I don’t want to open up a big new debate… we at > the stage of trying to narrow options. > > Thanks > > Simon > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > -------------- next part -------------- An HTML attachment was scrubbed... URL: From trupill at gmail.com Thu Jun 24 11:29:43 2021 From: trupill at gmail.com (Alejandro Serrano Mena) Date: Thu, 24 Jun 2021 11:29:43 +0000 Subject: [ghc-steering-committee] #392: Clarify modifiers design principle (recommendation: acceptance) In-Reply-To: References: Message-ID: Dear all, This discussion has been dormant for some time, but it’s time to revive it! Richard, Arnaud, did you manage to reach conclusion about the modification to the proposal? Apart from that, is there any other concern about the proposal? As I said in my original message, this is a very small amendment to an already-existing proposal, so if we accepted the previous one I see no problem in this one. I’ll wait until Richard and Arnaud get back on the issue, and then assume that silence for a week is acceptance. Regards, Alejandro El 11 jun 2021 14:55:41, Spiwack, Arnaud escribió: > I think that my discussion with Richard has come to a conclusion (it > should incur a small modification to the proposal). > > It is a very small (amendment to a) proposal, let's find a consensus on > this one quickly. > > > On Wed, May 12, 2021 at 11:26 AM Spiwack, Arnaud > wrote: > >> I've commented on the PR [ >> https://github.com/ghc-proposals/ghc-proposals/pull/392#pullrequestreview-657652189 >> ] the changes on the syntax of lambda expressions are not motivated at all, >> I think at the very least there should be a discussion in the Alternatives >> section. >> >> But mostly, I'm worried about the implications/interactions that these >> changes have with linear types. >> >> (I'll be off for the rest of the week starting tonight, so I'll be back >> on this conversation on Monday, most likely) >> >> On Tue, May 11, 2021 at 10:10 AM Alejandro Serrano Mena < >> trupill at gmail.com> wrote: >> >>> Dear Committee, >>> This proposal seems a natural extension of #370, covering some >>> additional cases (modifiers to classes and other declarations) that we’ve >>> found along the way. My recommendation is acceptance. >>> >>> Regards, >>> Alejandro >>> >>> On 4 May 2021 at 09:41:56, Joachim Breitner >>> wrote: >>> >>>> Dear Committe, >>>> >>>> Clarify modifiers design principle >>>> has been proposed by Richard >>>> https://github.com/ghc-proposals/ghc-proposals/pull/392 >>>> >>>> This is an amendmend to #370, see the PR description for links to diffs >>>> etc. >>>> >>>> I propose Alejandro as the shepherd, as he shepherded #370 before. >>>> >>>> Please guide us to a conclusion as outlined in >>>> https://github.com/ghc-proposals/ghc-proposals#committee-process >>>> >>>> Thanks, >>>> Joachim >>>> -- >>>> -- >>>> Joachim Breitner >>>> mail at joachim-breitner.de >>>> http://www.joachim-breitner.de/ >>>> >>>> >>>> _______________________________________________ >>>> ghc-steering-committee mailing list >>>> ghc-steering-committee at haskell.org >>>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >>>> >>> _______________________________________________ >>> ghc-steering-committee mailing list >>> ghc-steering-committee at haskell.org >>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >>> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Thu Jun 24 11:43:43 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Thu, 24 Jun 2021 11:43:43 +0000 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> Message-ID: I think \cases could completely replace \if. Just replace \if with \cases. Am I wrong about that? If it could replace it, then deprecating \if in favour of \cases would make sense. I'm very relaxed about having both \case and \cases, because they do not require any extra mental scaffolding or complication. \cases always works; you can use \case if there is one argument and you don't want to write those extra parens (as indeed you don't in case). Simon From: Alejandro Serrano Mena Sent: 24 June 2021 12:03 To: Simon Peyton Jones Cc: ghc-steering-committee at haskell.org Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) Dear all, To be honest, I'm still trying to make up my mind about this. If we were to accept the proposal, I think option (1) is the best one, since it otherwise `\case` would have a different behaviour depending on whether you have -XLambdaCase or -XExtendedLambdaCase on. Having said so, the words of Simon M. and Richard resonate with me: do we really want \case, \cases, if|, all in the language? - I would prefer one single way to do stuff, let's say having a `cases ... of` which also works as case, if|... and then a \cases for lambdas; - but this is not the world we live in! We already have those things, and this would be yet another small syntactic addition, so we need to think about whether the language is becoming too big. So right now I'm in favor of option (X), reject the proposal. Regards, Alejandro El 24 jun 2021 12:52:10, Simon Peyton Jones via ghc-steering-committee > escribió: Dear Steering committee Simon and Joachim have responded, but only those two . Please reply! Thanks Simon From: ghc-steering-committee > On Behalf Of Simon Peyton Jones via ghc-steering-committee Sent: 15 June 2021 13:52 To: Joachim Breitner >; ghc-steering-committee at haskell.org Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) | I'd like to reassing shepherding of this one. | | It seems to be clear that we want "something like this", there are many ways | to skin the cat, so it comes down to opinion and what we need is a decision | (or a call to votes). As with anything that's possibly quite opinionated, | it's good to have an authorative voice, so in this case, Simon PJ. | | Simon, can you either come up with a "all things considered, I think this | variant is the (narrowly) the best" recommendation or, alternative, a | "please vote on the following options" verdict? OK, to remind everyone 1. Here is the proposal: https://github.com/JakobBruenker/ghc-proposals/blob/patch-1/proposals/0000-lambda-layout.md 2. Here is the discussion: https://github.com/ghc-proposals/ghc-proposals/pull/302 The basic idea is to extend to lambda all the facilities that you get with function definitions, especially multiple patterns and guards. This seems clearly a good idea, whose only obstacle is syntactic. There are no conceptual or specification challenges. The only point at issue is that of concrete syntax. The proposal offers four possible syntactic options. After reviewing, I propose to discard (2) and (3) leaving these alternatives * Option (1) \cases { p1 p2 -> rhs1; q1 q2 -> rhs2 } * Lives alongside \case, but allows multiple patterns * Other keywords are possible, but I think it must be a variant on \case * Option (4) Same, but use \case as the keyword * Incompatible with existing \case => extended transition period, unhappy users * \case { (Just x) -> rhs1; Nothing -> rhs2 } will require parens forever, which in the common case of a one argument lambda see clunky. * Option (X). Reject the proposal. Personally I favour (1). I'm relaxed about having multiple ways of saying the thing (think of let vs where), and I see no harm provided the two constructs look and behave the same. I've decided I like \cases precisely because it's the plural of \case, which is exactly what is going on. I think we'll end up having to vote on this, which is fine when it's a judgement call about syntax. But first: * Are there any other alternatives you strongly want on the ballot? I say "strongly" because I don't want to open up a big new debate... we at the stage of trying to narrow options. Thanks Simon _______________________________________________ ghc-steering-committee mailing list ghc-steering-committee at haskell.org https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee -------------- next part -------------- An HTML attachment was scrubbed... URL: From arnaud.spiwack at tweag.io Thu Jun 24 15:26:36 2021 From: arnaud.spiwack at tweag.io (Spiwack, Arnaud) Date: Thu, 24 Jun 2021 17:26:36 +0200 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> Message-ID: I don't have anything to add to the ballot. I'm in favour of the proposal, and don't really have a preference between (1) and (4) (If \case didn't exist I'd like (4) best, but I don't know how to orchestrate a transition) On Thu, Jun 24, 2021 at 1:44 PM Simon Peyton Jones via ghc-steering-committee wrote: > I think \cases could completely replace \if. Just replace \if with > \cases. Am I wrong about that? > > > > If it could replace it, then deprecating \if in favour of \cases would > make sense. > > > > I’m very relaxed about having both \case and \cases, because they do not > require any extra mental scaffolding or complication. \cases always works; > you can use \case if there is one argument and you don’t want to write > those extra parens (as indeed you don’t in case). > > > > Simon > > > > *From:* Alejandro Serrano Mena > *Sent:* 24 June 2021 12:03 > *To:* Simon Peyton Jones > *Cc:* ghc-steering-committee at haskell.org > *Subject:* Re: [ghc-steering-committee] Proposal #302: `\of` (New > Shepherd: Simon PJ) > > > > Dear all, > > > > To be honest, I’m still trying to make up my mind about this. If we were > to accept the proposal, I think option (1) is the best one, since it > otherwise `\case` would have a different behaviour depending on whether you > have -XLambdaCase or -XExtendedLambdaCase on. > > > > Having said so, the words of Simon M. and Richard resonate with me: do we > really want \case, \cases, if|, all in the language? > > - I would prefer one single way to do stuff, let’s say having a `cases … > of` which also works as case, if|… and then a \cases for lambdas; > > - but this is not the world we live in! We already have those things, and > this would be yet another small syntactic addition, so we need to think > about whether the language is becoming too big. > > > > So right now I’m in favor of option (X), reject the proposal. > > > > Regards, > > Alejandro > > > > El 24 jun 2021 12:52:10, Simon Peyton Jones via ghc-steering-committee < > ghc-steering-committee at haskell.org> escribió: > > Dear Steering committee > > Simon and Joachim have responded, but only those two . Please reply! > > Thanks > > Simon > > > > *From:* ghc-steering-committee > *On Behalf Of *Simon Peyton Jones via ghc-steering-committee > *Sent:* 15 June 2021 13:52 > *To:* Joachim Breitner ; > ghc-steering-committee at haskell.org > *Subject:* Re: [ghc-steering-committee] Proposal #302: `\of` (New > Shepherd: Simon PJ) > > > > | I’d like to reassing shepherding of this one. > > | > > | It seems to be clear that we want “something like this”, there are many > ways > > | to skin the cat, so it comes down to opinion and what we need is a > decision > > | (or a call to votes). As with anything that’s possibly quite > opinionated, > > | it’s good to have an authorative voice, so in this case, Simon PJ. > > | > > | Simon, can you either come up with a “all things considered, I think > this > > | variant is the (narrowly) the best” recommendation or, alternative, a > > | “please vote on the following options” verdict? > > > > OK, to remind everyone > > 1. Here is the proposal: > https://github.com/JakobBruenker/ghc-proposals/blob/patch-1/proposals/0000-lambda-layout.md > > 2. Here is the discussion: > https://github.com/ghc-proposals/ghc-proposals/pull/302 > > > > > The basic idea is to extend to lambda all the facilities that you get with > function definitions, especially multiple patterns and guards. This seems > clearly a good idea, whose only obstacle is syntactic. There are no > conceptual or specification challenges. The only point at issue is that of > concrete syntax. > > > > The proposal offers four possible syntactic options. After reviewing, I > propose to discard (2) and (3) leaving these alternatives > > > > - *Option (1) * \cases { p1 p2 -> rhs1; q1 q2 -> rhs2 } > > > - Lives alongside \case, but allows multiple patterns > - Other keywords are possible, but I think it must be a variant on > \case > > > - *Option (4)* Same, but use \case as the keyword > > > - Incompatible with existing \case => extended transition period, > unhappy users > - \case { (Just x) -> rhs1; Nothing -> rhs2 } will require parens > forever, which in the common case of a one argument lambda see clunky. > > > - *Option (X).* Reject the proposal. > > > > Personally I favour (1). I’m relaxed about having multiple ways of > saying the thing (think of let vs where), and I see no harm provided the > two constructs look and behave the same. I’ve decided I like \cases > precisely because it’s the plural of \case, which is exactly what is going > on. > > I think we’ll end up having to vote on this, which is fine when it’s a > judgement call about syntax. But first: > > - *Are there any other alternatives you strongly want on the ballot?* > > I say “strongly” because I don’t want to open up a big new debate… we at > the stage of trying to narrow options. > > Thanks > > Simon > > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > > > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Sun Jun 27 15:39:41 2021 From: mail at joachim-breitner.de (Joachim Breitner) Date: Sun, 27 Jun 2021 17:39:41 +0200 Subject: [ghc-steering-committee] #409: Exportable named defaults, Recommendation: Partial Accept In-Reply-To: References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> <77209cd3-2da0-4bda-8a09-a7870d7e9d22@www.fastmail.com> <7a913d64-b6a7-4d51-9b6c-7c6e9d2011d6@www.fastmail.com> Message-ID: <5813a08c390adf628f215ee4ba3fd22ef5a77d51.camel@joachim-breitner.de> Hi, Am Sonntag, dem 20.06.2021 um 22:24 -0400 schrieb Eric Seidel: > I recommend we treat defaulting rules like any other importable entity to match how the proposal treats them in export lists I am not confident that I can fully predict the practical implications of this design, e.g. how well it works for people who advocate for an “explicit import lists always” style. But yes, it is a reasonable starting point. A gut feeling tells me that defaulting rules are a bit more like typeclass instances and a bit less like named entities (which you import to refer to them in your text). Alejandro voiced that feeling too. If we now add a way to mention these typeclass-instancy-thing in import and export lists, this _might_ set precendent which could eventually lead to syntax for explicitly exporting or importing type class instances. This is not a value judgment, just a thought. Cheers, Joachim -- Joachim Breitner mail at joachim-breitner.de http://www.joachim-breitner.de/ From arnaud.spiwack at tweag.io Mon Jun 28 07:01:28 2021 From: arnaud.spiwack at tweag.io (Spiwack, Arnaud) Date: Mon, 28 Jun 2021 09:01:28 +0200 Subject: [ghc-steering-committee] #392: Clarify modifiers design principle (recommendation: acceptance) In-Reply-To: References: Message-ID: Yes, I believe that Richard and I are in agreement now. I don't think all the conclusions have been added to the proposal yet, though; but whatever's left, it's fairly minor. On Thu, Jun 24, 2021 at 1:29 PM Alejandro Serrano Mena wrote: > Dear all, > This discussion has been dormant for some time, but it’s time to revive it! > > Richard, Arnaud, did you manage to reach conclusion about the modification > to the proposal? > > Apart from that, is there any other concern about the proposal? As I said > in my original message, this is a very small amendment to an > already-existing proposal, so if we accepted the previous one I see no > problem in this one. I’ll wait until Richard and Arnaud get back on the > issue, and then assume that silence for a week is acceptance. > > Regards, > Alejandro > > El 11 jun 2021 14:55:41, Spiwack, Arnaud > escribió: > >> I think that my discussion with Richard has come to a conclusion (it >> should incur a small modification to the proposal). >> >> It is a very small (amendment to a) proposal, let's find a consensus on >> this one quickly. >> >> >> On Wed, May 12, 2021 at 11:26 AM Spiwack, Arnaud >> wrote: >> >>> I've commented on the PR [ >>> https://github.com/ghc-proposals/ghc-proposals/pull/392#pullrequestreview-657652189 >>> ] the changes on the syntax of lambda expressions are not motivated at all, >>> I think at the very least there should be a discussion in the Alternatives >>> section. >>> >>> But mostly, I'm worried about the implications/interactions that these >>> changes have with linear types. >>> >>> (I'll be off for the rest of the week starting tonight, so I'll be back >>> on this conversation on Monday, most likely) >>> >>> On Tue, May 11, 2021 at 10:10 AM Alejandro Serrano Mena < >>> trupill at gmail.com> wrote: >>> >>>> Dear Committee, >>>> This proposal seems a natural extension of #370, covering some >>>> additional cases (modifiers to classes and other declarations) that we’ve >>>> found along the way. My recommendation is acceptance. >>>> >>>> Regards, >>>> Alejandro >>>> >>>> On 4 May 2021 at 09:41:56, Joachim Breitner >>>> wrote: >>>> >>>>> Dear Committe, >>>>> >>>>> Clarify modifiers design principle >>>>> has been proposed by Richard >>>>> https://github.com/ghc-proposals/ghc-proposals/pull/392 >>>>> >>>>> This is an amendmend to #370, see the PR description for links to diffs >>>>> etc. >>>>> >>>>> I propose Alejandro as the shepherd, as he shepherded #370 before. >>>>> >>>>> Please guide us to a conclusion as outlined in >>>>> https://github.com/ghc-proposals/ghc-proposals#committee-process >>>>> >>>>> Thanks, >>>>> Joachim >>>>> -- >>>>> -- >>>>> Joachim Breitner >>>>> mail at joachim-breitner.de >>>>> http://www.joachim-breitner.de/ >>>>> >>>>> >>>>> _______________________________________________ >>>>> ghc-steering-committee mailing list >>>>> ghc-steering-committee at haskell.org >>>>> >>>>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >>>>> >>>> _______________________________________________ >>>> ghc-steering-committee mailing list >>>> ghc-steering-committee at haskell.org >>>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >>>> >>> -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Jun 28 09:44:33 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 28 Jun 2021 09:44:33 +0000 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> Message-ID: Dear Steering Committee Two weeks ago I asked * Are there any other alternatives you strongly want on the ballot? I got these responses * Joachim, Simon, Alejandro, Arnaud: nothing to add * Vitaly, Eric, Tom, Richard, Vlad: no response I'd love to hear from the five of you, please. I want to get a decision on this, and I can't do that if I don't hear from you. Thanks Simon From: ghc-steering-committee On Behalf Of Simon Peyton Jones via ghc-steering-committee Sent: 15 June 2021 13:52 To: Joachim Breitner ; ghc-steering-committee at haskell.org Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) | I'd like to reassing shepherding of this one. | | It seems to be clear that we want "something like this", there are many ways | to skin the cat, so it comes down to opinion and what we need is a decision | (or a call to votes). As with anything that's possibly quite opinionated, | it's good to have an authorative voice, so in this case, Simon PJ. | | Simon, can you either come up with a "all things considered, I think this | variant is the (narrowly) the best" recommendation or, alternative, a | "please vote on the following options" verdict? OK, to remind everyone * Here is the proposal: https://github.com/JakobBruenker/ghc-proposals/blob/patch-1/proposals/0000-lambda-layout.md * Here is the discussion: https://github.com/ghc-proposals/ghc-proposals/pull/302 The basic idea is to extend to lambda all the facilities that you get with function definitions, especially multiple patterns and guards. This seems clearly a good idea, whose only obstacle is syntactic. There are no conceptual or specification challenges. The only point at issue is that of concrete syntax. The proposal offers four possible syntactic options. After reviewing, I propose to discard (2) and (3) leaving these alternatives * Option (1) \cases { p1 p2 -> rhs1; q1 q2 -> rhs2 } * Lives alongside \case, but allows multiple patterns * Other keywords are possible, but I think it must be a variant on \case * Option (4) Same, but use \case as the keyword * Incompatible with existing \case => extended transition period, unhappy users * \case { (Just x) -> rhs1; Nothing -> rhs2 } will require parens forever, which in the common case of a one argument lambda see clunky. * Option (X). Reject the proposal. Personally I favour (1). I'm relaxed about having multiple ways of saying the thing (think of let vs where), and I see no harm provided the two constructs look and behave the same. I've decided I like \cases precisely because it's the plural of \case, which is exactly what is going on. I think we'll end up having to vote on this, which is fine when it's a judgement call about syntax. But first: * Are there any other alternatives you strongly want on the ballot? I say "strongly" because I don't want to open up a big new debate... we at the stage of trying to narrow options. Thanks Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Mon Jun 28 09:56:12 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 28 Jun 2021 09:56:12 +0000 Subject: [ghc-steering-committee] GHC proposals Message-ID: Friends I'm a bit concerned that we are falling down on our commitment to decide about GHC proposals in a timely manner. Part of the problem is that at any moment I don't have a clear snapshot in my head of what decisions are pending, and who is driving them. I know that Joachim hates manual solutions, but I have spent a few minutes digging through my email to build * this spreadsheet giving the current status You all have edit permissions. It covers only the handful of proposals that are in our court. Can I suggest that we all use it to keep ourselves on the ball? E.g. as a shepherd you can use it to record who you are waiting for, as I have done for #302. You'll notice that we are behind on every one of them. Remember, if there edits we want the author to make, we push it back, out of our court. It can re-enter when the author re-submits. If our commitments are over-ambitious, let's review them. Tom: you are our official nudger. Would you like to make you weekly nudge into an email to the full committee, with a pointer to the spreadsheet and your current understanding of who is responsible for driving? I hope this is helpful. If not, let's think of something else! Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From vlad.z.4096 at gmail.com Mon Jun 28 10:19:33 2021 From: vlad.z.4096 at gmail.com (Vladislav Zavialov (int-index)) Date: Mon, 28 Jun 2021 13:19:33 +0300 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> Message-ID: <0849EAA1-2ABB-4CC7-8316-FED4311413E3@gmail.com> There’s major flaw in options (1) and (4). Consider: \cases X a -> -- very long -- rhs -- that takes -- several lines Y b -> … By the time I get to the `Y b -> …` alternative, I may have forgotten if it’s \case or \cases, so I won’t know whether to (mentally) parse it as two patterns `Y` `b`, or a single pattern `Y b`. Option (2) solves this with commas: \cases X, a -> ... Y, b -> … Option (3) solves this with a lambda: case of \X a -> … \Y b -> … So in both (2) and (3) there’s a clear syntactic indication that parsing this alternative differs from normal, unary \case and case of. Unfortunately, Simon discarded both of these from the vote! So I’m currently leaning towards rejecting the proposal, since I can’t vote for the options that look reasonable to me. - Vlad > On 28 Jun 2021, at 12:44, Simon Peyton Jones via ghc-steering-committee wrote: > > Dear Steering Committee > > Two weeks ago I asked > > • Are there any other alternatives you strongly want on the ballot? > > > I got these responses > > • Joachim, Simon, Alejandro, Arnaud: nothing to add > • Vitaly, Eric, Tom, Richard, Vlad: no response > I’d love to hear from the five of you, please. I want to get a decision on this, and I can’t do that if I don’t hear from you. > > Thanks > > Simon > > > > From: ghc-steering-committee On Behalf Of Simon Peyton Jones via ghc-steering-committee > Sent: 15 June 2021 13:52 > To: Joachim Breitner ; ghc-steering-committee at haskell.org > Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) > > > | I’d like to reassing shepherding of this one. > | > | It seems to be clear that we want “something like this”, there are many ways > | to skin the cat, so it comes down to opinion and what we need is a decision > | (or a call to votes). As with anything that’s possibly quite opinionated, > | it’s good to have an authorative voice, so in this case, Simon PJ. > | > | Simon, can you either come up with a “all things considered, I think this > | variant is the (narrowly) the best” recommendation or, alternative, a > | “please vote on the following options” verdict? > > OK, to remind everyone > • Here is the proposal: https://github.com/JakobBruenker/ghc-proposals/blob/patch-1/proposals/0000-lambda-layout.md > • Here is the discussion: https://github.com/ghc-proposals/ghc-proposals/pull/302 > > The basic idea is to extend to lambda all the facilities that you get with function definitions, especially multiple patterns and guards. This seems clearly a good idea, whose only obstacle is syntactic. There are no conceptual or specification challenges. The only point at issue is that of concrete syntax. > > The proposal offers four possible syntactic options. After reviewing, I propose to discard (2) and (3) leaving these alternatives > > • Option (1) \cases { p1 p2 -> rhs1; q1 q2 -> rhs2 } > • Lives alongside \case, but allows multiple patterns > • Other keywords are possible, but I think it must be a variant on \case > • Option (4) Same, but use \case as the keyword > • Incompatible with existing \case => extended transition period, unhappy users > • \case { (Just x) -> rhs1; Nothing -> rhs2 } will require parens forever, which in the common case of a one argument lambda see clunky. > • Option (X). Reject the proposal. > > > Personally I favour (1). I’m relaxed about having multiple ways of saying the thing (think of let vs where), and I see no harm provided the two constructs look and behave the same. I’ve decided I like \cases precisely because it’s the plural of \case, which is exactly what is going on. > > I think we’ll end up having to vote on this, which is fine when it’s a judgement call about syntax. But first: > > • Are there any other alternatives you strongly want on the ballot? > I say “strongly” because I don’t want to open up a big new debate… we at the stage of trying to narrow options. > > Thanks > > Simon > > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee From simonpj at microsoft.com Mon Jun 28 10:55:56 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 28 Jun 2021 10:55:56 +0000 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: <0849EAA1-2ABB-4CC7-8316-FED4311413E3@gmail.com> References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> <0849EAA1-2ABB-4CC7-8316-FED4311413E3@gmail.com> Message-ID: Thanks Vlad. Personally I don't see this as a problem, but my question was only: | > * Are there any other alternatives you strongly want on the ballot? I believe you may be saying that you'd like (2) or maybe (3) or maybe both on the ballot as well? Or perhaps some other alternative? Let me know what you'd like. Then we can proceed to voting on them. But the first thing is to have some clearly-stated alternatives on which to vote. Thanks Simon | -----Original Message----- | From: Vladislav Zavialov (int-index) | Sent: 28 June 2021 11:20 | To: Simon Peyton Jones | Cc: ghc-steering-committee at haskell.org | Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: | Simon PJ) | | There's major flaw in options (1) and (4). Consider: | | \cases | X a -> | -- very long | -- rhs | -- that takes | -- several lines | Y b -> ... | | By the time I get to the `Y b -> ...` alternative, I may have forgotten if | it's \case or \cases, so I won't know whether to (mentally) parse it as two | patterns `Y` `b`, or a single pattern `Y b`. | | Option (2) solves this with commas: | | \cases | X, a -> ... | Y, b -> ... | | Option (3) solves this with a lambda: | | case of | \X a -> ... | \Y b -> ... | | So in both (2) and (3) there's a clear syntactic indication that parsing | this alternative differs from normal, unary \case and case of. | | Unfortunately, Simon discarded both of these from the vote! So I'm currently | leaning towards rejecting the proposal, since I can't vote for the options | that look reasonable to me. | | - Vlad | | | > On 28 Jun 2021, at 12:44, Simon Peyton Jones via ghc-steering-committee | wrote: | > | > Dear Steering Committee | > | > Two weeks ago I asked | > | > * Are there any other alternatives you strongly want on the ballot? | > | > | > I got these responses | > | > * Joachim, Simon, Alejandro, Arnaud: nothing to add | > * Vitaly, Eric, Tom, Richard, Vlad: no response I'd love to hear from | > the five of you, please. I want to get a decision on this, and I can't do | that if I don't hear from you. | > | > Thanks | > | > Simon | > | > | > | > From: ghc-steering-committee | > On Behalf Of Simon Peyton | > Jones via ghc-steering-committee | > Sent: 15 June 2021 13:52 | > To: Joachim Breitner ; | > ghc-steering-committee at haskell.org | > Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New | > Shepherd: Simon PJ) | > | > | > | I'd like to reassing shepherding of this one. | > | | > | It seems to be clear that we want "something like this", there are | > | many ways to skin the cat, so it comes down to opinion and what we | > | need is a decision (or a call to votes). As with anything that's | > | possibly quite opinionated, it's good to have an authorative voice, so | in this case, Simon PJ. | > | | > | Simon, can you either come up with a "all things considered, I | > | think this variant is the (narrowly) the best" recommendation or, | > | alternative, a "please vote on the following options" verdict? | > | > OK, to remind everyone | > * Here is the proposal: | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com | %2FJakobBruenker%2Fghc-proposals%2Fblob%2Fpatch-1%2Fproposals%2F0000-lambda- | layout.md&data=04%7C01%7Csimonpj%40microsoft.com%7C11e2548cef584a4816480 | 8d93a1e3b84%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637604724423195072% | 7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwi | LCJXVCI6Mn0%3D%7C3000&sdata=riZXAyQbv1LLzbiHbPPIPMnXzrFOhtMeuH2SfIje8ls% | 3D&reserved=0 | > * Here is the discussion: | > https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgith | > ub.com%2Fghc-proposals%2Fghc-proposals%2Fpull%2F302&data=04%7C01%7 | > Csimonpj%40microsoft.com%7C11e2548cef584a48164808d93a1e3b84%7C72f988bf | > 86f141af91ab2d7cd011db47%7C1%7C0%7C637604724423195072%7CUnknown%7CTWFp | > bGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwiLCJXVCI6Mn | > 0%3D%7C3000&sdata=PqnR%2BWM9RDQkrWCk4ItoZYZMl2z1tCPlVqbG8y2lL70%3D | > &reserved=0 | > | > The basic idea is to extend to lambda all the facilities that you get with | function definitions, especially multiple patterns and guards. This seems | clearly a good idea, whose only obstacle is syntactic. There are no | conceptual or specification challenges. The only point at issue is that of | concrete syntax. | > | > The proposal offers four possible syntactic options. After reviewing, | > I propose to discard (2) and (3) leaving these alternatives | > | > * Option (1) \cases { p1 p2 -> rhs1; q1 q2 -> rhs2 } | > * Lives alongside \case, but allows multiple patterns | > * Other keywords are possible, but I think it must be a variant | on \case | > * Option (4) Same, but use \case as the keyword | > * Incompatible with existing \case => extended transition | period, unhappy users | > * \case { (Just x) -> rhs1; Nothing -> rhs2 } will require | parens forever, which in the common case of a one argument lambda see | clunky. | > * Option (X). Reject the proposal. | > | > | > Personally I favour (1). I'm relaxed about having multiple ways of | saying the thing (think of let vs where), and I see no harm provided the two | constructs look and behave the same. I've decided I like \cases precisely | because it's the plural of \case, which is exactly what is going on. | > | > I think we'll end up having to vote on this, which is fine when it's a | judgement call about syntax. But first: | > | > * Are there any other alternatives you strongly want on the ballot? | > I say "strongly" because I don't want to open up a big new debate... we at | the stage of trying to narrow options. | > | > Thanks | > | > Simon | > | > _______________________________________________ | > ghc-steering-committee mailing list | > ghc-steering-committee at haskell.org | > https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fmail | > .haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-steering-committee&a | > mp;data=04%7C01%7Csimonpj%40microsoft.com%7C11e2548cef584a48164808d93a | > 1e3b84%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637604724423195072 | > %7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6I | > k1haWwiLCJXVCI6Mn0%3D%7C3000&sdata=1QO9LR43LzG3TELp2guWxCH9B0Fqm8v | > HB%2FgadoRTwQg%3D&reserved=0 From vlad.z.4096 at gmail.com Mon Jun 28 11:26:38 2021 From: vlad.z.4096 at gmail.com (Vladislav Zavialov (int-index)) Date: Mon, 28 Jun 2021 14:26:38 +0300 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> <0849EAA1-2ABB-4CC7-8316-FED4311413E3@gmail.com> Message-ID: <1640632A-5806-4EE3-8E6F-CF2A6C2CF5B7@gmail.com> Yes, I find (2) and (3) to be the superior options, so it’d be nice to have at least one of those on the ballot. - Vlad > On 28 Jun 2021, at 13:55, Simon Peyton Jones wrote: > > Thanks Vlad. Personally I don't see this as a problem, but my question was only: > > | > * Are there any other alternatives you strongly want on the ballot? > > I believe you may be saying that you'd like (2) or maybe (3) or maybe both on the ballot as well? Or perhaps some other alternative? > > Let me know what you'd like. Then we can proceed to voting on them. But the first thing is to have some clearly-stated alternatives on which to vote. > > Thanks > > Simon From simonpj at microsoft.com Mon Jun 28 11:50:23 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 28 Jun 2021 11:50:23 +0000 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: <1640632A-5806-4EE3-8E6F-CF2A6C2CF5B7@gmail.com> References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> <0849EAA1-2ABB-4CC7-8316-FED4311413E3@gmail.com> <1640632A-5806-4EE3-8E6F-CF2A6C2CF5B7@gmail.com> Message-ID: Thanks. Which one? Or do you want both? Simon | -----Original Message----- | From: Vladislav Zavialov (int-index) | Sent: 28 June 2021 12:27 | To: Simon Peyton Jones | Cc: ghc-steering-committee at haskell.org | Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: | Simon PJ) | | Yes, I find (2) and (3) to be the superior options, so it’d be nice to have | at least one of those on the ballot. | | - Vlad | | > On 28 Jun 2021, at 13:55, Simon Peyton Jones | wrote: | > | > Thanks Vlad. Personally I don't see this as a problem, but my question was | only: | > | > | > * Are there any other alternatives you strongly want on the | ballot? | > | > I believe you may be saying that you'd like (2) or maybe (3) or maybe both | on the ballot as well? Or perhaps some other alternative? | > | > Let me know what you'd like. Then we can proceed to voting on them. But | the first thing is to have some clearly-stated alternatives on which to | vote. | > | > Thanks | > | > Simon From vlad.z.4096 at gmail.com Mon Jun 28 15:25:16 2021 From: vlad.z.4096 at gmail.com (Vladislav Zavialov (int-index)) Date: Mon, 28 Jun 2021 18:25:16 +0300 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> <0849EAA1-2ABB-4CC7-8316-FED4311413E3@gmail.com> <1640632A-5806-4EE3-8E6F-CF2A6C2CF5B7@gmail.com> Message-ID: <39EE5778-44EA-40AD-88C0-987AF3A4B132@gmail.com> While (3) is my personal favorite, it has received some heavy pushback, and I don’t suppose it has any chance of getting accepted. Therefore, I guess I’m asking to add (2). - Vlad > On 28 Jun 2021, at 14:50, Simon Peyton Jones wrote: > > Thanks. Which one? Or do you want both? > > Simon From trupill at gmail.com Mon Jun 28 19:26:45 2021 From: trupill at gmail.com (Alejandro Serrano Mena) Date: Mon, 28 Jun 2021 19:26:45 +0000 Subject: [ghc-steering-committee] #392: Clarify modifiers design principle (recommendation: acceptance) In-Reply-To: References: Message-ID: Richard, will you take care of making those small changes to the proposal? That way we could mark this as accepted. Regards, Alejandro El 28 jun 2021 9:01:28, Spiwack, Arnaud escribió: > Yes, I believe that Richard and I are in agreement now. I don't think all > the conclusions have been added to the proposal yet, though; but whatever's > left, it's fairly minor. > > On Thu, Jun 24, 2021 at 1:29 PM Alejandro Serrano Mena > wrote: > >> Dear all, >> This discussion has been dormant for some time, but it’s time to revive >> it! >> >> Richard, Arnaud, did you manage to reach conclusion about the >> modification to the proposal? >> >> Apart from that, is there any other concern about the proposal? As I said >> in my original message, this is a very small amendment to an >> already-existing proposal, so if we accepted the previous one I see no >> problem in this one. I’ll wait until Richard and Arnaud get back on the >> issue, and then assume that silence for a week is acceptance. >> >> Regards, >> Alejandro >> >> El 11 jun 2021 14:55:41, Spiwack, Arnaud >> escribió: >> >>> I think that my discussion with Richard has come to a conclusion (it >>> should incur a small modification to the proposal). >>> >>> It is a very small (amendment to a) proposal, let's find a consensus on >>> this one quickly. >>> >>> >>> On Wed, May 12, 2021 at 11:26 AM Spiwack, Arnaud < >>> arnaud.spiwack at tweag.io> wrote: >>> >>>> I've commented on the PR [ >>>> https://github.com/ghc-proposals/ghc-proposals/pull/392#pullrequestreview-657652189 >>>> ] the changes on the syntax of lambda expressions are not motivated at all, >>>> I think at the very least there should be a discussion in the Alternatives >>>> section. >>>> >>>> But mostly, I'm worried about the implications/interactions that these >>>> changes have with linear types. >>>> >>>> (I'll be off for the rest of the week starting tonight, so I'll be back >>>> on this conversation on Monday, most likely) >>>> >>>> On Tue, May 11, 2021 at 10:10 AM Alejandro Serrano Mena < >>>> trupill at gmail.com> wrote: >>>> >>>>> Dear Committee, >>>>> This proposal seems a natural extension of #370, covering some >>>>> additional cases (modifiers to classes and other declarations) that we’ve >>>>> found along the way. My recommendation is acceptance. >>>>> >>>>> Regards, >>>>> Alejandro >>>>> >>>>> On 4 May 2021 at 09:41:56, Joachim Breitner >>>>> wrote: >>>>> >>>>>> Dear Committe, >>>>>> >>>>>> Clarify modifiers design principle >>>>>> has been proposed by Richard >>>>>> https://github.com/ghc-proposals/ghc-proposals/pull/392 >>>>>> >>>>>> This is an amendmend to #370, see the PR description for links to >>>>>> diffs >>>>>> etc. >>>>>> >>>>>> I propose Alejandro as the shepherd, as he shepherded #370 before. >>>>>> >>>>>> Please guide us to a conclusion as outlined in >>>>>> https://github.com/ghc-proposals/ghc-proposals#committee-process >>>>>> >>>>>> Thanks, >>>>>> Joachim >>>>>> -- >>>>>> -- >>>>>> Joachim Breitner >>>>>> mail at joachim-breitner.de >>>>>> http://www.joachim-breitner.de/ >>>>>> >>>>>> >>>>>> _______________________________________________ >>>>>> ghc-steering-committee mailing list >>>>>> ghc-steering-committee at haskell.org >>>>>> >>>>>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >>>>>> >>>>> _______________________________________________ >>>>> ghc-steering-committee mailing list >>>>> ghc-steering-committee at haskell.org >>>>> >>>>> https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee >>>>> >>>> -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Jun 29 08:59:33 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 29 Jun 2021 08:59:33 +0000 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: <39EE5778-44EA-40AD-88C0-987AF3A4B132@gmail.com> References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> <0849EAA1-2ABB-4CC7-8316-FED4311413E3@gmail.com> <1640632A-5806-4EE3-8E6F-CF2A6C2CF5B7@gmail.com> <39EE5778-44EA-40AD-88C0-987AF3A4B132@gmail.com> Message-ID: Got it thanks. Awaiting input from Vitaly, Tom, Eric, Richard. Simon | -----Original Message----- | From: Vladislav Zavialov (int-index) | Sent: 28 June 2021 16:25 | To: Simon Peyton Jones | Cc: ghc-steering-committee at haskell.org | Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: | Simon PJ) | | While (3) is my personal favorite, it has received some heavy pushback, and | I don’t suppose it has any chance of getting accepted. Therefore, I guess | I’m asking to add (2). | | - Vlad | | > On 28 Jun 2021, at 14:50, Simon Peyton Jones | wrote: | > | > Thanks. Which one? Or do you want both? | > | > Simon From lists at richarde.dev Tue Jun 29 22:03:25 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Tue, 29 Jun 2021 22:03:25 +0000 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> <0849EAA1-2ABB-4CC7-8316-FED4311413E3@gmail.com> <1640632A-5806-4EE3-8E6F-CF2A6C2CF5B7@gmail.com> <39EE5778-44EA-40AD-88C0-987AF3A4B132@gmail.com> Message-ID: <010f017a59cc65b9-9d886eb7-f3df-4adf-a483-a3086a1f6e73-000000@us-east-2.amazonses.com> I don't need any further options, but I'm happy for (2) to be on the ballot. Thanks, Richard > On Jun 29, 2021, at 4:59 AM, Simon Peyton Jones via ghc-steering-committee wrote: > > Got it thanks. > > Awaiting input from Vitaly, Tom, Eric, Richard. > > Simon > > | -----Original Message----- > | From: Vladislav Zavialov (int-index) > | Sent: 28 June 2021 16:25 > | To: Simon Peyton Jones > | Cc: ghc-steering-committee at haskell.org > | Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: > | Simon PJ) > | > | While (3) is my personal favorite, it has received some heavy pushback, and > | I don’t suppose it has any chance of getting accepted. Therefore, I guess > | I’m asking to add (2). > | > | - Vlad > | > | > On 28 Jun 2021, at 14:50, Simon Peyton Jones > | wrote: > | > > | > Thanks. Which one? Or do you want both? > | > > | > Simon > > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee From lists at richarde.dev Wed Jun 30 02:38:09 2021 From: lists at richarde.dev (Richard Eisenberg) Date: Wed, 30 Jun 2021 02:38:09 +0000 Subject: [ghc-steering-committee] #409: Exportable named defaults, Recommendation: Partial Accept In-Reply-To: <5813a08c390adf628f215ee4ba3fd22ef5a77d51.camel@joachim-breitner.de> References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> <77209cd3-2da0-4bda-8a09-a7870d7e9d22@www.fastmail.com> <7a913d64-b6a7-4d51-9b6c-7c6e9d2011d6@www.fastmail.com> <5813a08c390adf628f215ee4ba3fd22ef5a77d51.camel@joachim-breitner.de> Message-ID: <010f017a5ac7ed07-92163998-1078-4d7c-85aa-a34e30335f99-000000@us-east-2.amazonses.com> Just to chime in now that I'm back in action: I'm reasonably happy with the final result here, but still curious about whether the new warning will be on by default or not. If it's not: then an unsuspecting user's program could drastically, silently change its meaning just by adding an import -- even if no symbol is used from that import! (I guess this is already true with overlapping instances and orphans. But that doesn't mean we should make the threat worse!) If it is: the usefulness of the extension is lessened, because any use of it will be noisy. Richard > On Jun 27, 2021, at 11:39 AM, Joachim Breitner wrote: > > Hi, > > Am Sonntag, dem 20.06.2021 um 22:24 -0400 schrieb Eric Seidel: >> I recommend we treat defaulting rules like any other importable entity to match how the proposal treats them in export lists > > I am not confident that I can fully predict the practical implications > of this design, e.g. how well it works for people who advocate for an > “explicit import lists always” style. But yes, it is a reasonable > starting point. > > A gut feeling tells me that defaulting rules are a bit more like > typeclass instances and a bit less like named entities (which you > import to refer to them in your text). Alejandro voiced that feeling > too. If we now add a way to mention these typeclass-instancy-thing in > import and export lists, this _might_ set precendent which could > eventually lead to syntax for explicitly exporting or importing type > class instances. This is not a value judgment, just a thought. > > Cheers, > Joachim > > > > > -- > Joachim Breitner > mail at joachim-breitner.de > http://www.joachim-breitner.de/ > > > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee From eric at seidel.io Wed Jun 30 03:19:25 2021 From: eric at seidel.io (Eric Seidel) Date: Tue, 29 Jun 2021 23:19:25 -0400 Subject: [ghc-steering-committee] =?utf-8?q?=23409=3A_Exportable_named_def?= =?utf-8?q?aults=2C_Recommendation=3A_Partial_Accept?= In-Reply-To: <010f017a5ac7ed07-92163998-1078-4d7c-85aa-a34e30335f99-000000@us-east-2.amazonses.com> References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> <77209cd3-2da0-4bda-8a09-a7870d7e9d22@www.fastmail.com> <7a913d64-b6a7-4d51-9b6c-7c6e9d2011d6@www.fastmail.com> <5813a08c390adf628f215ee4ba3fd22ef5a77d51.camel@joachim-breitner.de> <010f017a5ac7ed07-92163998-1078-4d7c-85aa-a34e30335f99-000000@us-east-2.amazonses.com> Message-ID: On Tue, Jun 29, 2021, at 22:38, Richard Eisenberg wrote: > Just to chime in now that I'm back in action: I'm reasonably happy with > the final result here With Richard in support, that leaves Simon PJ opposed to explicit imports [1]. So we have Richard opposed to implicit imports, Simon opposed to explicit imports, and the rest of us (I believe) amenable to either. I think we have two options at this point: we can keep trying to achieve consensus, or we can take a vote. Richard, Simon, since the two of you seem to have the strongest opinions on the import question, do you think we can reach a consensus here? I'm happy to set up a call if it would help to discuss things live. > but still curious about whether the new warning will be on by default or not. I believe it should be off by default. The warning would interfere with Prelude replacements (and the Prelude itself, should it adopt ExportedDefaults), which I view as the biggest usecase for these extensions. Thanks! Eric [1]: https://github.com/ghc-proposals/ghc-proposals/pull/409#issuecomment-864809405 From eric at seidel.io Wed Jun 30 03:29:48 2021 From: eric at seidel.io (Eric Seidel) Date: Tue, 29 Jun 2021 23:29:48 -0400 Subject: [ghc-steering-committee] =?utf-8?b?UHJvcG9zYWwgIzMwMjogYFxvZmAg?= =?utf-8?q?=28New_Shepherd=3A_Simon_PJ=29?= In-Reply-To: <010f017a59cc65b9-9d886eb7-f3df-4adf-a483-a3086a1f6e73-000000@us-east-2.amazonses.com> References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> <0849EAA1-2ABB-4CC7-8316-FED4311413E3@gmail.com> <1640632A-5806-4EE3-8E6F-CF2A6C2CF5B7@gmail.com> <39EE5778-44EA-40AD-88C0-987AF3A4B132@gmail.com> <010f017a59cc65b9-9d886eb7-f3df-4adf-a483-a3086a1f6e73-000000@us-east-2.amazonses.com> Message-ID: <8c47a0e3-150d-4478-bae7-e7de5ea9121f@www.fastmail.com> I would like (2) to be on the ballot as well. It's unclear from the proposal whether (2) includes the extension to `case of` or if it's a hypothetical future extension, but I think the extension to `case of` should be included. On Tue, Jun 29, 2021, at 18:03, Richard Eisenberg wrote: > I don't need any further options, but I'm happy for (2) to be on the ballot. > > Thanks, > Richard > > > On Jun 29, 2021, at 4:59 AM, Simon Peyton Jones via ghc-steering-committee wrote: > > > > Got it thanks. > > > > Awaiting input from Vitaly, Tom, Eric, Richard. > > > > Simon > > > > | -----Original Message----- > > | From: Vladislav Zavialov (int-index) > > | Sent: 28 June 2021 16:25 > > | To: Simon Peyton Jones > > | Cc: ghc-steering-committee at haskell.org > > | Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: > > | Simon PJ) > > | > > | While (3) is my personal favorite, it has received some heavy pushback, and > > | I don’t suppose it has any chance of getting accepted. Therefore, I guess > > | I’m asking to add (2). > > | > > | - Vlad > > | > > | > On 28 Jun 2021, at 14:50, Simon Peyton Jones > > | wrote: > > | > > > | > Thanks. Which one? Or do you want both? > > | > > > | > Simon > > > > _______________________________________________ > > ghc-steering-committee mailing list > > ghc-steering-committee at haskell.org > > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > > _______________________________________________ > ghc-steering-committee mailing list > ghc-steering-committee at haskell.org > https://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-steering-committee > From simonpj at microsoft.com Wed Jun 30 07:26:06 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 30 Jun 2021 07:26:06 +0000 Subject: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: Simon PJ) In-Reply-To: <8c47a0e3-150d-4478-bae7-e7de5ea9121f@www.fastmail.com> References: <010f017455fde7c2-d0af078b-24b8-4c12-95fc-7c653a7251f8-000000@us-east-2.amazonses.com> <0849EAA1-2ABB-4CC7-8316-FED4311413E3@gmail.com> <1640632A-5806-4EE3-8E6F-CF2A6C2CF5B7@gmail.com> <39EE5778-44EA-40AD-88C0-987AF3A4B132@gmail.com> <010f017a59cc65b9-9d886eb7-f3df-4adf-a483-a3086a1f6e73-000000@us-east-2.amazonses.com> <8c47a0e3-150d-4478-bae7-e7de5ea9121f@www.fastmail.com> Message-ID: | I would like (2) to be on the ballot as well. It's unclear from the proposal | whether (2) includes the extension to `case of` or if it's a hypothetical | future extension, but I think the extension to `case of` should be included. By "case of" Eric means the ability to say case a, b of True, False -> blah OK, I suppose we can have 2a and 2b. I'm still hoping to hear from Tom, Richard, and Vitaly. Helloooo? Simon | -----Original Message----- | From: ghc-steering-committee On | Behalf Of Eric Seidel | Sent: 30 June 2021 04:30 | To: ghc-steering-committee at haskell.org | Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New Shepherd: | Simon PJ) | | I would like (2) to be on the ballot as well. It's unclear from the proposal | whether (2) includes the extension to `case of` or if it's a hypothetical | future extension, but I think the extension to `case of` should be included. | | On Tue, Jun 29, 2021, at 18:03, Richard Eisenberg wrote: | > I don't need any further options, but I'm happy for (2) to be on the | ballot. | > | > Thanks, | > Richard | > | > > On Jun 29, 2021, at 4:59 AM, Simon Peyton Jones via ghc-steering- | committee wrote: | > > | > > Got it thanks. | > > | > > Awaiting input from Vitaly, Tom, Eric, Richard. | > > | > > Simon | > > | > > | -----Original Message----- | > > | From: Vladislav Zavialov (int-index) | > > | Sent: 28 June 2021 16:25 | > > | To: Simon Peyton Jones | > > | Cc: ghc-steering-committee at haskell.org | > > | Subject: Re: [ghc-steering-committee] Proposal #302: `\of` (New | Shepherd: | > > | Simon PJ) | > > | | > > | While (3) is my personal favorite, it has received some heavy | > > | pushback, and I don't suppose it has any chance of getting | > > | accepted. Therefore, I guess I'm asking to add (2). | > > | | > > | - Vlad | > > | | > > | > On 28 Jun 2021, at 14:50, Simon Peyton Jones | > > | | > > | wrote: | > > | > | > > | > Thanks. Which one? Or do you want both? | > > | > | > > | > Simon | > > | > > _______________________________________________ | > > ghc-steering-committee mailing list | > > ghc-steering-committee at haskell.org | > > https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fma | > > il.haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-steering-committ | > > ee&data=04%7C01%7Csimonpj%40microsoft.com%7Caf6869ca4d2d4c572203 | > > 08d93b77671d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C6376062063 | > > 06488778%7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzI | > > iLCJBTiI6Ik1haWwiLCJXVCI6Mn0%3D%7C2000&sdata=XDGE60Iaq1NEmA%2FTH | > > rQsSrV1msxEsq6b6i4RLMAq4qc%3D&reserved=0 | > | > _______________________________________________ | > ghc-steering-committee mailing list | > ghc-steering-committee at haskell.org | > https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fmail | > .haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-steering-committee&a | > mp;data=04%7C01%7Csimonpj%40microsoft.com%7Caf6869ca4d2d4c57220308d93b | > 77671d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637606206306488778 | > %7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6I | > k1haWwiLCJXVCI6Mn0%3D%7C2000&sdata=XDGE60Iaq1NEmA%2FTHrQsSrV1msxEs | > q6b6i4RLMAq4qc%3D&reserved=0 | > | _______________________________________________ | ghc-steering-committee mailing list | ghc-steering-committee at haskell.org | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fmail.haske | ll.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-steering- | committee&data=04%7C01%7Csimonpj%40microsoft.com%7Caf6869ca4d2d4c5722030 | 8d93b77671d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637606206306488778% | 7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwi | LCJXVCI6Mn0%3D%7C2000&sdata=XDGE60Iaq1NEmA%2FTHrQsSrV1msxEsq6b6i4RLMAq4q | c%3D&reserved=0 From simonpj at microsoft.com Wed Jun 30 07:36:35 2021 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Wed, 30 Jun 2021 07:36:35 +0000 Subject: [ghc-steering-committee] #409: Exportable named defaults, Recommendation: Partial Accept In-Reply-To: References: <010f0179a51e4333-c762d7af-6f7e-4036-a04b-4ed60afd81ca-000000@us-east-2.amazonses.com> <1754f703-f87b-448b-bfd3-268226203b38@www.fastmail.com> <010f0179eca00f96-706787fc-ebda-4855-b38a-b7161d44f971-000000@us-east-2.amazonses.com> <77209cd3-2da0-4bda-8a09-a7870d7e9d22@www.fastmail.com> <7a913d64-b6a7-4d51-9b6c-7c6e9d2011d6@www.fastmail.com> <5813a08c390adf628f215ee4ba3fd22ef5a77d51.camel@joachim-breitner.de> <010f017a5ac7ed07-92163998-1078-4d7c-85aa-a34e30335f99-000000@us-east-2.amazonses.com> Message-ID: OK i've added a comment to explain the delay. Richard, you and I can discuss. Simon | -----Original Message----- | From: ghc-steering-committee On | Behalf Of Eric Seidel | Sent: 30 June 2021 04:19 | To: ghc-steering-committee at haskell.org | Subject: Re: [ghc-steering-committee] #409: Exportable named defaults, | Recommendation: Partial Accept | | On Tue, Jun 29, 2021, at 22:38, Richard Eisenberg wrote: | > Just to chime in now that I'm back in action: I'm reasonably happy | > with the final result here | | With Richard in support, that leaves Simon PJ opposed to explicit imports | [1]. So we have Richard opposed to implicit imports, Simon opposed to | explicit imports, and the rest of us (I believe) amenable to either. | | I think we have two options at this point: we can keep trying to achieve | consensus, or we can take a vote. Richard, Simon, since the two of you seem | to have the strongest opinions on the import question, do you think we can | reach a consensus here? I'm happy to set up a call if it would help to | discuss things live. | | > but still curious about whether the new warning will be on by default or | not. | | I believe it should be off by default. The warning would interfere with | Prelude replacements (and the Prelude itself, should it adopt | ExportedDefaults), which I view as the biggest usecase for these extensions. | | Thanks! | Eric | | [1]: | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgithub.com | %2Fghc-proposals%2Fghc-proposals%2Fpull%2F409%23issuecomment- | 864809405&data=04%7C01%7Csimonpj%40microsoft.com%7C5126784da503456fb1bb0 | 8d93b760db0%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637606200986942832% | 7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwi | LCJXVCI6Mn0%3D%7C3000&sdata=RqPy7fhDfWRyIdz7NEMWWwuWKLRRom8c%2BC3p%2BFYz | H4Q%3D&reserved=0 | _______________________________________________ | ghc-steering-committee mailing list | ghc-steering-committee at haskell.org | https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fmail.haske | ll.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-steering- | committee&data=04%7C01%7Csimonpj%40microsoft.com%7C5126784da503456fb1bb0 | 8d93b760db0%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C637606200986942832% | 7CUnknown%7CTWFpbGZsb3d8eyJWIjoiMC4wLjAwMDAiLCJQIjoiV2luMzIiLCJBTiI6Ik1haWwi | LCJXVCI6Mn0%3D%7C3000&sdata=ePQduxulLz%2FTmpGhfRjKxRJ1bRyRdorYEYnjyR96xb | w%3D&reserved=0