From tkn.akio at gmail.com Mon Jul 4 10:31:37 2016 From: tkn.akio at gmail.com (Akio Takano) Date: Mon, 4 Jul 2016 10:31:37 +0000 Subject: Proposal: ArgumentDo Message-ID: Hi glasgow-haskell-users, I have written a wiki page about a proposed extension called ArgumentDo. It's a small syntactic extension that allows "do" expressions, lambdas and a few other kinds of expressions to be used as function arguments, without parentheses. https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo Any feedback is appreciated. In particular, since the idea has received mixed support (see the "Discussion" section on the wiki page), I'd like to make sure that there is enough support for this feature to justify an implementation in GHC. Regards, Takano Akio From dluposchainsky at googlemail.com Mon Jul 4 16:28:16 2016 From: dluposchainsky at googlemail.com (David Luposchainsky) Date: Mon, 4 Jul 2016 18:28:16 +0200 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: <577A8EA0.1020204@gmail.com> Infix ($) is so noisy that I’ve adapted a code style that replaces it entirely with parentheses. And the hack to make ($) work with higher-rank types is pretty awkward too. Seen from these angles, I’m very much in favour of ArgumentDo. However, the clarity of `runST do ...` comes at a high price: only some of the missing ($) make the code clearer, where others make it much worse. You give a couple of examples yourself: > f > do x > do y I have to think a bit how this might be parsed even after reading the proposal. I’m a bit torn on whether I like or not like it, but I think the ArgumentDo syntax that I find awkward now is a matter of style, and one could probably get used to only using it in certain places, despite all of the possibilities. David/quchen From christiaan.baaij at gmail.com Wed Jul 6 08:08:01 2016 From: christiaan.baaij at gmail.com (Christiaan Baaij) Date: Wed, 6 Jul 2016 10:08:01 +0200 Subject: Space-leak incurred by constraints Message-ID: <577CBC61.3050001@gmail.com> Hi, The following reduced test-case: > {-# LANGUAGE DataKinds, TypeOperators, TypeFamilies, ConstraintKinds, > FlexibleContexts, BangPatterns #-} > module ConstraintLeak where > > import GHC.TypeLits > import Data.Proxy > > type Constraint1 n > = ( Constraint2 n > , Constraint2 (2^n) > ) > type Constraint2 n > = ( KnownNat n > , ((n-1)+1) ~ n -- Comment this line to run in constant space > ) > > test :: Constraint1 x => Proxy x -> String > test !s | s == s = test s > > main :: IO () > main = putStr (test (Proxy :: Proxy 3)) contains a space-leak when compiled without optimisations (i.e. -O0 or in GHCi). It's true that the code doesn't actually do anything (when compiled with -O you get "Exception <>"), but I'm using it to exemplify some code that runs for some time, and then prints something. As you can see, 'test' is strict in its arguments, but it seems lazy in its constraints. When I look at the heap profile (-hy), I see it rapidly accumulating values of the following types: - ~ - KnownNat - (,) The problem with these constraints, unlike a normal type-class constraints, is that I cannot 'seq' one of its members to force the dictionary and hence be strict in the constraints. We stumbled upon this particular space-leak while trying to find a space-leak in our own code; we don't think it's the real culprit in our own code, but find it disturbing nonetheless. GHCi is heavily used in our work-flow, meaning we often run in an -O0 setting, so I would like to know if it is possible to plug this constraint-induced space-leak. Regards, Christiaan Baaij From chr.maeder at web.de Wed Jul 6 16:08:09 2016 From: chr.maeder at web.de (C Maeder) Date: Wed, 6 Jul 2016 18:08:09 +0200 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: <577D2CE9.1050504@web.de> Hi, allowing group A constructs (do, case, ...) and group B constructs (\, let, if, ...) as parts of functions application (fexp) without extra parentheses looks natural to me. The current state is an artificial and unnecessary restriction. Style guides may dictate restrictions, but the parser/language should not (without good reasons). So +1 for the proposal from me. However, I would not distinguish group A and group B constructs in the proposed grammar rules. The report already states (for the group B constructs): "The grammar is ambiguous regarding the extent of lambda abstractions, let expressions, and conditionals. The ambiguity is resolved by the meta-rule that each of these constructs extends as far to the right as possible." Therefore I would simply add all constructs (that start with a unique keyword) to atomic expressions (aexp) where the term "atomic" might be misleading but is already accepted for the record constructs. For the group B constructs this simply means that they can only be the last argument (or the mere function itself) in any expression (exp). The non-terminal lexp is no longer needed (and could be replaced by fexp in infixexp). Furthermore group B constructs are also delimited by the layout rules (of decls). Cheers Christian Am 04.07.2016 um 12:31 schrieb Akio Takano: > Hi glasgow-haskell-users, > > I have written a wiki page about a proposed extension called > ArgumentDo. It's a small syntactic extension that allows "do" > expressions, lambdas and a few other kinds of expressions to be used > as function arguments, without parentheses. > > https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo > > Any feedback is appreciated. In particular, since the idea has > received mixed support (see the "Discussion" section on the wiki > page), I'd like to make sure that there is enough support for this > feature to justify an implementation in GHC. > > Regards, > Takano Akio > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From spam at scientician.net Wed Jul 6 17:39:36 2016 From: spam at scientician.net (Bardur Arantsson) Date: Wed, 6 Jul 2016 19:39:36 +0200 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: On 07/04/2016 12:31 PM, Akio Takano wrote: > Hi glasgow-haskell-users, > > I have written a wiki page about a proposed extension called > ArgumentDo. It's a small syntactic extension that allows "do" > expressions, lambdas and a few other kinds of expressions to be used > as function arguments, without parentheses. > > https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo > > Any feedback is appreciated. In particular, since the idea has > received mixed support (see the "Discussion" section on the wiki > page), I'd like to make sure that there is enough support for this > feature to justify an implementation in GHC. > -1 Reasons have already been given in previous threads on this. However, I'd point especially to the fact that people don't *agree* that this is more readable as a very strong point against -- regardless of whether any one individual thinks it's more readable or not. The point is the there seems to be a lot of disagreement -- that indicates to me that this cannot by definition be a "clear win"[1]. Disclosure: I personally find it less readable because of the implicitness. Implicitness which has a non-trivial probability of affecting semantics is bad in my book. Frankly, if it came to it, I'd rather just remove $ and deal with the parentheses. Regards, [1] Which I should think the barrier to extensions should roughly be :). From qdunkan at gmail.com Thu Jul 7 01:50:57 2016 From: qdunkan at gmail.com (Evan Laforge) Date: Wed, 6 Jul 2016 18:50:57 -0700 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: On Wed, Jul 6, 2016 at 10:39 AM, Bardur Arantsson wrote: > On 07/04/2016 12:31 PM, Akio Takano wrote: >> Hi glasgow-haskell-users, >> >> I have written a wiki page about a proposed extension called >> ArgumentDo. It's a small syntactic extension that allows "do" >> expressions, lambdas and a few other kinds of expressions to be used >> as function arguments, without parentheses. >> >> https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo >> >> Any feedback is appreciated. In particular, since the idea has >> received mixed support (see the "Discussion" section on the wiki >> page), I'd like to make sure that there is enough support for this >> feature to justify an implementation in GHC. >> > > -1 > > Reasons have already been given in previous threads on this. However, > I'd point especially to the fact that people don't *agree* that this is > more readable as a very strong point against -- regardless of whether > any one individual thinks it's more readable or not. The point is the > there seems to be a lot of disagreement -- that indicates to me that > this cannot by definition be a "clear win"[1]. Disclosure: I personally > find it less readable because of the implicitness. Implicitness which > has a non-trivial probability of affecting semantics is bad in my book. > Frankly, if it came to it, I'd rather just remove $ and deal with the > parentheses. I'm -1 because I think there are already too many styles. So I don't agree with the general sentiment that the parser should accept lots of stuff and to rely on style guides to specify something, because in practice everyone has their own style guide. I trained myself to see juxtaposition as highest precedence (which newcomers still struggle over) and it's confusing to see juxtaposition that has higher precedence because one of them is a keyword. In the same way I'm confused by 'f a { b = c }', but it's too late to change that one. I suppose this is already on the wiki page in the "cons" section. From carter.schonwald at gmail.com Thu Jul 7 17:15:55 2016 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 7 Jul 2016 13:15:55 -0400 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: agreed -1, ambiguity is bad for humans, not just parsers. perhaps most damningly, > f do{ x } do { y } is just reallly really weird/confusing to me, and as the proposal itself says at the end as the cons: - It's harder to read than the alternative. > - Creating a language extension to get rid of a single character is overkill and unnecessary. > - You can already get rid of the $ by just adding parentheses. > which kinda kills any benefit in my mind. thats a HUGE complexity vs alternative ratio. I'm all in favor of doing engineering work to *improve* our parser error messages and suggestions, but not stuff that complicates parsing for humans as well as machines On Wed, Jul 6, 2016 at 9:50 PM, Evan Laforge wrote: > On Wed, Jul 6, 2016 at 10:39 AM, Bardur Arantsson > wrote: > > On 07/04/2016 12:31 PM, Akio Takano wrote: > >> Hi glasgow-haskell-users, > >> > >> I have written a wiki page about a proposed extension called > >> ArgumentDo. It's a small syntactic extension that allows "do" > >> expressions, lambdas and a few other kinds of expressions to be used > >> as function arguments, without parentheses. > >> > >> https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo > >> > >> Any feedback is appreciated. In particular, since the idea has > >> received mixed support (see the "Discussion" section on the wiki > >> page), I'd like to make sure that there is enough support for this > >> feature to justify an implementation in GHC. > >> > > > > -1 > > > > Reasons have already been given in previous threads on this. However, > > I'd point especially to the fact that people don't *agree* that this is > > more readable as a very strong point against -- regardless of whether > > any one individual thinks it's more readable or not. The point is the > > there seems to be a lot of disagreement -- that indicates to me that > > this cannot by definition be a "clear win"[1]. Disclosure: I personally > > find it less readable because of the implicitness. Implicitness which > > has a non-trivial probability of affecting semantics is bad in my book. > > Frankly, if it came to it, I'd rather just remove $ and deal with the > > parentheses. > > I'm -1 because I think there are already too many styles. So I don't > agree with the general sentiment that the parser should accept lots of > stuff and to rely on style guides to specify something, because in > practice everyone has their own style guide. > > I trained myself to see juxtaposition as highest precedence (which > newcomers still struggle over) and it's confusing to see juxtaposition > that has higher precedence because one of them is a keyword. In the > same way I'm confused by 'f a { b = c }', but it's too late to change > that one. I suppose this is already on the wiki page in the "cons" > section. > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Thu Jul 7 17:23:19 2016 From: david.feuer at gmail.com (David Feuer) Date: Thu, 7 Jul 2016 13:23:19 -0400 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: What makes f do{x} do{y} any harder to read than similar record syntax? f Foo{foo=3} Foo{foo=4} On Thu, Jul 7, 2016 at 1:15 PM, Carter Schonwald wrote: > agreed -1, > ambiguity is bad for humans, not just parsers. > > perhaps most damningly, >> >> >> f do{ x } do { y } > > > is just reallly really weird/confusing to me, and as the proposal itself > says at the end as the cons: > > >> It's harder to read than the alternative. >> >> Creating a language extension to get rid of a single character is overkill >> and unnecessary. >> >> You can already get rid of the $ by just adding parentheses. > > which kinda kills any benefit in my mind. thats a HUGE complexity vs > alternative ratio. I'm all in favor of doing engineering work to *improve* > our parser error messages and suggestions, but not stuff that complicates > parsing for humans as well as machines > > > On Wed, Jul 6, 2016 at 9:50 PM, Evan Laforge wrote: >> >> On Wed, Jul 6, 2016 at 10:39 AM, Bardur Arantsson >> wrote: >> > On 07/04/2016 12:31 PM, Akio Takano wrote: >> >> Hi glasgow-haskell-users, >> >> >> >> I have written a wiki page about a proposed extension called >> >> ArgumentDo. It's a small syntactic extension that allows "do" >> >> expressions, lambdas and a few other kinds of expressions to be used >> >> as function arguments, without parentheses. >> >> >> >> https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo >> >> >> >> Any feedback is appreciated. In particular, since the idea has >> >> received mixed support (see the "Discussion" section on the wiki >> >> page), I'd like to make sure that there is enough support for this >> >> feature to justify an implementation in GHC. >> >> >> > >> > -1 >> > >> > Reasons have already been given in previous threads on this. However, >> > I'd point especially to the fact that people don't *agree* that this is >> > more readable as a very strong point against -- regardless of whether >> > any one individual thinks it's more readable or not. The point is the >> > there seems to be a lot of disagreement -- that indicates to me that >> > this cannot by definition be a "clear win"[1]. Disclosure: I personally >> > find it less readable because of the implicitness. Implicitness which >> > has a non-trivial probability of affecting semantics is bad in my book. >> > Frankly, if it came to it, I'd rather just remove $ and deal with the >> > parentheses. >> >> I'm -1 because I think there are already too many styles. So I don't >> agree with the general sentiment that the parser should accept lots of >> stuff and to rely on style guides to specify something, because in >> practice everyone has their own style guide. >> >> I trained myself to see juxtaposition as highest precedence (which >> newcomers still struggle over) and it's confusing to see juxtaposition >> that has higher precedence because one of them is a keyword. In the >> same way I'm confused by 'f a { b = c }', but it's too late to change >> that one. I suppose this is already on the wiki page in the "cons" >> section. >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From allbery.b at gmail.com Thu Jul 7 17:32:59 2016 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 7 Jul 2016 13:32:59 -0400 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: Didn't they already say they disliked record syntax for exactly that reason? On Thu, Jul 7, 2016 at 1:23 PM, David Feuer wrote: > What makes > > f do{x} do{y} > > any harder to read than similar record syntax? > > f Foo{foo=3} Foo{foo=4} > > On Thu, Jul 7, 2016 at 1:15 PM, Carter Schonwald > wrote: > > agreed -1, > > ambiguity is bad for humans, not just parsers. > > > > perhaps most damningly, > >> > >> > >> f do{ x } do { y } > > > > > > is just reallly really weird/confusing to me, and as the proposal itself > > says at the end as the cons: > > > > > >> It's harder to read than the alternative. > >> > >> Creating a language extension to get rid of a single character is > overkill > >> and unnecessary. > >> > >> You can already get rid of the $ by just adding parentheses. > > > > which kinda kills any benefit in my mind. thats a HUGE complexity vs > > alternative ratio. I'm all in favor of doing engineering work to > *improve* > > our parser error messages and suggestions, but not stuff that complicates > > parsing for humans as well as machines > > > > > > On Wed, Jul 6, 2016 at 9:50 PM, Evan Laforge wrote: > >> > >> On Wed, Jul 6, 2016 at 10:39 AM, Bardur Arantsson > > >> wrote: > >> > On 07/04/2016 12:31 PM, Akio Takano wrote: > >> >> Hi glasgow-haskell-users, > >> >> > >> >> I have written a wiki page about a proposed extension called > >> >> ArgumentDo. It's a small syntactic extension that allows "do" > >> >> expressions, lambdas and a few other kinds of expressions to be used > >> >> as function arguments, without parentheses. > >> >> > >> >> https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo > >> >> > >> >> Any feedback is appreciated. In particular, since the idea has > >> >> received mixed support (see the "Discussion" section on the wiki > >> >> page), I'd like to make sure that there is enough support for this > >> >> feature to justify an implementation in GHC. > >> >> > >> > > >> > -1 > >> > > >> > Reasons have already been given in previous threads on this. However, > >> > I'd point especially to the fact that people don't *agree* that this > is > >> > more readable as a very strong point against -- regardless of whether > >> > any one individual thinks it's more readable or not. The point is the > >> > there seems to be a lot of disagreement -- that indicates to me that > >> > this cannot by definition be a "clear win"[1]. Disclosure: I > personally > >> > find it less readable because of the implicitness. Implicitness which > >> > has a non-trivial probability of affecting semantics is bad in my > book. > >> > Frankly, if it came to it, I'd rather just remove $ and deal with the > >> > parentheses. > >> > >> I'm -1 because I think there are already too many styles. So I don't > >> agree with the general sentiment that the parser should accept lots of > >> stuff and to rely on style guides to specify something, because in > >> practice everyone has their own style guide. > >> > >> I trained myself to see juxtaposition as highest precedence (which > >> newcomers still struggle over) and it's confusing to see juxtaposition > >> that has higher precedence because one of them is a keyword. In the > >> same way I'm confused by 'f a { b = c }', but it's too late to change > >> that one. I suppose this is already on the wiki page in the "cons" > >> section. > >> _______________________________________________ > >> Glasgow-haskell-users mailing list > >> Glasgow-haskell-users at haskell.org > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > > > > > > _______________________________________________ > > Glasgow-haskell-users mailing list > > Glasgow-haskell-users at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Jul 7 17:44:49 2016 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 7 Jul 2016 13:44:49 -0400 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: the fact that its perilously close to looking like *1 typo* away from a parser error about record syntax makes me *-1000* now thanks for pointing this out! On Thu, Jul 7, 2016 at 1:32 PM, Brandon Allbery wrote: > Didn't they already say they disliked record syntax for exactly that > reason? > > On Thu, Jul 7, 2016 at 1:23 PM, David Feuer wrote: > >> What makes >> >> f do{x} do{y} >> >> any harder to read than similar record syntax? >> >> f Foo{foo=3} Foo{foo=4} >> >> On Thu, Jul 7, 2016 at 1:15 PM, Carter Schonwald >> wrote: >> > agreed -1, >> > ambiguity is bad for humans, not just parsers. >> > >> > perhaps most damningly, >> >> >> >> >> >> f do{ x } do { y } >> > >> > >> > is just reallly really weird/confusing to me, and as the proposal itself >> > says at the end as the cons: >> > >> > >> >> It's harder to read than the alternative. >> >> >> >> Creating a language extension to get rid of a single character is >> overkill >> >> and unnecessary. >> >> >> >> You can already get rid of the $ by just adding parentheses. >> > >> > which kinda kills any benefit in my mind. thats a HUGE complexity vs >> > alternative ratio. I'm all in favor of doing engineering work to >> *improve* >> > our parser error messages and suggestions, but not stuff that >> complicates >> > parsing for humans as well as machines >> > >> > >> > On Wed, Jul 6, 2016 at 9:50 PM, Evan Laforge wrote: >> >> >> >> On Wed, Jul 6, 2016 at 10:39 AM, Bardur Arantsson < >> spam at scientician.net> >> >> wrote: >> >> > On 07/04/2016 12:31 PM, Akio Takano wrote: >> >> >> Hi glasgow-haskell-users, >> >> >> >> >> >> I have written a wiki page about a proposed extension called >> >> >> ArgumentDo. It's a small syntactic extension that allows "do" >> >> >> expressions, lambdas and a few other kinds of expressions to be used >> >> >> as function arguments, without parentheses. >> >> >> >> >> >> https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo >> >> >> >> >> >> Any feedback is appreciated. In particular, since the idea has >> >> >> received mixed support (see the "Discussion" section on the wiki >> >> >> page), I'd like to make sure that there is enough support for this >> >> >> feature to justify an implementation in GHC. >> >> >> >> >> > >> >> > -1 >> >> > >> >> > Reasons have already been given in previous threads on this. However, >> >> > I'd point especially to the fact that people don't *agree* that this >> is >> >> > more readable as a very strong point against -- regardless of whether >> >> > any one individual thinks it's more readable or not. The point is the >> >> > there seems to be a lot of disagreement -- that indicates to me that >> >> > this cannot by definition be a "clear win"[1]. Disclosure: I >> personally >> >> > find it less readable because of the implicitness. Implicitness which >> >> > has a non-trivial probability of affecting semantics is bad in my >> book. >> >> > Frankly, if it came to it, I'd rather just remove $ and deal with the >> >> > parentheses. >> >> >> >> I'm -1 because I think there are already too many styles. So I don't >> >> agree with the general sentiment that the parser should accept lots of >> >> stuff and to rely on style guides to specify something, because in >> >> practice everyone has their own style guide. >> >> >> >> I trained myself to see juxtaposition as highest precedence (which >> >> newcomers still struggle over) and it's confusing to see juxtaposition >> >> that has higher precedence because one of them is a keyword. In the >> >> same way I'm confused by 'f a { b = c }', but it's too late to change >> >> that one. I suppose this is already on the wiki page in the "cons" >> >> section. >> >> _______________________________________________ >> >> Glasgow-haskell-users mailing list >> >> Glasgow-haskell-users at haskell.org >> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> > >> > >> > >> > _______________________________________________ >> > Glasgow-haskell-users mailing list >> > Glasgow-haskell-users at haskell.org >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> > >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> > > > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Thu Jul 7 18:50:29 2016 From: mail at joachim-breitner.de (Joachim Breitner) Date: Thu, 07 Jul 2016 20:50:29 +0200 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: <1467917429.28020.5.camel@joachim-breitner.de> Hi, Am Donnerstag, den 07.07.2016, 13:15 -0400 schrieb Carter Schonwald: > agreed -1, > ambiguity is bad for humans, not just parsers.  > > perhaps most damningly,  > > f do{ x } do { y } > > is just reallly really weird/confusing to me, It is weird to me, but in no way confusing under the simple new rules, and I am actually looking forward to using that, and also to reading code with that. In fact, everything I wanted to pass two arguments in do-notation to a function I felt at a loss. The prospect of itemizing multiple large arguments to a function by writing someFunctionWithManyArguments   do firstArgument   do second Argument which may span        several lines   do third Argument is actually making me happy! It feels like going from XML to YAML... Greetings, Joachim -- Joachim “nomeata” Breitner   mail at joachim-breitner.de • https://www.joachim-breitner.de/   XMPP: nomeata at joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F   Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From ryan.trinkle at gmail.com Thu Jul 7 19:40:05 2016 From: ryan.trinkle at gmail.com (Ryan Trinkle) Date: Thu, 7 Jul 2016 15:40:05 -0400 Subject: Proposal: ArgumentDo In-Reply-To: <1467917429.28020.5.camel@joachim-breitner.de> References: <1467917429.28020.5.camel@joachim-breitner.de> Message-ID: I'm very on the fence on this topic, but one point i haven't seen mentioned is the influence of syntax highlighting on this. My guess is that I would like this extension when I have syntax highlighting available and would dislike it when I do not. Also, I agree with Carter about the record update syntax - I find it harder to parse visually than most other parts of the language, and I expect I'd find curly brace syntax for inline 'do' harder to parse in a similar way. On the other hand, maybe I should get used to both... On Thu, Jul 7, 2016 at 2:50 PM, Joachim Breitner wrote: > Hi, > > Am Donnerstag, den 07.07.2016, 13:15 -0400 schrieb Carter Schonwald: > > agreed -1, > > ambiguity is bad for humans, not just parsers. > > > > perhaps most damningly, > > > f do{ x } do { y } > > > > is just reallly really weird/confusing to me, > > It is weird to me, but in no way confusing under the simple new rules, > and I am actually looking forward to using that, and also to reading > code with that. > > In fact, everything I wanted to pass two arguments in do-notation to a > function I felt at a loss. The prospect of itemizing multiple large > arguments to a function by writing > > someFunctionWithManyArguments > do firstArgument > do second Argument which may span > several lines > do third Argument > > is actually making me happy! It feels like going from XML to YAML... > > Greetings, > Joachim > > -- > > Joachim “nomeata” Breitner > mail at joachim-breitner.de • https://www.joachim-breitner.de/ > XMPP: nomeata at joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F > Debian Developer: nomeata at debian.org > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From evincarofautumn at gmail.com Thu Jul 7 20:46:51 2016 From: evincarofautumn at gmail.com (Jon Purdy) Date: Thu, 7 Jul 2016 13:46:51 -0700 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: > ambiguity is bad for humans, not just parsers. This is not ambiguous. It’s removing the need for a redundant set of parentheses, whichever way you slice it. Of course, some redundancy is useful for readability (look at natural language), but you should really be explicit if you’re arguing from that position. > perhaps most damningly, >> >> >> f do{ x } do { y } > > > is just reallly really weird/confusing to me By “weird”, do you mean anything other than “I don’t understand it, and I blame it”? Can you give an example of how you might misparse it, as a human reader? >> It's harder to read than the alternative. >> >> Creating a language extension to get rid of a single character is overkill >> and unnecessary. It’s only a language extension for backward compatibility. It’s really fixing a bug in the grammar. > I'm all in favor of doing engineering work to *improve* > our parser error messages and suggestions, but not stuff that complicates > parsing for humans as well as machines This would be a simplification of the parser if the bug hadn’t been standardised originally. From carter.schonwald at gmail.com Thu Jul 7 22:40:52 2016 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 7 Jul 2016 18:40:52 -0400 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: Can you walk me through how this simplifies the grammar etc in concrete compare contrast or what the diffs between the grammar and associated engineering would be? I don't see how it simplifies the grammar, but I could be a bit obtuse. That aside, I'm also a bit fuzzy on the other claim, that this change will simplify post parsing engineering, On Jul 7, 2016 4:47 PM, "Jon Purdy" wrote: > > ambiguity is bad for humans, not just parsers. > > This is not ambiguous. It’s removing the need for a redundant set of > parentheses, whichever way you slice it. Of course, some redundancy is > useful for readability (look at natural language), but you should > really be explicit if you’re arguing from that position. > > > perhaps most damningly, > >> > >> > >> f do{ x } do { y } > > > > > > is just reallly really weird/confusing to me > > By “weird”, do you mean anything other than “I don’t understand it, > and I blame it”? Can you give an example of how you might misparse it, > as a human reader? > > >> It's harder to read than the alternative. > >> > >> Creating a language extension to get rid of a single character is > overkill > >> and unnecessary. > > It’s only a language extension for backward compatibility. It’s really > fixing a bug in the grammar. > > > I'm all in favor of doing engineering work to *improve* > > our parser error messages and suggestions, but not stuff that complicates > > parsing for humans as well as machines > > This would be a simplification of the parser if the bug hadn’t been > standardised originally. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From svenpanne at gmail.com Fri Jul 8 06:35:18 2016 From: svenpanne at gmail.com (Sven Panne) Date: Fri, 8 Jul 2016 08:35:18 +0200 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: [ There is a trend to repeat one's argument about this proposed extension in various mailing lists/wiki pages/etc., so let's repeat myself, too... :-] 2016-07-07 19:44 GMT+02:00 Carter Schonwald : > the fact that its perilously close to looking like *1 typo* away from a > parser error about record syntax makes me > *-1000* now [...] > -1000 for exactly the same reason, and more: If you look at the "Block as a LHS" section on the wiki, things get insame IMHO: do f &&& g x should mean "(f &&& g) x"? It's probably 99% more likely that somebody didn't get the indentation right for the "do". And what about: foobar do f &&& g x Should the x now be an argument of foobar (as it is currently) or the "do"? If it is not an argument of the "do", suddenly things get very context-dependent. Computers are good at handling context-dependent things, humans are quite bad at it. Taking one step back: I think a lot of the discussion is based on the false assumption that "something can be parsed in an unambiguous way by some more or less random parsing technology" means "it can easily be parsed by a human". This is a fundamental misconception, otherwise reading programs in Brainfuck or Whitespace would be easy, too. In our case at hand, visually determining what is an argument of a function in a quick way is *supported* by some (perhaps) redundant syntactic stuff. That's exactly the reason why the current record syntax is a big mistake: Normally, an argument is beginning after a whitespace (unless there are other syntactic clues like '$', '(', etc.), but foo bar { baz = blah } runs against this intuition and one has to mentally backtrack. The proposal at hand would enshrine this kind of broken syntax in more places. As has already been said in another thread, the goal of language design is not to make writing correct programs easier (by allowing more and more syntax), but to make writing wrong programs harder. And a note about counting votes: I think normal democrating voting procedures simply don't apply here. Even if e.g. 80% of the voters find something OK while the other 20% find it confusing, the majority vote doesn't make the confusion of a fifth of the people go away. For a change like this, I would expect near unanimous consent, but I think we are very, very far away from that... -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Fri Jul 8 07:09:51 2016 From: mail at joachim-breitner.de (Joachim Breitner) Date: Fri, 08 Jul 2016 09:09:51 +0200 Subject: Proposal: ArgumentDo In-Reply-To: References: Message-ID: <1467961791.1639.3.camel@joachim-breitner.de> Hi, Am Freitag, den 08.07.2016, 08:35 +0200 schrieb Sven Panne: >    foobar >       do f &&& g >       x > > Should the x now be an argument of foobar (as it is currently) or the > "do"? If it is not an argument of the "do", suddenly things get very > context-dependent. Computers are good at handling context-dependent > things, humans are quite bad at it. What do you mean by “as it is currently”. Currently, this is a syntax error! (“parse error on input ‘do’”). Only with the proposed addition, it becomes an argument to foobar. And it is not hard to reason about this: "x" is lined up with the "do", so it is a sibling, not a child, in the AST. Hence, both are arguments to foobar. This is another good instance of how the (by me) beloved feature of “parenthesless arguments”, which so far is only available for the last argument of a function (using the “$” idiom), would now be possible for every argument of a function. Greetings, Joachim -- Joachim “nomeata” Breitner   mail at joachim-breitner.de • https://www.joachim-breitner.de/   XMPP: nomeata at joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F   Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From chr.maeder at web.de Fri Jul 8 09:20:53 2016 From: chr.maeder at web.de (C Maeder) Date: Fri, 8 Jul 2016 11:20:53 +0200 Subject: Proposal: ArgumentDo In-Reply-To: <1467961791.1639.3.camel@joachim-breitner.de> References: <1467961791.1639.3.camel@joachim-breitner.de> Message-ID: <577F7075.1020908@web.de> Surely layout can bite you: f do x do y and I'm having difficulties to find the documentation for the various layout options. But this is no argument against this proposal! Improper use of white spaces can always be used to obfuscate code! Style guides are important. Furthermore, a wrong/unintended parse tree (due to layout) will - in many cases - result in a typing error. Christian Am 08.07.2016 um 09:09 schrieb Joachim Breitner: > Hi, > > Am Freitag, den 08.07.2016, 08:35 +0200 schrieb Sven Panne: >> foobar >> do f &&& g >> x >> >> Should the x now be an argument of foobar (as it is currently) or the >> "do"? If it is not an argument of the "do", suddenly things get very >> context-dependent. Computers are good at handling context-dependent >> things, humans are quite bad at it. > > What do you mean by “as it is currently”. Currently, this is a syntax > error! (“parse error on input ‘do’”). > > Only with the proposed addition, it becomes an argument to foobar. > > And it is not hard to reason about this: "x" is lined up with the "do", > so it is a sibling, not a child, in the AST. Hence, both are arguments > to foobar. > > This is another good instance of how the (by me) beloved feature of > “parenthesless arguments”, which so far is only available for the last > argument of a function (using the “$” idiom), would now be possible for > every argument of a function. > > Greetings, > Joachim > > > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From svenpanne at gmail.com Fri Jul 8 09:32:43 2016 From: svenpanne at gmail.com (Sven Panne) Date: Fri, 8 Jul 2016 11:32:43 +0200 Subject: Proposal: ArgumentDo In-Reply-To: <1467961791.1639.3.camel@joachim-breitner.de> References: <1467961791.1639.3.camel@joachim-breitner.de> Message-ID: 2016-07-08 9:09 GMT+02:00 Joachim Breitner : > Am Freitag, den 08.07.2016, 08:35 +0200 schrieb Sven Panne: > > foobar > > do f &&& g > > x > [...] Only with the proposed addition, it becomes an argument to foobar. > [...] > Huh? Nope! The Wiki page explicitly says that do f &&& g x means (f &&& g) x Why should this be different here? Simply writing "foobar" above that construct won't trigger any special layout rules, I hope... -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Fri Jul 8 10:28:27 2016 From: mail at joachim-breitner.de (Joachim Breitner) Date: Fri, 08 Jul 2016 12:28:27 +0200 Subject: Proposal: ArgumentDo In-Reply-To: References: <1467961791.1639.3.camel@joachim-breitner.de> Message-ID: <1467973707.1639.10.camel@joachim-breitner.de> Hi, Am Freitag, den 08.07.2016, 11:32 +0200 schrieb Sven Panne: > 2016-07-08 9:09 GMT+02:00 Joachim Breitner : > > Am Freitag, den 08.07.2016, 08:35 +0200 schrieb Sven Panne: > > >    foobar > > >       do f &&& g > > >       x > > [...] Only with the proposed addition, it becomes an argument to foobar. [...] > > Huh?  Nope! The Wiki page explicitly says that > >    do f &&& g >    x > > means > >    (f &&& g) x > > Why should this be different here? Simply writing "foobar" above that > construct won't trigger any special layout rules, I hope... I believe this follows from the existing layout rules. Currenlty, foobar   (do f &&& g)   x calls foobar with two arguments, while    (do f &&& g) x calls (f &&& g) with one argument. The ArgumentDo proposal does not change that, only that the parenthesis become redundant. Greetings, Joachim --  -- Joachim “nomeata” Breitner   mail at joachim-breitner.de • https://www.joachim-breitner.de/   XMPP: nomeata at joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F   Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From svenpanne at gmail.com Fri Jul 8 11:09:15 2016 From: svenpanne at gmail.com (Sven Panne) Date: Fri, 8 Jul 2016 13:09:15 +0200 Subject: Proposal: ArgumentDo In-Reply-To: <1467973707.1639.10.camel@joachim-breitner.de> References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> Message-ID: 2016-07-08 12:28 GMT+02:00 Joachim Breitner : > Currenlty, > > foobar > (do f &&& g) > x > > calls foobar with two arguments, while > > (do f &&& g) > x > > calls (f &&& g) with one argument. The ArgumentDo proposal does not change > that, only that the parenthesis become redundant. > I don't think so: https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo#BlockasaLHS explicit states that do f &&& g x parses as (f &&& g) x , so foobar do f &&& g x parses as foobar ((f &&& g) x) under the new proposal, which I find highly confusing. If it doesn't parse like this under the proposal, the wiki page is wrong and/or the proposal is not compositional: Why should being below "foobar" change the parse? "foobar" is not a keyword switching to some different mode. -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Fri Jul 8 11:27:45 2016 From: mail at joachim-breitner.de (Joachim Breitner) Date: Fri, 08 Jul 2016 13:27:45 +0200 Subject: Proposal: ArgumentDo In-Reply-To: References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> Message-ID: <1467977265.1639.15.camel@joachim-breitner.de> Hi, Am Freitag, den 08.07.2016, 13:09 +0200 schrieb Sven Panne: > I don't think so: https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo#Bl > ockasaLHS explicit states that > >    do f &&& g >    x > > parses as > >    (f &&& g) x Correct > , so > >    foobar >       do f &&& g >       x > > parses as > >    foobar ((f &&& g) x) Where is the outer set of parenthesis coming from? This is all not related to the ArgumentDo notation. Note that (f &&& g) x parses as    (f &&& g) x and still    foobar      (f &&& g)      x parses as foobar (f &&& g) x just as    foobar    (f &&& g)    x does. (NB: I consider   foobar   arg1   arg2 bad style and prefer   foobar       arg1       arg2 but the former is allowed now and will be allowed later as well.) Greetings, Joachim -- Joachim “nomeata” Breitner   mail at joachim-breitner.de • https://www.joachim-breitner.de/   XMPP: nomeata at joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F   Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From Henrik.Nilsson at nottingham.ac.uk Fri Jul 8 12:00:35 2016 From: Henrik.Nilsson at nottingham.ac.uk (Henrik Nilsson) Date: Fri, 08 Jul 2016 13:00:35 +0100 Subject: Proposal: ArgumentDo In-Reply-To: <1467977265.1639.15.camel@joachim-breitner.de> References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> Message-ID: <577F95E3.2000004@nottingham.ac.uk> Hi all, Joachim Breitner wrote: > Am Freitag, den 08.07.2016, 13:09 +0200 schrieb Sven Panne: > > I don't think so: https://ghc.haskell.org/trac/ghc > /wiki/ArgumentDo#Bl > [...] > Where is the outer set of parenthesis coming from? > > This is all not related to the ArgumentDo notation. Note that [...] The very fact that that experts can't easily agree on how a small Haskell fragment is parsed to me just confirms that Haskell already is a syntactically very cumbersome language. The present proposal just makes matters worse. For that reason alone, I don't find it compelling at all. (So -1 from me, then.) I will not repeat the many other strong arguments against that has been made. But I must say I don't find the use cases as documented on the associated web page compelling at all. Maybe there is a tacit desire to be able to pretend functions are keywords for various creative uses in supporting EDSLs and such. But for that to be truly useful, one need to support groups of related keywords. Something like Agda's mixfix syntax springs to mind. But this proposal does not come close, so the benefits are minimal and the drawbacks large. As a final point, the inherent asymmetry of the proposal (the last argument position is special as, for certain kinds of expressions, parentheses may be omitted there but not elsewhere) is also deeply unsettling. Best, /Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham nhn at cs.nott.ac.uk This message and any attachment are intended solely for the addressee and may contain confidential information. If you have received this message in error, please send it back to me, and immediately delete it. Please do not use, copy or disclose the information contained in this message or in any attachment. Any views or opinions expressed by the author of this email do not necessarily reflect the views of the University of Nottingham. This message has been checked for viruses but the contents of an attachment may still contain software viruses which could damage your computer system, you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation. From alois.cochard at gmail.com Fri Jul 8 12:03:01 2016 From: alois.cochard at gmail.com (=?UTF-8?Q?Alo=C3=AFs_Cochard?=) Date: Fri, 8 Jul 2016 14:03:01 +0200 Subject: Proposal: ArgumentDo In-Reply-To: <577F95E3.2000004@nottingham.ac.uk> References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> Message-ID: -1 for same reasons. On 8 July 2016 at 14:00, Henrik Nilsson wrote: > Hi all, > > Joachim Breitner wrote: > > > Am Freitag, den 08.07.2016, 13:09 +0200 schrieb Sven Panne: > > > I don't think so: https://ghc.haskell.org/trac/ghc > > /wiki/ArgumentDo#Bl > > [...] > > Where is the outer set of parenthesis coming from? > > > > This is all not related to the ArgumentDo notation. Note that [...] > > The very fact that that experts can't easily agree on how a small > Haskell fragment is parsed to me just confirms that Haskell already > is a syntactically very cumbersome language. > > The present proposal just makes matters worse. For that reason > alone, I don't find it compelling at all. (So -1 from me, then.) > > I will not repeat the many other strong arguments against that has been > made. But I must say I don't find the use cases as documented > on the associated web page compelling at all. Maybe there is a tacit > desire to be able to pretend functions are keywords for various > creative uses in supporting EDSLs and such. But for that to be truly > useful, one need to support groups of related keywords. Something > like Agda's mixfix syntax springs to mind. But this proposal does > not come close, so the benefits are minimal and the drawbacks large. > > As a final point, the inherent asymmetry of the proposal (the > last argument position is special as, for certain kinds of > expressions, parentheses may be omitted there but not elsewhere) > is also deeply unsettling. > > Best, > > /Henrik > > -- > Henrik Nilsson > School of Computer Science > The University of Nottingham > nhn at cs.nott.ac.uk > > > > > This message and any attachment are intended solely for the addressee > and may contain confidential information. If you have received this > message in error, please send it back to me, and immediately delete it. > Please do not use, copy or disclose the information contained in this > message or in any attachment. Any views or opinions expressed by the > author of this email do not necessarily reflect the views of the > University of Nottingham. > > This message has been checked for viruses but the contents of an > attachment may still contain software viruses which could damage your > computer system, you are advised to perform your own checks. Email > communications with the University of Nottingham may be monitored as > permitted by UK legislation. > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -- *Λ\oïs* http://twitter.com/aloiscochard http://github.com/aloiscochard -------------- next part -------------- An HTML attachment was scrubbed... URL: From chr.maeder at web.de Fri Jul 8 12:37:04 2016 From: chr.maeder at web.de (C Maeder) Date: Fri, 8 Jul 2016 14:37:04 +0200 Subject: layout was Re: Proposal: ArgumentDo In-Reply-To: <577F7075.1020908@web.de> References: <1467961791.1639.3.camel@joachim-breitner.de> <577F7075.1020908@web.de> Message-ID: <577F9E70.5090300@web.de> Hi, the layout language options are hard to find (at least in the user guide). Therefore I try to give an overview here. The relevant options I've found by using ghc-7.10.3 with option --supported-languages are: NondecreasingIndentation DoAndIfThenElse RelaxedLayout AlternativeLayoutRule AlternativeLayoutRuleTransitional I ignore the last 3 options since these seem to be candidates for removal: https://ghc.haskell.org/trac/ghc/ticket/11359. The default option is NondecreasingIndentation, that is do x do y is legal and parsed as a single expression "do {x ; do y}". With -XNoNondecreasingIndentation one gets an "Empty 'do' block" for the second do (and this error would not change with ArgumentDo!). DoAndIfThenElse is not switched on by default and requires the keywords "then" and "else" to be further indented for an "if" within a "do". So I believe these options do not interfere with ArgumentDo, but maybe this should be discussed more and maybe mentioned on the wiki page. Surely a single space (inserted before x or removed before the second "do") makes a difference between one or two argument expressions in the example below. HTH Christian Am 08.07.2016 um 11:20 schrieb C Maeder: > Surely layout can bite you: > > f > do > x > do > y > > and I'm having difficulties to find the documentation for the various > layout options. > > But this is no argument against this proposal! > > Improper use of white spaces can always be used to obfuscate code! > Style guides are important. Furthermore, a wrong/unintended parse tree > (due to layout) will - in many cases - result in a typing error. > > Christian From iavor.diatchki at gmail.com Fri Jul 8 16:42:24 2016 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Fri, 8 Jul 2016 09:42:24 -0700 Subject: Proposal: ArgumentDo In-Reply-To: References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> Message-ID: Hello, while we are voting here, I kind of like this proposal, so +1 for me. I understand that some of the examples look strange to Haskell old-timers but, as Joachim points out, the behavior is very consistent. Besides, the "Less Obvious Examples" were selected so that they are, well, less obvious. The common use cases (as in ticket #10843) seem quite appealing, at least to me, and not at all confusing. But, then, I also like the records-with-no-parens notation :-) -Iavor On Fri, Jul 8, 2016 at 5:03 AM, Aloïs Cochard wrote: > -1 for same reasons. > > On 8 July 2016 at 14:00, Henrik Nilsson > wrote: > >> Hi all, >> >> Joachim Breitner wrote: >> >> > Am Freitag, den 08.07.2016, 13:09 +0200 schrieb Sven Panne: >> > > I don't think so: https://ghc.haskell.org/trac/ghc >> > /wiki/ArgumentDo#Bl >> > [...] >> > Where is the outer set of parenthesis coming from? >> > >> > This is all not related to the ArgumentDo notation. Note that [...] >> >> The very fact that that experts can't easily agree on how a small >> Haskell fragment is parsed to me just confirms that Haskell already >> is a syntactically very cumbersome language. >> >> The present proposal just makes matters worse. For that reason >> alone, I don't find it compelling at all. (So -1 from me, then.) >> >> I will not repeat the many other strong arguments against that has been >> made. But I must say I don't find the use cases as documented >> on the associated web page compelling at all. Maybe there is a tacit >> desire to be able to pretend functions are keywords for various >> creative uses in supporting EDSLs and such. But for that to be truly >> useful, one need to support groups of related keywords. Something >> like Agda's mixfix syntax springs to mind. But this proposal does >> not come close, so the benefits are minimal and the drawbacks large. >> >> As a final point, the inherent asymmetry of the proposal (the >> last argument position is special as, for certain kinds of >> expressions, parentheses may be omitted there but not elsewhere) >> is also deeply unsettling. >> >> Best, >> >> /Henrik >> >> -- >> Henrik Nilsson >> School of Computer Science >> The University of Nottingham >> nhn at cs.nott.ac.uk >> >> >> >> >> This message and any attachment are intended solely for the addressee >> and may contain confidential information. If you have received this >> message in error, please send it back to me, and immediately delete it. >> Please do not use, copy or disclose the information contained in this >> message or in any attachment. Any views or opinions expressed by the >> author of this email do not necessarily reflect the views of the >> University of Nottingham. >> >> This message has been checked for viruses but the contents of an >> attachment may still contain software viruses which could damage your >> computer system, you are advised to perform your own checks. Email >> communications with the University of Nottingham may be monitored as >> permitted by UK legislation. >> >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> > > > > -- > *Λ\oïs* > http://twitter.com/aloiscochard > http://github.com/aloiscochard > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From chr.maeder at web.de Sat Jul 9 07:09:17 2016 From: chr.maeder at web.de (C Maeder) Date: Sat, 9 Jul 2016 09:09:17 +0200 Subject: Proposal: ArgumentDo In-Reply-To: <577F95E3.2000004@nottingham.ac.uk> References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> Message-ID: <5780A31D.5080109@web.de> The asymmetry that you mention is already apparent for (Haskell98) infix expressions, i.e. when "composing" lambda- or if-expression: (if c then f else g) . \ x -> h x Parentheses around the last argument of "." do not matter, but parentheses around the first argument make a real difference (that the type checker will not detect)! Cheers Christian Am 08.07.2016 um 14:00 schrieb Henrik Nilsson: > Hi all, [...] > As a final point, the inherent asymmetry of the proposal (the > last argument position is special as, for certain kinds of > expressions, parentheses may be omitted there but not elsewhere) > is also deeply unsettling. > > Best, > > /Henrik > From spam at scientician.net Sat Jul 9 07:42:06 2016 From: spam at scientician.net (Bardur Arantsson) Date: Sat, 9 Jul 2016 09:42:06 +0200 Subject: Proposal: ArgumentDo In-Reply-To: <5780A31D.5080109@web.de> References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> <5780A31D.5080109@web.de> Message-ID: On 07/09/2016 09:09 AM, C Maeder wrote: > The asymmetry that you mention is already apparent for (Haskell98) infix > expressions, i.e. when "composing" lambda- or if-expression: > > (if c then f else g) . \ x -> h x > > Parentheses around the last argument of "." do not matter, but > parentheses around the first argument make a real difference (that the > type checker will not detect)! > What I'm reading here is essentially "Parser already does non-obvious thing" ===> "Adding more non-obvious things is fine!" This is simply bad reasoning, and I'm not sure why a number of people are saying it. Am I missing something? Regards, From Henrik.Nilsson at nottingham.ac.uk Sat Jul 9 09:46:14 2016 From: Henrik.Nilsson at nottingham.ac.uk (Henrik Nilsson) Date: Sat, 09 Jul 2016 10:46:14 +0100 Subject: Proposal: ArgumentDo In-Reply-To: <5780A31D.5080109@web.de> References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> <5780A31D.5080109@web.de> Message-ID: <5780C7E6.6030606@nottingham.ac.uk> Hi all, On 07/09/2016 08:09 AM, C Maeder wrote: > The asymmetry that you mention is already apparent for (Haskell98) infix > expressions, i.e. when "composing" lambda- or if-expression: > > (if c then f else g) . \ x -> h x > > Parentheses around the last argument of "." do not matter, but > parentheses around the first argument make a real difference But that has to do with how grammatical ambiguity related to in this case "if" and "lambda" are resolved by letting the constructs extend as far as possible to the right. This the standard way of resolving that kind of ambiguity across a very wide range of programming languages and parsing tools (e.g. preferring shift over reduce in an LR parser). (And also in principle how lexical ambiguities are typically resolved, sometimes referred to as the "maximal munch rule".) In contrast, the present proposal suggests treating different argument positions in grammatically different ways (different non-terminals). As far as I know, that is unprecedented. And in any case, it manifestly complicates the grammar (more non-terminals) and as a consequence adds another grammatical hurdle to learning the language. I think we often tend to forget just how exotic Haskell syntax can be to the uninitiated. Which is the vast majority of the rest of the programmer world as well as beginners. Only the other week I gave a presentation to a group of highly skilled developers at a tech-savvy London-based company. The emphasis of the talk was not at all on Haskell as such, but small Haskell fragments did feature here and there, which I (naively) thought would be mostly self explanatory. Well, let's just say I was wrong. Now, we can't make Haskell syntax less exotic (not that I'd advocate that: I think basic Haskell syntax for the most part strikes a pretty good balance on a number of counts), but we can certainly avoid making it even more complicated and exotic. Which the present proposal would, in my opinion. Best, /Henrik -- Henrik Nilsson School of Computer Science The University of Nottingham nhn at cs.nott.ac.uk This message and any attachment are intended solely for the addressee and may contain confidential information. If you have received this message in error, please send it back to me, and immediately delete it. Please do not use, copy or disclose the information contained in this message or in any attachment. Any views or opinions expressed by the author of this email do not necessarily reflect the views of the University of Nottingham. This message has been checked for viruses but the contents of an attachment may still contain software viruses which could damage your computer system, you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation. From carter.schonwald at gmail.com Sat Jul 9 12:45:21 2016 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 9 Jul 2016 08:45:21 -0400 Subject: Proposal: ArgumentDo In-Reply-To: <5780C7E6.6030606@nottingham.ac.uk> References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> <5780A31D.5080109@web.de> <5780C7E6.6030606@nottingham.ac.uk> Message-ID: On Saturday, July 9, 2016, Henrik Nilsson wrote: > Hi all, > > On 07/09/2016 08:09 AM, C Maeder wrote: > >> The asymmetry that you mention is already apparent for (Haskell98) infix >> expressions, i.e. when "composing" lambda- or if-expression: >> >> (if c then f else g) . \ x -> h x >> >> Parentheses around the last argument of "." do not matter, but >> parentheses around the first argument make a real difference >> > > But that has to do with how grammatical ambiguity related to > in this case "if" and "lambda" are resolved by letting > the constructs extend as far as possible to the right. > > This the standard way of resolving that kind of ambiguity > across a very wide range of programming languages and parsing > tools (e.g. preferring shift over reduce in an LR parser). > (And also in principle how lexical ambiguities are typically > resolved, sometimes referred to as the "maximal munch rule".) > > In contrast, the present proposal suggests treating > different argument positions in grammatically > different ways (different non-terminals). As far as I know, > that is unprecedented. And in any case, it manifestly > complicates the grammar (more non-terminals) and as > a consequence adds another grammatical hurdle to > learning the language. > > Well said, I think this articulates exactly what I'm reacting to. Thanks for taking the time to articulate this. I agree. > I think we often tend to forget just how exotic > Haskell syntax can be to the uninitiated. Which is > the vast majority of the rest of the programmer world > as well as beginners. Only the other week I gave a > presentation to a group of highly skilled developers > at a tech-savvy London-based company. The emphasis of > the talk was not at all on Haskell as such, but small > Haskell fragments did feature here and there, which I > (naively) thought would be mostly self explanatory. > Well, let's just say I was wrong. > > Now, we can't make Haskell syntax less exotic (not that I'd > advocate that: I think basic Haskell syntax for the most part > strikes a pretty good balance on a number of counts), but we can > certainly avoid making it even more complicated and exotic. > Which the present proposal would, in my opinion. > > Best, > > /Henrik > > -- > Henrik Nilsson > School of Computer Science > The University of Nottingham > nhn at cs.nott.ac.uk > > > > > This message and any attachment are intended solely for the addressee > and may contain confidential information. If you have received this > message in error, please send it back to me, and immediately delete it. > Please do not use, copy or disclose the information contained in this > message or in any attachment. Any views or opinions expressed by the > author of this email do not necessarily reflect the views of the > University of Nottingham. > > This message has been checked for viruses but the contents of an > attachment may still contain software viruses which could damage your > computer system, you are advised to perform your own checks. Email > communications with the University of Nottingham may be monitored as > permitted by UK legislation. > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ralf.hutchison at gmail.com Sat Jul 9 19:26:48 2016 From: ralf.hutchison at gmail.com (Ralf Hutchison) Date: Sat, 9 Jul 2016 12:26:48 -0700 Subject: Glasgow-haskell-users Digest, Vol 155, Issue 9 In-Reply-To: References: Message-ID: Well Iavor likes it. (see 2 below) Anyway, you know I'm really puzzled with the question of how to spend time. Maybe you can help me. In any case, it's such a lucky thing to have some to spend. Toshia and I are watching season 4 of Game of Thrones. I'm so addicted. I'm also addicted to speed chess in the same way. (I am ralf_ben_h at chess.com) I think that we have some structure in our minds, in our brains or our spines or our hearts say, and any story or game illuminates and awakens this structure. The addictive feeling or attachment is a fascination with this part of ourselves and a willingness to experience it. You wrote me a note about music recently. How are you feeling about music today? Best, Ralph On Sat, Jul 9, 2016 at 2:36 AM, wrote: > Send Glasgow-haskell-users mailing list submissions to > glasgow-haskell-users at haskell.org > > To subscribe or unsubscribe via the World Wide Web, visit > > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > or, via email, send a message with subject or body 'help' to > glasgow-haskell-users-request at haskell.org > > You can reach the person managing the list at > glasgow-haskell-users-owner at haskell.org > > When replying, please edit your Subject line so it is more specific > than "Re: Contents of Glasgow-haskell-users digest..." > > > Today's Topics: > > 1. layout was Re: Proposal: ArgumentDo (C Maeder) > 2. Re: Proposal: ArgumentDo (Iavor Diatchki) > 3. Re: Proposal: ArgumentDo (C Maeder) > 4. Re: Proposal: ArgumentDo (Bardur Arantsson) > 5. Re: Proposal: ArgumentDo (Henrik Nilsson) > > > ---------------------------------------------------------------------- > > Message: 1 > Date: Fri, 8 Jul 2016 14:37:04 +0200 > From: C Maeder > To: glasgow-haskell-users at haskell.org > Subject: layout was Re: Proposal: ArgumentDo > Message-ID: <577F9E70.5090300 at web.de> > Content-Type: text/plain; charset=utf-8 > > Hi, > > the layout language options are hard to find (at least in the user > guide). Therefore I try to give an overview here. The relevant options > I've found by using ghc-7.10.3 with option --supported-languages are: > > NondecreasingIndentation > DoAndIfThenElse > > RelaxedLayout > AlternativeLayoutRule > AlternativeLayoutRuleTransitional > > I ignore the last 3 options since these seem to be candidates for > removal: https://ghc.haskell.org/trac/ghc/ticket/11359. > > The default option is NondecreasingIndentation, that is > > do > x > do > y > > is legal and parsed as a single expression "do {x ; do y}". With > -XNoNondecreasingIndentation one gets an "Empty 'do' block" for the > second do (and this error would not change with ArgumentDo!). > > DoAndIfThenElse is not switched on by default and requires the keywords > "then" and "else" to be further indented for an "if" within a "do". > > So I believe these options do not interfere with ArgumentDo, but maybe > this should be discussed more and maybe mentioned on the wiki page. > > Surely a single space (inserted before x or removed before the second > "do") makes a difference between one or two argument expressions in the > example below. > > HTH Christian > > Am 08.07.2016 um 11:20 schrieb C Maeder: > > Surely layout can bite you: > > > > f > > do > > x > > do > > y > > > > and I'm having difficulties to find the documentation for the various > > layout options. > > > > But this is no argument against this proposal! > > > > Improper use of white spaces can always be used to obfuscate code! > > Style guides are important. Furthermore, a wrong/unintended parse tree > > (due to layout) will - in many cases - result in a typing error. > > > > Christian > > > > ------------------------------ > > Message: 2 > Date: Fri, 8 Jul 2016 09:42:24 -0700 > From: Iavor Diatchki > To: Aloïs Cochard > Cc: GHC users , Henrik Nilsson > > Subject: Re: Proposal: ArgumentDo > Message-ID: > g9FktDG37iE7EeFwW6P5w5GOud3dmQkHA8oukg at mail.gmail.com> > Content-Type: text/plain; charset="utf-8" > > Hello, > > while we are voting here, I kind of like this proposal, so +1 for me. > > I understand that some of the examples look strange to Haskell old-timers > but, as Joachim points out, the behavior is very consistent. Besides, the > "Less Obvious Examples" were selected so that they are, well, less obvious. > The common use cases (as in ticket #10843) seem quite appealing, at least > to me, and not at all confusing. But, then, I also like the > records-with-no-parens notation :-) > > -Iavor > > > > On Fri, Jul 8, 2016 at 5:03 AM, Aloïs Cochard > wrote: > > > -1 for same reasons. > > > > On 8 July 2016 at 14:00, Henrik Nilsson > > > wrote: > > > >> Hi all, > >> > >> Joachim Breitner wrote: > >> > >> > Am Freitag, den 08.07.2016, 13:09 +0200 schrieb Sven Panne: > >> > > I don't think so: https://ghc.haskell.org/trac/ghc > >> > /wiki/ArgumentDo#Bl > >> > [...] > >> > Where is the outer set of parenthesis coming from? > >> > > >> > This is all not related to the ArgumentDo notation. Note that [...] > >> > >> The very fact that that experts can't easily agree on how a small > >> Haskell fragment is parsed to me just confirms that Haskell already > >> is a syntactically very cumbersome language. > >> > >> The present proposal just makes matters worse. For that reason > >> alone, I don't find it compelling at all. (So -1 from me, then.) > >> > >> I will not repeat the many other strong arguments against that has been > >> made. But I must say I don't find the use cases as documented > >> on the associated web page compelling at all. Maybe there is a tacit > >> desire to be able to pretend functions are keywords for various > >> creative uses in supporting EDSLs and such. But for that to be truly > >> useful, one need to support groups of related keywords. Something > >> like Agda's mixfix syntax springs to mind. But this proposal does > >> not come close, so the benefits are minimal and the drawbacks large. > >> > >> As a final point, the inherent asymmetry of the proposal (the > >> last argument position is special as, for certain kinds of > >> expressions, parentheses may be omitted there but not elsewhere) > >> is also deeply unsettling. > >> > >> Best, > >> > >> /Henrik > >> > >> -- > >> Henrik Nilsson > >> School of Computer Science > >> The University of Nottingham > >> nhn at cs.nott.ac.uk > >> > >> > >> > >> > >> This message and any attachment are intended solely for the addressee > >> and may contain confidential information. If you have received this > >> message in error, please send it back to me, and immediately delete it. > >> Please do not use, copy or disclose the information contained in this > >> message or in any attachment. Any views or opinions expressed by the > >> author of this email do not necessarily reflect the views of the > >> University of Nottingham. > >> > >> This message has been checked for viruses but the contents of an > >> attachment may still contain software viruses which could damage your > >> computer system, you are advised to perform your own checks. Email > >> communications with the University of Nottingham may be monitored as > >> permitted by UK legislation. > >> > >> _______________________________________________ > >> Glasgow-haskell-users mailing list > >> Glasgow-haskell-users at haskell.org > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > >> > > > > > > > > -- > > *Λ\oïs* > > http://twitter.com/aloiscochard > > http://github.com/aloiscochard > > > > _______________________________________________ > > Glasgow-haskell-users mailing list > > Glasgow-haskell-users at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > > > -------------- next part -------------- > An HTML attachment was scrubbed... > URL: < > http://mail.haskell.org/pipermail/glasgow-haskell-users/attachments/20160708/f6d53261/attachment-0001.html > > > > ------------------------------ > > Message: 3 > Date: Sat, 9 Jul 2016 09:09:17 +0200 > From: C Maeder > To: Henrik Nilsson , > glasgow-haskell-users at haskell.org > Subject: Re: Proposal: ArgumentDo > Message-ID: <5780A31D.5080109 at web.de> > Content-Type: text/plain; charset=utf-8 > > The asymmetry that you mention is already apparent for (Haskell98) infix > expressions, i.e. when "composing" lambda- or if-expression: > > (if c then f else g) . \ x -> h x > > Parentheses around the last argument of "." do not matter, but > parentheses around the first argument make a real difference (that the > type checker will not detect)! > > Cheers Christian > > Am 08.07.2016 um 14:00 schrieb Henrik Nilsson: > > Hi all, > > [...] > > > As a final point, the inherent asymmetry of the proposal (the > > last argument position is special as, for certain kinds of > > expressions, parentheses may be omitted there but not elsewhere) > > is also deeply unsettling. > > > > Best, > > > > /Henrik > > > > > > ------------------------------ > > Message: 4 > Date: Sat, 9 Jul 2016 09:42:06 +0200 > From: Bardur Arantsson > To: glasgow-haskell-users at haskell.org > Subject: Re: Proposal: ArgumentDo > Message-ID: > Content-Type: text/plain; charset=utf-8 > > On 07/09/2016 09:09 AM, C Maeder wrote: > > The asymmetry that you mention is already apparent for (Haskell98) infix > > expressions, i.e. when "composing" lambda- or if-expression: > > > > (if c then f else g) . \ x -> h x > > > > Parentheses around the last argument of "." do not matter, but > > parentheses around the first argument make a real difference (that the > > type checker will not detect)! > > > > What I'm reading here is essentially > > "Parser already does non-obvious thing" > ===> "Adding more non-obvious things is fine!" > > This is simply bad reasoning, and I'm not sure why a number of people > are saying it. Am I missing something? > > Regards, > > > > ------------------------------ > > Message: 5 > Date: Sat, 09 Jul 2016 10:46:14 +0100 > From: Henrik Nilsson > To: C Maeder , Henrik Nilsson > , > glasgow-haskell-users at haskell.org > Subject: Re: Proposal: ArgumentDo > Message-ID: <5780C7E6.6030606 at nottingham.ac.uk> > Content-Type: text/plain; charset=UTF-8; format=flowed > > Hi all, > > On 07/09/2016 08:09 AM, C Maeder wrote: > > The asymmetry that you mention is already apparent for (Haskell98) infix > > expressions, i.e. when "composing" lambda- or if-expression: > > > > (if c then f else g) . \ x -> h x > > > > Parentheses around the last argument of "." do not matter, but > > parentheses around the first argument make a real difference > > But that has to do with how grammatical ambiguity related to > in this case "if" and "lambda" are resolved by letting > the constructs extend as far as possible to the right. > > This the standard way of resolving that kind of ambiguity > across a very wide range of programming languages and parsing > tools (e.g. preferring shift over reduce in an LR parser). > (And also in principle how lexical ambiguities are typically > resolved, sometimes referred to as the "maximal munch rule".) > > In contrast, the present proposal suggests treating > different argument positions in grammatically > different ways (different non-terminals). As far as I know, > that is unprecedented. And in any case, it manifestly > complicates the grammar (more non-terminals) and as > a consequence adds another grammatical hurdle to > learning the language. > > I think we often tend to forget just how exotic > Haskell syntax can be to the uninitiated. Which is > the vast majority of the rest of the programmer world > as well as beginners. Only the other week I gave a > presentation to a group of highly skilled developers > at a tech-savvy London-based company. The emphasis of > the talk was not at all on Haskell as such, but small > Haskell fragments did feature here and there, which I > (naively) thought would be mostly self explanatory. > Well, let's just say I was wrong. > > Now, we can't make Haskell syntax less exotic (not that I'd > advocate that: I think basic Haskell syntax for the most part > strikes a pretty good balance on a number of counts), but we can > certainly avoid making it even more complicated and exotic. > Which the present proposal would, in my opinion. > > Best, > > /Henrik > > -- > Henrik Nilsson > School of Computer Science > The University of Nottingham > nhn at cs.nott.ac.uk > > > > > This message and any attachment are intended solely for the addressee > and may contain confidential information. If you have received this > message in error, please send it back to me, and immediately delete it. > > Please do not use, copy or disclose the information contained in this > message or in any attachment. Any views or opinions expressed by the > author of this email do not necessarily reflect the views of the > University of Nottingham. > > This message has been checked for viruses but the contents of an > attachment may still contain software viruses which could damage your > computer system, you are advised to perform your own checks. Email > communications with the University of Nottingham may be monitored as > permitted by UK legislation. > > > > ------------------------------ > > Subject: Digest Footer > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > ------------------------------ > > End of Glasgow-haskell-users Digest, Vol 155, Issue 9 > ***************************************************** > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ralf.hutchison at gmail.com Sat Jul 9 19:32:49 2016 From: ralf.hutchison at gmail.com (Ralf Hutchison) Date: Sat, 9 Jul 2016 12:32:49 -0700 Subject: Glasgow-haskell-users Digest, Vol 155, Issue 9 In-Reply-To: References: Message-ID: continuing my thought, There was a medical student, Jonathan, working here at True North. He was really into macrobiotics and studied with the great Denny Waxman. Jonathan told me legends of the great George Oshawa who traveled the world as a sort of super human meeting with people and inspiring and teaching people. One thing that really stuck with me is the note that this Oshawa would wake very early (maybe 3?) and spend hours writing letters. That sounds so nice!! I am remembering with gratitude a letter you wrote me in Japan. Best, Ralph On Sat, Jul 9, 2016 at 12:26 PM, Ralf Hutchison wrote: > Well Iavor likes it. (see 2 below) > > Anyway, you know I'm really puzzled with the question of how to spend > time. > > Maybe you can help me. > > In any case, it's such a lucky thing to have some to spend. > > Toshia and I are watching season 4 of Game of Thrones. I'm so addicted. > > I'm also addicted to speed chess in the same way. (I am ralf_ben_h at > chess.com) > > I think that we have some structure in our minds, in our brains or our > spines or our hearts say, and any story or game illuminates and awakens > this structure. The addictive feeling or attachment is a fascination with > this part of ourselves and a willingness to experience it. > > You wrote me a note about music recently. How are you feeling about music > today? > > Best, > Ralph > > On Sat, Jul 9, 2016 at 2:36 AM, > wrote: > >> Send Glasgow-haskell-users mailing list submissions to >> glasgow-haskell-users at haskell.org >> >> To subscribe or unsubscribe via the World Wide Web, visit >> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> >> or, via email, send a message with subject or body 'help' to >> glasgow-haskell-users-request at haskell.org >> >> You can reach the person managing the list at >> glasgow-haskell-users-owner at haskell.org >> >> When replying, please edit your Subject line so it is more specific >> than "Re: Contents of Glasgow-haskell-users digest..." >> >> >> Today's Topics: >> >> 1. layout was Re: Proposal: ArgumentDo (C Maeder) >> 2. Re: Proposal: ArgumentDo (Iavor Diatchki) >> 3. Re: Proposal: ArgumentDo (C Maeder) >> 4. Re: Proposal: ArgumentDo (Bardur Arantsson) >> 5. Re: Proposal: ArgumentDo (Henrik Nilsson) >> >> >> ---------------------------------------------------------------------- >> >> Message: 1 >> Date: Fri, 8 Jul 2016 14:37:04 +0200 >> From: C Maeder >> To: glasgow-haskell-users at haskell.org >> Subject: layout was Re: Proposal: ArgumentDo >> Message-ID: <577F9E70.5090300 at web.de> >> Content-Type: text/plain; charset=utf-8 >> >> Hi, >> >> the layout language options are hard to find (at least in the user >> guide). Therefore I try to give an overview here. The relevant options >> I've found by using ghc-7.10.3 with option --supported-languages are: >> >> NondecreasingIndentation >> DoAndIfThenElse >> >> RelaxedLayout >> AlternativeLayoutRule >> AlternativeLayoutRuleTransitional >> >> I ignore the last 3 options since these seem to be candidates for >> removal: https://ghc.haskell.org/trac/ghc/ticket/11359. >> >> The default option is NondecreasingIndentation, that is >> >> do >> x >> do >> y >> >> is legal and parsed as a single expression "do {x ; do y}". With >> -XNoNondecreasingIndentation one gets an "Empty 'do' block" for the >> second do (and this error would not change with ArgumentDo!). >> >> DoAndIfThenElse is not switched on by default and requires the keywords >> "then" and "else" to be further indented for an "if" within a "do". >> >> So I believe these options do not interfere with ArgumentDo, but maybe >> this should be discussed more and maybe mentioned on the wiki page. >> >> Surely a single space (inserted before x or removed before the second >> "do") makes a difference between one or two argument expressions in the >> example below. >> >> HTH Christian >> >> Am 08.07.2016 um 11:20 schrieb C Maeder: >> > Surely layout can bite you: >> > >> > f >> > do >> > x >> > do >> > y >> > >> > and I'm having difficulties to find the documentation for the various >> > layout options. >> > >> > But this is no argument against this proposal! >> > >> > Improper use of white spaces can always be used to obfuscate code! >> > Style guides are important. Furthermore, a wrong/unintended parse tree >> > (due to layout) will - in many cases - result in a typing error. >> > >> > Christian >> >> >> >> ------------------------------ >> >> Message: 2 >> Date: Fri, 8 Jul 2016 09:42:24 -0700 >> From: Iavor Diatchki >> To: Aloïs Cochard >> Cc: GHC users , Henrik Nilsson >> >> Subject: Re: Proposal: ArgumentDo >> Message-ID: >> > g9FktDG37iE7EeFwW6P5w5GOud3dmQkHA8oukg at mail.gmail.com> >> Content-Type: text/plain; charset="utf-8" >> >> Hello, >> >> while we are voting here, I kind of like this proposal, so +1 for me. >> >> I understand that some of the examples look strange to Haskell old-timers >> but, as Joachim points out, the behavior is very consistent. Besides, >> the >> "Less Obvious Examples" were selected so that they are, well, less >> obvious. >> The common use cases (as in ticket #10843) seem quite appealing, at >> least >> to me, and not at all confusing. But, then, I also like the >> records-with-no-parens notation :-) >> >> -Iavor >> >> >> >> On Fri, Jul 8, 2016 at 5:03 AM, Aloïs Cochard >> wrote: >> >> > -1 for same reasons. >> > >> > On 8 July 2016 at 14:00, Henrik Nilsson < >> Henrik.Nilsson at nottingham.ac.uk> >> > wrote: >> > >> >> Hi all, >> >> >> >> Joachim Breitner wrote: >> >> >> >> > Am Freitag, den 08.07.2016, 13:09 +0200 schrieb Sven Panne: >> >> > > I don't think so: https://ghc.haskell.org/trac/ghc >> >> > /wiki/ArgumentDo#Bl >> >> > [...] >> >> > Where is the outer set of parenthesis coming from? >> >> > >> >> > This is all not related to the ArgumentDo notation. Note that [...] >> >> >> >> The very fact that that experts can't easily agree on how a small >> >> Haskell fragment is parsed to me just confirms that Haskell already >> >> is a syntactically very cumbersome language. >> >> >> >> The present proposal just makes matters worse. For that reason >> >> alone, I don't find it compelling at all. (So -1 from me, then.) >> >> >> >> I will not repeat the many other strong arguments against that has been >> >> made. But I must say I don't find the use cases as documented >> >> on the associated web page compelling at all. Maybe there is a tacit >> >> desire to be able to pretend functions are keywords for various >> >> creative uses in supporting EDSLs and such. But for that to be truly >> >> useful, one need to support groups of related keywords. Something >> >> like Agda's mixfix syntax springs to mind. But this proposal does >> >> not come close, so the benefits are minimal and the drawbacks large. >> >> >> >> As a final point, the inherent asymmetry of the proposal (the >> >> last argument position is special as, for certain kinds of >> >> expressions, parentheses may be omitted there but not elsewhere) >> >> is also deeply unsettling. >> >> >> >> Best, >> >> >> >> /Henrik >> >> >> >> -- >> >> Henrik Nilsson >> >> School of Computer Science >> >> The University of Nottingham >> >> nhn at cs.nott.ac.uk >> >> >> >> >> >> >> >> >> >> This message and any attachment are intended solely for the addressee >> >> and may contain confidential information. If you have received this >> >> message in error, please send it back to me, and immediately delete it. >> >> Please do not use, copy or disclose the information contained in this >> >> message or in any attachment. Any views or opinions expressed by the >> >> author of this email do not necessarily reflect the views of the >> >> University of Nottingham. >> >> >> >> This message has been checked for viruses but the contents of an >> >> attachment may still contain software viruses which could damage your >> >> computer system, you are advised to perform your own checks. Email >> >> communications with the University of Nottingham may be monitored as >> >> permitted by UK legislation. >> >> >> >> _______________________________________________ >> >> Glasgow-haskell-users mailing list >> >> Glasgow-haskell-users at haskell.org >> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> >> >> > >> > >> > >> > -- >> > *Λ\oïs* >> > http://twitter.com/aloiscochard >> > http://github.com/aloiscochard >> > >> > _______________________________________________ >> > Glasgow-haskell-users mailing list >> > Glasgow-haskell-users at haskell.org >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> > >> > >> -------------- next part -------------- >> An HTML attachment was scrubbed... >> URL: < >> http://mail.haskell.org/pipermail/glasgow-haskell-users/attachments/20160708/f6d53261/attachment-0001.html >> > >> >> ------------------------------ >> >> Message: 3 >> Date: Sat, 9 Jul 2016 09:09:17 +0200 >> From: C Maeder >> To: Henrik Nilsson , >> glasgow-haskell-users at haskell.org >> Subject: Re: Proposal: ArgumentDo >> Message-ID: <5780A31D.5080109 at web.de> >> Content-Type: text/plain; charset=utf-8 >> >> The asymmetry that you mention is already apparent for (Haskell98) infix >> expressions, i.e. when "composing" lambda- or if-expression: >> >> (if c then f else g) . \ x -> h x >> >> Parentheses around the last argument of "." do not matter, but >> parentheses around the first argument make a real difference (that the >> type checker will not detect)! >> >> Cheers Christian >> >> Am 08.07.2016 um 14:00 schrieb Henrik Nilsson: >> > Hi all, >> >> [...] >> >> > As a final point, the inherent asymmetry of the proposal (the >> > last argument position is special as, for certain kinds of >> > expressions, parentheses may be omitted there but not elsewhere) >> > is also deeply unsettling. >> > >> > Best, >> > >> > /Henrik >> > >> >> >> >> ------------------------------ >> >> Message: 4 >> Date: Sat, 9 Jul 2016 09:42:06 +0200 >> From: Bardur Arantsson >> To: glasgow-haskell-users at haskell.org >> Subject: Re: Proposal: ArgumentDo >> Message-ID: >> Content-Type: text/plain; charset=utf-8 >> >> On 07/09/2016 09:09 AM, C Maeder wrote: >> > The asymmetry that you mention is already apparent for (Haskell98) infix >> > expressions, i.e. when "composing" lambda- or if-expression: >> > >> > (if c then f else g) . \ x -> h x >> > >> > Parentheses around the last argument of "." do not matter, but >> > parentheses around the first argument make a real difference (that the >> > type checker will not detect)! >> > >> >> What I'm reading here is essentially >> >> "Parser already does non-obvious thing" >> ===> "Adding more non-obvious things is fine!" >> >> This is simply bad reasoning, and I'm not sure why a number of people >> are saying it. Am I missing something? >> >> Regards, >> >> >> >> ------------------------------ >> >> Message: 5 >> Date: Sat, 09 Jul 2016 10:46:14 +0100 >> From: Henrik Nilsson >> To: C Maeder , Henrik Nilsson >> , >> glasgow-haskell-users at haskell.org >> Subject: Re: Proposal: ArgumentDo >> Message-ID: <5780C7E6.6030606 at nottingham.ac.uk> >> Content-Type: text/plain; charset=UTF-8; format=flowed >> >> Hi all, >> >> On 07/09/2016 08:09 AM, C Maeder wrote: >> > The asymmetry that you mention is already apparent for (Haskell98) infix >> > expressions, i.e. when "composing" lambda- or if-expression: >> > >> > (if c then f else g) . \ x -> h x >> > >> > Parentheses around the last argument of "." do not matter, but >> > parentheses around the first argument make a real difference >> >> But that has to do with how grammatical ambiguity related to >> in this case "if" and "lambda" are resolved by letting >> the constructs extend as far as possible to the right. >> >> This the standard way of resolving that kind of ambiguity >> across a very wide range of programming languages and parsing >> tools (e.g. preferring shift over reduce in an LR parser). >> (And also in principle how lexical ambiguities are typically >> resolved, sometimes referred to as the "maximal munch rule".) >> >> In contrast, the present proposal suggests treating >> different argument positions in grammatically >> different ways (different non-terminals). As far as I know, >> that is unprecedented. And in any case, it manifestly >> complicates the grammar (more non-terminals) and as >> a consequence adds another grammatical hurdle to >> learning the language. >> >> I think we often tend to forget just how exotic >> Haskell syntax can be to the uninitiated. Which is >> the vast majority of the rest of the programmer world >> as well as beginners. Only the other week I gave a >> presentation to a group of highly skilled developers >> at a tech-savvy London-based company. The emphasis of >> the talk was not at all on Haskell as such, but small >> Haskell fragments did feature here and there, which I >> (naively) thought would be mostly self explanatory. >> Well, let's just say I was wrong. >> >> Now, we can't make Haskell syntax less exotic (not that I'd >> advocate that: I think basic Haskell syntax for the most part >> strikes a pretty good balance on a number of counts), but we can >> certainly avoid making it even more complicated and exotic. >> Which the present proposal would, in my opinion. >> >> Best, >> >> /Henrik >> >> -- >> Henrik Nilsson >> School of Computer Science >> The University of Nottingham >> nhn at cs.nott.ac.uk >> >> >> >> >> This message and any attachment are intended solely for the addressee >> and may contain confidential information. If you have received this >> message in error, please send it back to me, and immediately delete it. >> >> Please do not use, copy or disclose the information contained in this >> message or in any attachment. Any views or opinions expressed by the >> author of this email do not necessarily reflect the views of the >> University of Nottingham. >> >> This message has been checked for viruses but the contents of an >> attachment may still contain software viruses which could damage your >> computer system, you are advised to perform your own checks. Email >> communications with the University of Nottingham may be monitored as >> permitted by UK legislation. >> >> >> >> ------------------------------ >> >> Subject: Digest Footer >> >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> >> >> ------------------------------ >> >> End of Glasgow-haskell-users Digest, Vol 155, Issue 9 >> ***************************************************** >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at well-typed.com Sat Jul 9 20:45:35 2016 From: ben at well-typed.com (Ben Gamari) Date: Sat, 09 Jul 2016 22:45:35 +0200 Subject: Rethinking GHC's approach to managing proposals Message-ID: <87shvilevk.fsf@smart-cactus.org> Hello everyone, Recently there has been a fair bit of discussion[1,2] around the mechanisms by which proposed changes to GHC are evaluated. While we have something of a formal proposal protocol [3], it is not clearly documented, inconsistently applied, and may be failing to serve a significant fraction of GHC's potential contributor pool. Over the last few weeks, I have been doing a fair amount of reading, thinking, and discussing to try to piece together a proposal scheme which better serves our community. The resulting proposal [4] is strongly inspired by the RFC process in place in the Rust community [5], the leaders of which have thought quite hard about fostering community growth and participation. While no process is perfect, I feel like the Rust process is a good starting point for discussion, offering enough structure to guide new contributors through the process while requiring only a modest investment of developer time. To get a sense for how well this will work in our community, I propose that we attempt to self-host the proposed process. To this end I have setup a ghc-proposals repository [6] and opened a pull request for discussion of the process proposal [4]. Let's see how this goes. Cheers, - Ben [1] https://www.reddit.com/r/haskell/comments/4oyxo2/blog_contributing_to_ghc/ [2] https://www.reddit.com/r/haskell/comments/4isua9/ghc_development_outsidein/ [3] https://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/AddingFeatures [4] https://github.com/ghc-proposals/ghc-proposals/pull/1/files?short_path=14d66cd#diff-14d66cda32248456a5f223b6333c6132 [5] https://github.com/rust-lang/rfcs [6] https://github.com/ghc-proposals/ghc-proposals -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From chr.maeder at web.de Sun Jul 10 09:28:20 2016 From: chr.maeder at web.de (C Maeder) Date: Sun, 10 Jul 2016 11:28:20 +0200 Subject: Proposal: ArgumentDo In-Reply-To: <5780C7E6.6030606@nottingham.ac.uk> References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> <5780A31D.5080109@web.de> <5780C7E6.6030606@nottingham.ac.uk> Message-ID: <57821534.1070904@web.de> Hi Hendrik, juxtaposition (of grammar non-terminals aexp) is function application in Haskell. Why does an explicit infix operator make such a big difference for you? (if c then f else g) $ if d then a else b (if c then f else g) if d then a else b The keyword "if" starts a new expression. Nobody would wrongly parse this as "(...(if c then f else g) if)...)", because also nobody parses "... then a else b" wrongly as "... ((then a) else) b)". Actually, I see less rather than more non-terminals (no lexp) in the grammar and no additional ambiguity. Cheers Christian Am 09.07.2016 um 11:46 schrieb Henrik Nilsson: > Hi all, > > On 07/09/2016 08:09 AM, C Maeder wrote: >> The asymmetry that you mention is already apparent for (Haskell98) infix >> expressions, i.e. when "composing" lambda- or if-expression: >> >> (if c then f else g) . \ x -> h x >> >> Parentheses around the last argument of "." do not matter, but >> parentheses around the first argument make a real difference > > But that has to do with how grammatical ambiguity related to > in this case "if" and "lambda" are resolved by letting > the constructs extend as far as possible to the right. > > This the standard way of resolving that kind of ambiguity > across a very wide range of programming languages and parsing > tools (e.g. preferring shift over reduce in an LR parser). > (And also in principle how lexical ambiguities are typically > resolved, sometimes referred to as the "maximal munch rule".) > > In contrast, the present proposal suggests treating > different argument positions in grammatically > different ways (different non-terminals). As far as I know, > that is unprecedented. And in any case, it manifestly > complicates the grammar (more non-terminals) and as > a consequence adds another grammatical hurdle to > learning the language. > > I think we often tend to forget just how exotic > Haskell syntax can be to the uninitiated. Which is > the vast majority of the rest of the programmer world > as well as beginners. Only the other week I gave a > presentation to a group of highly skilled developers > at a tech-savvy London-based company. The emphasis of > the talk was not at all on Haskell as such, but small > Haskell fragments did feature here and there, which I > (naively) thought would be mostly self explanatory. > Well, let's just say I was wrong. > > Now, we can't make Haskell syntax less exotic (not that I'd > advocate that: I think basic Haskell syntax for the most part > strikes a pretty good balance on a number of counts), but we can > certainly avoid making it even more complicated and exotic. > Which the present proposal would, in my opinion. > > Best, > > /Henrik > From chr.maeder at web.de Sun Jul 10 09:30:43 2016 From: chr.maeder at web.de (C Maeder) Date: Sun, 10 Jul 2016 11:30:43 +0200 Subject: Proposal: ArgumentDo In-Reply-To: <57821534.1070904@web.de> References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> <5780A31D.5080109@web.de> <5780C7E6.6030606@nottingham.ac.uk> <57821534.1070904@web.de> Message-ID: <578215C3.6040302@web.de> Hi Henrik apologize my "d" in your name below. Am 10.07.2016 um 11:28 schrieb C Maeder: > Hi Hendrik, > > juxtaposition (of grammar non-terminals aexp) is function application in > Haskell. > > Why does an explicit infix operator make such a big difference for you? > > (if c then f else g) $ if d then a else b > > (if c then f else g) if d then a else b > > The keyword "if" starts a new expression. Nobody would wrongly parse > this as "(...(if c then f else g) if)...)", because also nobody parses > "... then a else b" wrongly as "... ((then a) else) b)". > > Actually, I see less rather than more non-terminals (no lexp) in the > grammar and no additional ambiguity. > > Cheers Christian > > Am 09.07.2016 um 11:46 schrieb Henrik Nilsson: >> Hi all, >> >> On 07/09/2016 08:09 AM, C Maeder wrote: >>> The asymmetry that you mention is already apparent for (Haskell98) infix >>> expressions, i.e. when "composing" lambda- or if-expression: >>> >>> (if c then f else g) . \ x -> h x >>> >>> Parentheses around the last argument of "." do not matter, but >>> parentheses around the first argument make a real difference >> >> But that has to do with how grammatical ambiguity related to >> in this case "if" and "lambda" are resolved by letting >> the constructs extend as far as possible to the right. >> >> This the standard way of resolving that kind of ambiguity >> across a very wide range of programming languages and parsing >> tools (e.g. preferring shift over reduce in an LR parser). >> (And also in principle how lexical ambiguities are typically >> resolved, sometimes referred to as the "maximal munch rule".) >> >> In contrast, the present proposal suggests treating >> different argument positions in grammatically >> different ways (different non-terminals). As far as I know, >> that is unprecedented. And in any case, it manifestly >> complicates the grammar (more non-terminals) and as >> a consequence adds another grammatical hurdle to >> learning the language. >> >> I think we often tend to forget just how exotic >> Haskell syntax can be to the uninitiated. Which is >> the vast majority of the rest of the programmer world >> as well as beginners. Only the other week I gave a >> presentation to a group of highly skilled developers >> at a tech-savvy London-based company. The emphasis of >> the talk was not at all on Haskell as such, but small >> Haskell fragments did feature here and there, which I >> (naively) thought would be mostly self explanatory. >> Well, let's just say I was wrong. >> >> Now, we can't make Haskell syntax less exotic (not that I'd >> advocate that: I think basic Haskell syntax for the most part >> strikes a pretty good balance on a number of counts), but we can >> certainly avoid making it even more complicated and exotic. >> Which the present proposal would, in my opinion. >> >> Best, >> >> /Henrik >> > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From asyropoulos at aol.com Sun Jul 10 13:58:34 2016 From: asyropoulos at aol.com (asyropoulos at aol.com) Date: Sun, 10 Jul 2016 09:58:34 -0400 Subject: Rethinking GHC's approach to managing proposals In-Reply-To: <87shvilevk.fsf@smart-cactus.org> References: <87shvilevk.fsf@smart-cactus.org> Message-ID: <155d51a3e5c-cd9-1fe57@webprd-m28.mail.aol.com> >Recently there has been a fair bit of discussion[1,2] around the >mechanisms by which proposed changes to GHC are evaluated. While we have >something of a formal proposal protocol [3], it is not clearly >documented, inconsistently applied, and may be failing to serve a >significant fraction of GHC's potential contributor pool. I think the best thing to do is to fork the source code and modify it according to one's own needs. Having some sort of committees to decide about the syntax, etc. is a really bad idea. A.S. -- Apostolos Syropoulos Xanthi, Greece -------------- next part -------------- An HTML attachment was scrubbed... URL: From tkn.akio at gmail.com Mon Jul 11 01:33:48 2016 From: tkn.akio at gmail.com (Akio Takano) Date: Mon, 11 Jul 2016 01:33:48 +0000 Subject: Proposal: ArgumentDo In-Reply-To: <577D2CE9.1050504@web.de> References: <577D2CE9.1050504@web.de> Message-ID: Hi Christian, On 6 July 2016 at 16:08, C Maeder wrote: > Hi, > > allowing group A constructs (do, case, ...) and group B constructs (\, > let, if, ...) as parts of functions application (fexp) without extra > parentheses looks natural to me. The current state is an artificial and > unnecessary restriction. Style guides may dictate restrictions, but the > parser/language should not (without good reasons). > > So +1 for the proposal from me. > > However, I would not distinguish group A and group B constructs in the > proposed grammar rules. The report already states (for the group B > constructs): > "The grammar is ambiguous regarding the extent of lambda abstractions, > let expressions, and conditionals. The ambiguity is resolved by the > meta-rule that each of these constructs extends as far to the right as > possible." This is a good point, I have updated the wiki page and simplified the grammar change. Thank you, Akio From tkn.akio at gmail.com Mon Jul 11 01:53:42 2016 From: tkn.akio at gmail.com (Akio Takano) Date: Mon, 11 Jul 2016 01:53:42 +0000 Subject: Proposal: ArgumentDo In-Reply-To: References: <1467917429.28020.5.camel@joachim-breitner.de> Message-ID: Hi Ryan, On 7 July 2016 at 19:40, Ryan Trinkle wrote: > I'm very on the fence on this topic, but one point i haven't seen mentioned > is the influence of syntax highlighting on this. My guess is that I would > like this extension when I have syntax highlighting available and would > dislike it when I do not. vim and hscolour can highlight code with the new syntax just fine. I imagine that most existing syntax highlighter will be able to deal with the new syntax without needing to be updated, because they usually don't attempt to fully parse expressions: they mostly just pattern-match on tokens. - Akio > > Also, I agree with Carter about the record update syntax - I find it harder > to parse visually than most other parts of the language, and I expect I'd > find curly brace syntax for inline 'do' harder to parse in a similar way. > On the other hand, maybe I should get used to both... > > On Thu, Jul 7, 2016 at 2:50 PM, Joachim Breitner > wrote: >> >> Hi, >> >> Am Donnerstag, den 07.07.2016, 13:15 -0400 schrieb Carter Schonwald: >> > agreed -1, >> > ambiguity is bad for humans, not just parsers. >> > >> > perhaps most damningly, >> > > f do{ x } do { y } >> > >> > is just reallly really weird/confusing to me, >> >> It is weird to me, but in no way confusing under the simple new rules, >> and I am actually looking forward to using that, and also to reading >> code with that. >> >> In fact, everything I wanted to pass two arguments in do-notation to a >> function I felt at a loss. The prospect of itemizing multiple large >> arguments to a function by writing >> >> someFunctionWithManyArguments >> do firstArgument >> do second Argument which may span >> several lines >> do third Argument >> >> is actually making me happy! It feels like going from XML to YAML... >> >> Greetings, >> Joachim >> >> -- >> >> Joachim “nomeata” Breitner >> mail at joachim-breitner.de • https://www.joachim-breitner.de/ >> XMPP: nomeata at joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F >> Debian Developer: nomeata at debian.org >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users >> > > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From tkn.akio at gmail.com Mon Jul 11 02:06:18 2016 From: tkn.akio at gmail.com (Akio Takano) Date: Mon, 11 Jul 2016 02:06:18 +0000 Subject: Proposal: ArgumentDo In-Reply-To: <5780C7E6.6030606@nottingham.ac.uk> References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> <5780A31D.5080109@web.de> <5780C7E6.6030606@nottingham.ac.uk> Message-ID: Hi Henrik, On 9 July 2016 at 09:46, Henrik Nilsson wrote: > Hi all, > > On 07/09/2016 08:09 AM, C Maeder wrote: >> >> The asymmetry that you mention is already apparent for (Haskell98) infix >> expressions, i.e. when "composing" lambda- or if-expression: >> >> (if c then f else g) . \ x -> h x >> >> Parentheses around the last argument of "." do not matter, but >> parentheses around the first argument make a real difference > > > But that has to do with how grammatical ambiguity related to > in this case "if" and "lambda" are resolved by letting > the constructs extend as far as possible to the right. > > This the standard way of resolving that kind of ambiguity > across a very wide range of programming languages and parsing > tools (e.g. preferring shift over reduce in an LR parser). > (And also in principle how lexical ambiguities are typically > resolved, sometimes referred to as the "maximal munch rule".) > > In contrast, the present proposal suggests treating > different argument positions in grammatically > different ways (different non-terminals). As far as I know, > that is unprecedented. And in any case, it manifestly > complicates the grammar (more non-terminals) and as > a consequence adds another grammatical hurdle to > learning the language. Thank you for pointing this out. I have updated the proposal so that it doesn't introduce a new non-terminal. I'm not sure if it should be implemented this way in the GHC parser, but this is probably a separate question. - Akio From ryan.trinkle at gmail.com Mon Jul 11 02:07:19 2016 From: ryan.trinkle at gmail.com (Ryan Trinkle) Date: Sun, 10 Jul 2016 22:07:19 -0400 Subject: Proposal: ArgumentDo In-Reply-To: References: <1467917429.28020.5.camel@joachim-breitner.de> Message-ID: Akio, Yes, definitely! I think I was a bit unclear, but what I was trying to say was that, in the (rare) circumstances in which I'm editing Haskell without the benefit of syntax highlighting, the difference between keywords and identifiers is not quite as obvious. In those cases, requiring an operator may make things easier to read. This is a very small point, but I appreciate you taking the time to respond! Ryan On Sun, Jul 10, 2016 at 9:53 PM, Akio Takano wrote: > Hi Ryan, > > On 7 July 2016 at 19:40, Ryan Trinkle wrote: > > I'm very on the fence on this topic, but one point i haven't seen > mentioned > > is the influence of syntax highlighting on this. My guess is that I > would > > like this extension when I have syntax highlighting available and would > > dislike it when I do not. > > vim and hscolour can highlight code with the new syntax just fine. I > imagine that most existing syntax highlighter will be able to deal > with the new syntax without needing to be updated, because they > usually don't attempt to fully parse expressions: they mostly just > pattern-match on tokens. > > - Akio > > > > > Also, I agree with Carter about the record update syntax - I find it > harder > > to parse visually than most other parts of the language, and I expect I'd > > find curly brace syntax for inline 'do' harder to parse in a similar way. > > On the other hand, maybe I should get used to both... > > > > On Thu, Jul 7, 2016 at 2:50 PM, Joachim Breitner < > mail at joachim-breitner.de> > > wrote: > >> > >> Hi, > >> > >> Am Donnerstag, den 07.07.2016, 13:15 -0400 schrieb Carter Schonwald: > >> > agreed -1, > >> > ambiguity is bad for humans, not just parsers. > >> > > >> > perhaps most damningly, > >> > > f do{ x } do { y } > >> > > >> > is just reallly really weird/confusing to me, > >> > >> It is weird to me, but in no way confusing under the simple new rules, > >> and I am actually looking forward to using that, and also to reading > >> code with that. > >> > >> In fact, everything I wanted to pass two arguments in do-notation to a > >> function I felt at a loss. The prospect of itemizing multiple large > >> arguments to a function by writing > >> > >> someFunctionWithManyArguments > >> do firstArgument > >> do second Argument which may span > >> several lines > >> do third Argument > >> > >> is actually making me happy! It feels like going from XML to YAML... > >> > >> Greetings, > >> Joachim > >> > >> -- > >> > >> Joachim “nomeata” Breitner > >> mail at joachim-breitner.de • https://www.joachim-breitner.de/ > >> XMPP: nomeata at joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F > >> Debian Developer: nomeata at debian.org > >> _______________________________________________ > >> Glasgow-haskell-users mailing list > >> Glasgow-haskell-users at haskell.org > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > >> > > > > > > _______________________________________________ > > Glasgow-haskell-users mailing list > > Glasgow-haskell-users at haskell.org > > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tkn.akio at gmail.com Mon Jul 11 02:24:12 2016 From: tkn.akio at gmail.com (Akio Takano) Date: Mon, 11 Jul 2016 02:24:12 +0000 Subject: ArgumentDo proposal updated Message-ID: Hi glasgow-haskell-users, Thank you for all the feedback to the ArgumentDo proposal. Following the discussion, I made changes to the proposal and updated the wiki page [0]. Now the proposed grammar is greatly simplified: it doesn't add a new non-terminal anymore, indeed it removes one instead. The proposed set of accepted programs remains unchanged. I hope the this update addresses one major concern that was raised in the previous discussion. Any feedback is appreciated. Regards, Takano Akio [0]: https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo From svenpanne at gmail.com Mon Jul 11 06:31:55 2016 From: svenpanne at gmail.com (Sven Panne) Date: Mon, 11 Jul 2016 08:31:55 +0200 Subject: Proposal: ArgumentDo In-Reply-To: <57821534.1070904@web.de> References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> <5780A31D.5080109@web.de> <5780C7E6.6030606@nottingham.ac.uk> <57821534.1070904@web.de> Message-ID: 2016-07-10 11:28 GMT+02:00 C Maeder : > [...] Why does an explicit infix operator make such a big difference for > you? > > (if c then f else g) $ if d then a else b > > (if c then f else g) if d then a else b > [...] > Because at first glance, this is visually only a tiny fraction away from (if c then f else g) it d them a elsa b which would be parsed in a totally different way. (Personally, I think that if/then/else is useless in Haskell and just a concession for readers from other programming languages. Having a plain old "if" function would have done the job in a more consistent way.) Of course syntax highlighting improves readability here, but code should be easily digestible in black and white, too. Visual clues matter... -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Mon Jul 11 07:45:18 2016 From: mail at joachim-breitner.de (Joachim Breitner) Date: Mon, 11 Jul 2016 09:45:18 +0200 Subject: Proposal: ArgumentDo In-Reply-To: References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> <5780A31D.5080109@web.de> <5780C7E6.6030606@nottingham.ac.uk> <57821534.1070904@web.de> Message-ID: <1468223118.1589.7.camel@joachim-breitner.de> Hi, Am Montag, den 11.07.2016, 08:31 +0200 schrieb Sven Panne: > Because at first glance, this is visually only a tiny fraction away > from >   >    (if c then f else g)  it d them a elsa b > > which would be parsed in a totally different way. (Personally, I > think that if/then/else is useless in Haskell and just a concession > for readers from other programming languages. Having a plain old "if" > function would have done the job in a more consistent way.) Of course > syntax highlighting improves readability here, but code should be > easily digestible in black and white, too. Visual clues matter... I believe we can and should expect programmers to know the keywords (there are not many of them) and should _not_ compromise other goals for “makes similar sense even if a keyword is mistake or mistyped as a symbol name”. Greetings, Joachim -- Joachim “nomeata” Breitner   mail at joachim-breitner.de • https://www.joachim-breitner.de/   XMPP: nomeata at joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F   Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From chr.maeder at web.de Mon Jul 11 08:27:44 2016 From: chr.maeder at web.de (C Maeder) Date: Mon, 11 Jul 2016 10:27:44 +0200 Subject: Proposal: ArgumentDo In-Reply-To: References: <1467961791.1639.3.camel@joachim-breitner.de> <1467973707.1639.10.camel@joachim-breitner.de> <1467977265.1639.15.camel@joachim-breitner.de> <577F95E3.2000004@nottingham.ac.uk> <5780A31D.5080109@web.de> <5780C7E6.6030606@nottingham.ac.uk> <57821534.1070904@web.de> Message-ID: <57835880.70009@web.de> Hi Sven, a wrongly spelled keyword will soon be detected by the checker in either cases. Readability is the responsibility of programmers. It is up to you or a team to use parentheses for the examples below. (I find a line break and indentation to be sufficient.) (I know people - mostly beginners - that insist on using "if b then True else False" instead of "b" for readability reasons.) Surely, a grammar could enforce more redundancy, but this is usually considered as an annoyance (in particular for instance distant closing tags that are more or less hidden in a pile of other closing tags). The $-notation was (in the first place) only used (and maybe misused) to avoid additional parentheses. Haskell's strong typing is the major safeguard (against spelling errors). Cheers Christian Am 11.07.2016 um 08:31 schrieb Sven Panne: > 2016-07-10 11:28 GMT+02:00 C Maeder >: > > [...] Why does an explicit infix operator make such a big difference > for you? > > (if c then f else g) $ if d then a else b > > (if c then f else g) if d then a else b > [...] > > > Because at first glance, this is visually only a tiny fraction away from > > (if c then f else g) it d them a elsa b > > which would be parsed in a totally different way. (Personally, I think > that if/then/else is useless in Haskell and just a concession for > readers from other programming languages. Having a plain old "if" > function would have done the job in a more consistent way.) Of course > syntax highlighting improves readability here, but code should be easily > digestible in black and white, too. Visual clues matter... From ben at smart-cactus.org Mon Jul 11 13:40:10 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Mon, 11 Jul 2016 15:40:10 +0200 Subject: Rethinking GHC's approach to managing proposals In-Reply-To: <155d51a3e5c-cd9-1fe57@webprd-m28.mail.aol.com> References: <87shvilevk.fsf@smart-cactus.org> <155d51a3e5c-cd9-1fe57@webprd-m28.mail.aol.com> Message-ID: <87r3b05m4l.fsf@smart-cactus.org> Apostolos Syropoulos via Glasgow-haskell-users writes: > >Recently there has been a fair bit of discussion[1,2] around the >>mechanisms by which proposed changes to GHC are evaluated. While we have >>something of a formal proposal protocol [3], it is not clearly >>documented, inconsistently applied, and may be failing to serve a >>significant fraction of GHC's potential contributor pool. > > I think the best thing to do is to fork the source code and modify it according > to one's own needs. Having some sort of committees to decide about the > syntax, etc. is a really bad idea. > The point here is not to place a committee in charge of designing features. To the contrary, the point of this proposal is to revamp our protocol for handling proposals brought by others. The committee merely serves as a gatekeeper to ensure that GHC's design and implementation remains coherent and maintainable and its semantics well-defined. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From simonpj at microsoft.com Mon Jul 11 21:36:27 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Mon, 11 Jul 2016 21:36:27 +0000 Subject: Rethinking GHC's approach to managing proposals In-Reply-To: <87shvilevk.fsf@smart-cactus.org> References: <87shvilevk.fsf@smart-cactus.org> Message-ID: Just to be clear: * We are actively seeking feedback about the proposal [4] below. It's not a fait-accompli. * You can join the dialogue by (a) replying to this email, (b) via the "Conversations" tab of [4], namely https://github.com/ghc-proposals/ghc-proposals/pull/1 Doubtless via reddit too! If you don't like something, the more specific and concrete you can be about a better alternative, the better. E.g. Richard's comments on the "conversations" tab both ask questions and propose answers. Bravo! Simon | -----Original Message----- | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Ben | Gamari | Sent: 09 July 2016 21:46 | To: GHC developers ; ghc-users | Subject: Rethinking GHC's approach to managing proposals | | Hello everyone, | | Recently there has been a fair bit of discussion[1,2] around the | mechanisms by which proposed changes to GHC are evaluated. While we have | something of a formal proposal protocol [3], it is not clearly | documented, inconsistently applied, and may be failing to serve a | significant fraction of GHC's potential contributor pool. | | Over the last few weeks, I have been doing a fair amount of reading, | thinking, and discussing to try to piece together a proposal scheme | which better serves our community. | | The resulting proposal [4] is strongly inspired by the RFC process in | place in the Rust community [5], the leaders of which have thought quite | hard about fostering community growth and participation. While no | process is perfect, I feel like the Rust process is a good starting | point for discussion, offering enough structure to guide new | contributors through the process while requiring only a modest | investment of developer time. | | To get a sense for how well this will work in our community, I propose | that we attempt to self-host the proposed process. To this end I have | setup a ghc-proposals repository [6] and opened a pull request for | discussion of the process proposal [4]. | | Let's see how this goes. | | Cheers, | | - Ben | | | [1] | https://na01.safelinks.protection.outlook.com/?url=https%3a%2f%2fwww.red | dit.com%2fr%2fhaskell%2fcomments%2f4oyxo2%2fblog_contributing_to_ghc%2f& | data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c99735311c5f64cac6a6608 | d3a83a032a%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=Hl6GqRWfu7IOQtpE | jpfsNAkv3mmLgNKm2ciQDoMe6HA%3d | [2] | https://na01.safelinks.protection.outlook.com/?url=https%3a%2f%2fwww.red | dit.com%2fr%2fhaskell%2fcomments%2f4isua9%2fghc_development_outsidein%2f | &data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c99735311c5f64cac6a660 | 8d3a83a032a%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=bj2AQqQirX3X%2f | 4%2fFr05eXFuD4yW0r9Nmrmdg7IGEF%2f8%3d | [3] | https://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/AddingFeatures | [4] https://github.com/ghc-proposals/ghc- | proposals/pull/1/files?short_path=14d66cd#diff- | 14d66cda32248456a5f223b6333c6132 | [5] https://github.com/rust-lang/rfcs | [6] https://github.com/ghc-proposals/ghc-proposals From iavor.diatchki at gmail.com Mon Jul 11 22:00:46 2016 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Mon, 11 Jul 2016 15:00:46 -0700 Subject: Rethinking GHC's approach to managing proposals In-Reply-To: References: <87shvilevk.fsf@smart-cactus.org> Message-ID: Hello, I think this sounds fairly reasonable, but it is hard to say how well it will work in practice until we try it. Some clarifying questions on the intended process: 1. After submitting the initial merge request, is the person making the proposal to wait for any kind of acknowledgment, or just move on to step 2? 2. Is the discussion going to happen on one of the mailing lists, if so which? Is it the job of the proposing person to involve/notify the committee about the discussion? If so, how are they to find out who is on the committee? 3. How does one actually perform step 3, another pull request or simply an e-mail to someone? Typo: two separate bullets in the proposal are labelled as 4. Cheers, -Iavor On Mon, Jul 11, 2016 at 2:36 PM, Simon Peyton Jones via Glasgow-haskell-users wrote: > Just to be clear: > > * We are actively seeking feedback about the proposal [4] below. > It's not a fait-accompli. > > * You can join the dialogue by (a) replying to this email, > (b) via the "Conversations" tab of [4], namely > https://github.com/ghc-proposals/ghc-proposals/pull/1 > Doubtless via reddit too! > > If you don't like something, the more specific and concrete you > can be about a better alternative, the better. E.g. Richard's > comments on the "conversations" tab both ask questions and propose > answers. Bravo! > > Simon > > | -----Original Message----- > | From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of Ben > | Gamari > | Sent: 09 July 2016 21:46 > | To: GHC developers ; ghc-users | users at haskell.org> > | Subject: Rethinking GHC's approach to managing proposals > | > | Hello everyone, > | > | Recently there has been a fair bit of discussion[1,2] around the > | mechanisms by which proposed changes to GHC are evaluated. While we have > | something of a formal proposal protocol [3], it is not clearly > | documented, inconsistently applied, and may be failing to serve a > | significant fraction of GHC's potential contributor pool. > | > | Over the last few weeks, I have been doing a fair amount of reading, > | thinking, and discussing to try to piece together a proposal scheme > | which better serves our community. > | > | The resulting proposal [4] is strongly inspired by the RFC process in > | place in the Rust community [5], the leaders of which have thought quite > | hard about fostering community growth and participation. While no > | process is perfect, I feel like the Rust process is a good starting > | point for discussion, offering enough structure to guide new > | contributors through the process while requiring only a modest > | investment of developer time. > | > | To get a sense for how well this will work in our community, I propose > | that we attempt to self-host the proposed process. To this end I have > | setup a ghc-proposals repository [6] and opened a pull request for > | discussion of the process proposal [4]. > | > | Let's see how this goes. > | > | Cheers, > | > | - Ben > | > | > | [1] > | https://na01.safelinks.protection.outlook.com/?url=https%3a%2f%2fwww.red > | dit.com%2fr%2fhaskell%2fcomments%2f4oyxo2%2fblog_contributing_to_ghc%2f& > | data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c99735311c5f64cac6a6608 > | d3a83a032a%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=Hl6GqRWfu7IOQtpE > | jpfsNAkv3mmLgNKm2ciQDoMe6HA%3d > | [2] > | https://na01.safelinks.protection.outlook.com/?url=https%3a%2f%2fwww.red > | dit.com%2fr%2fhaskell%2fcomments%2f4isua9%2fghc_development_outsidein%2f > | &data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c99735311c5f64cac6a660 > | 8d3a83a032a%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=bj2AQqQirX3X%2f > | 4%2fFr05eXFuD4yW0r9Nmrmdg7IGEF%2f8%3d > | [3] > | https://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/AddingFeatures > | [4] https://github.com/ghc-proposals/ghc- > | proposals/pull/1/files?short_path=14d66cd#diff- > | 14d66cda32248456a5f223b6333c6132 > | [5] https://github.com/rust-lang/rfcs > | [6] https://github.com/ghc-proposals/ghc-proposals > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonpj at microsoft.com Tue Jul 12 08:36:17 2016 From: simonpj at microsoft.com (Simon Peyton Jones) Date: Tue, 12 Jul 2016 08:36:17 +0000 Subject: ArgumentDo proposal updated In-Reply-To: References: Message-ID: <5dd9d25118f7462fbb043ce94b87b873@DB4PR30MB030.064d.mgd.msft.net> I've added record construction and update to the syntax, which makes it clearer how the other constructs are analogous to them. Simon | -----Original Message----- | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- | bounces at haskell.org] On Behalf Of Akio Takano | Sent: 11 July 2016 03:24 | To: glasgow-haskell-users at haskell.org | Subject: ArgumentDo proposal updated | | Hi glasgow-haskell-users, | | Thank you for all the feedback to the ArgumentDo proposal. Following | the discussion, I made changes to the proposal and updated the wiki | page [0]. | | Now the proposed grammar is greatly simplified: it doesn't add a new | non-terminal anymore, indeed it removes one instead. The proposed set | of accepted programs remains unchanged. | | I hope the this update addresses one major concern that was raised in | the previous discussion. | | Any feedback is appreciated. | | Regards, | Takano Akio | | [0]: https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users at haskell.org | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h | askell.org%2fcgi-bin%2fmailman%2flistinfo%2fglasgow-haskell- | users&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c4ef11cd0d5d041 | 3ac28108d3a9327fd1%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=flpo46 | T9CWuGH8ndJY3roC44iubY7U8xeYWkJ2J8Img%3d From chr.maeder at web.de Wed Jul 13 09:42:09 2016 From: chr.maeder at web.de (C Maeder) Date: Wed, 13 Jul 2016 11:42:09 +0200 Subject: ArgumentDo proposal updated In-Reply-To: <5dd9d25118f7462fbb043ce94b87b873@DB4PR30MB030.064d.mgd.msft.net> References: <5dd9d25118f7462fbb043ce94b87b873@DB4PR30MB030.064d.mgd.msft.net> Message-ID: <57860CF1.7030006@web.de> seeing aexp -> qvar (variable) | gcon (general constructor) ... | qcon { fbind1 … fbindn } (labeled construction) | aexp { fbind1 … fbindn } (labelled update) and https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-220003 I realise that the update requires at least one field binding whereas for a construction "C {}" (n = 0) could be used. ("C {}" makes sense for patterns!) And due to the meta-rule a labelled update is not possible for a lambda abstraction, let expression, or conditional (as aexp), but it is for case (and do if the record type happens to be a monad). So a further less obvious example is: case e of p -> r { f = v } that will be parsed as: (case e of p -> r) { f = v } (I'm sure the grammar could be fully disambiguated, but this would not improve readability. Preferring shift over reduce is common and fine for such cases.) Cheers Christian Am 12.07.2016 um 10:36 schrieb Simon Peyton Jones via Glasgow-haskell-users: > I've added record construction and update to the syntax, which makes it clearer how the other constructs are analogous to them. > > Simon > > | -----Original Message----- > | From: Glasgow-haskell-users [mailto:glasgow-haskell-users- > | bounces at haskell.org] On Behalf Of Akio Takano > | Sent: 11 July 2016 03:24 > | To: glasgow-haskell-users at haskell.org > | Subject: ArgumentDo proposal updated > | > | Hi glasgow-haskell-users, > | > | Thank you for all the feedback to the ArgumentDo proposal. Following > | the discussion, I made changes to the proposal and updated the wiki > | page [0]. > | > | Now the proposed grammar is greatly simplified: it doesn't add a new > | non-terminal anymore, indeed it removes one instead. The proposed set > | of accepted programs remains unchanged. > | > | I hope the this update addresses one major concern that was raised in > | the previous discussion. > | > | Any feedback is appreciated. > | > | Regards, > | Takano Akio > | > | [0]: https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo > | _______________________________________________ > | Glasgow-haskell-users mailing list > | Glasgow-haskell-users at haskell.org > | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.h > | askell.org%2fcgi-bin%2fmailman%2flistinfo%2fglasgow-haskell- > | users&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c4ef11cd0d5d041 > | 3ac28108d3a9327fd1%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=flpo46 > | T9CWuGH8ndJY3roC44iubY7U8xeYWkJ2J8Img%3d > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > From targen at gmail.com Wed Jul 13 17:35:42 2016 From: targen at gmail.com (=?UTF-8?Q?Manuel_G=C3=B3mez?=) Date: Wed, 13 Jul 2016 13:35:42 -0400 Subject: ArgumentDo proposal updated In-Reply-To: <57860CF1.7030006@web.de> References: <5dd9d25118f7462fbb043ce94b87b873@DB4PR30MB030.064d.mgd.msft.net> <57860CF1.7030006@web.de> Message-ID: On Wed, Jul 13, 2016 at 5:42 AM, C Maeder wrote: > seeing > > aexp -> qvar (variable) > | gcon (general constructor) > ... > | qcon { fbind1 … fbindn } (labeled construction) > | aexp { fbind1 … fbindn } (labelled update) > > and > https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-220003 > > I realise that the update requires at least one field binding whereas > for a construction "C {}" (n = 0) could be used. ("C {}" makes sense > for patterns!) > > And due to the meta-rule a labelled update is not possible for a lambda > abstraction, let expression, or conditional (as aexp), but it is for > case (and do if the record type happens to be a monad). So a further > less obvious example is: > > case e of > p -> r > { f = v } > > that will be parsed as: (case e of p -> r) { f = v } > > (I'm sure the grammar could be fully disambiguated, but this would not > improve readability. Preferring shift over reduce is common and fine for > such cases.) Upon reading this example, I believed this to be simply a matter of the layout rule. case e of p -> r { f = v } would become case e of { p -> r } { f = v } This, on the other hand case e of p -> r { f = v } would be equivalent to case e of { p -> (r { f = v }) } I just tested this after writing the preceding as I was confused about what you found confusing, and I am surprised that the example you showed does indeed yield a parse error. I very much expected this to be valid Haskell: data X = X { x :: Bool } someX = X True foo = case () of _ -> someX { x = False } Am I alone in my surprise? From allbery.b at gmail.com Wed Jul 13 17:41:11 2016 From: allbery.b at gmail.com (Brandon Allbery) Date: Wed, 13 Jul 2016 13:41:11 -0400 Subject: ArgumentDo proposal updated In-Reply-To: References: <5dd9d25118f7462fbb043ce94b87b873@DB4PR30MB030.064d.mgd.msft.net> <57860CF1.7030006@web.de> Message-ID: On Wed, Jul 13, 2016 at 1:35 PM, Manuel Gómez wrote: > foo = > case () of > _ -> someX > { x = False } > > Am I alone in my surprise? > My own expectation would be that the outdent to the level of "case" terminated the "case", and that is indeed a syntax error. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From iavor.diatchki at gmail.com Wed Jul 13 18:51:37 2016 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Wed, 13 Jul 2016 11:51:37 -0700 Subject: ArgumentDo proposal updated In-Reply-To: References: <5dd9d25118f7462fbb043ce94b87b873@DB4PR30MB030.064d.mgd.msft.net> <57860CF1.7030006@web.de> Message-ID: Hello Manuel, this is exactly the change that is being discussed: currently a `case` expression is not considered to be atomic (`aexp`), which is why it can't appear in a record update without parens. The proposed change, as I understand it, is to make `case` (and `do`) into atomic expressions as they are "parentesized" by the key-word (`case` or `do`) at the start, and the closing `}` at the end. Making this change would allow the kind of thing you were expecting, which to me makes sense. Others seem to find it confusing :-) -Iavor On Wed, Jul 13, 2016 at 10:35 AM, Manuel Gómez wrote: > On Wed, Jul 13, 2016 at 5:42 AM, C Maeder wrote: > > seeing > > > > aexp -> qvar (variable) > > | gcon (general constructor) > > ... > > | qcon { fbind1 … fbindn } (labeled construction) > > | aexp { fbind1 … fbindn } (labelled update) > > > > and > > > https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-220003 > > > > I realise that the update requires at least one field binding whereas > > for a construction "C {}" (n = 0) could be used. ("C {}" makes sense > > for patterns!) > > > > And due to the meta-rule a labelled update is not possible for a lambda > > abstraction, let expression, or conditional (as aexp), but it is for > > case (and do if the record type happens to be a monad). So a further > > less obvious example is: > > > > case e of > > p -> r > > { f = v } > > > > that will be parsed as: (case e of p -> r) { f = v } > > > > (I'm sure the grammar could be fully disambiguated, but this would not > > improve readability. Preferring shift over reduce is common and fine for > > such cases.) > > Upon reading this example, I believed this to be simply a matter of > the layout rule. > > case e of > p -> r > { f = v } > > would become > > case e of { > p -> r > } { f = v } > > This, on the other hand > > case e of p -> r { f = v } > > would be equivalent to > > case e of { p -> (r { f = v }) } > > I just tested this after writing the preceding as I was confused about > what you found confusing, and I am surprised that the example you > showed does indeed yield a parse error. I very much expected this to > be valid Haskell: > > data X = X { x :: Bool } > someX = X True > > foo = > case () of > _ -> someX > { x = False } > > Am I alone in my surprise? > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at well-typed.com Wed Jul 20 09:36:55 2016 From: ben at well-typed.com (Ben Gamari) Date: Wed, 20 Jul 2016 11:36:55 +0200 Subject: Proposal process status Message-ID: <87mvlc1wi0.fsf@smart-cactus.org> Hello everyone, As you hopefully know, a few weeks ago we proposed a new process [1] for collecting, discussing, and deciding upon changes to GHC and its Haskell superset. While we have been happy to see a small contingent of contributors join the discussion, the number is significantly smaller than the set who took part in the earlier Reddit discussions. In light of this, we are left a bit uncertain of how to proceed. So, we would like to ask you to let us know your feelings regarding the proposed process: * Do you feel the proposed process is an improvement over the status quo? * Why? (this needn't be long, just a sentence hitting the major points) * What would you like to see changed in the proposed process, if anything? That's all. Again, feel free to reply either on the GitHub pull request [1] or this thread if you would prefer. Your response needn't be long; we just want to get a sense of how much of the community feels that 1) this effort is worth undertaking, and 2) that the proposal before us is in fact an improvement over the current state of affairs. Thanks for your help! Cheers, - Ben [1] https://github.com/ghc-proposals/ghc-proposals/pull/1 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From thomasmiedema at gmail.com Wed Jul 20 10:45:28 2016 From: thomasmiedema at gmail.com (Thomas Miedema) Date: Wed, 20 Jul 2016 12:45:28 +0200 Subject: Proposal process status In-Reply-To: <87mvlc1wi0.fsf@smart-cactus.org> References: <87mvlc1wi0.fsf@smart-cactus.org> Message-ID: > > * What would you like to see changed in the proposed process, if > anything? > *Simon Peyton Jones as Benevolent Dictator For Life (BDFL)* If the BDFL had made a simple YES/NO decision on ShortImports [1] and ArgumentDo [2], we wouldn't be here talking about process proposals, Anthony wouldn't be mad, everything would be fine. We don't need another Haskell committee. * Keep using Trac for proposals, but use the description field of a ticket for the specification, instead of separate wiki page. * Add better filtering possibilities to Trac (say someone wants to only subscribe to tickets where syntax extensions are discussed). Adding better filtering possibilities will also benefit bug fixers (say someone wants to only subscribe to bugs on Windows or with keyword=PatternSynonyms). * Don't let hotly debated feature requests go without a resolution. [0] https://en.wikipedia.org/wiki/Benevolent_dictator_for_life [1] https://ghc.haskell.org/trac/ghc/ticket/10478 [2] https://ghc.haskell.org/trac/ghc/ticket/10843 -------------- next part -------------- An HTML attachment was scrubbed... URL: From shumovichy at gmail.com Wed Jul 20 11:42:31 2016 From: shumovichy at gmail.com (Yuras Shumovich) Date: Wed, 20 Jul 2016 14:42:31 +0300 Subject: Proposal process status In-Reply-To: <87mvlc1wi0.fsf@smart-cactus.org> References: <87mvlc1wi0.fsf@smart-cactus.org> Message-ID: <1469014951.4633.2.camel@gmail.com> Looks like reddit is a wrong place, so I'm replicating my comment here: On Wed, 2016-07-20 at 11:36 +0200, Ben Gamari wrote: > Hello everyone, > > As you hopefully know, a few weeks ago we proposed a new process [1] > for > collecting, discussing, and deciding upon changes to GHC and its > Haskell > superset. While we have been happy to see a small contingent of > contributors join the discussion, the number is significantly smaller > than the set who took part in the earlier Reddit discussions. > > In light of this, we are left a bit uncertain of how to proceed. So, > we would like to ask you to let us know your feelings regarding the > proposed process: > >   * Do you feel the proposed process is an improvement over the > status >     quo? Yes, definitely. The existing process is too vague, so formalizing it is a win in any case. > >   * Why? (this needn't be long, just a sentence hitting the major > points) > >   * What would you like to see changed in the proposed process, if >     anything? The proposed process overlaps with the Language Committee powers. In theory the Committee works on language standard, but de facto Haskell is GHC/Haskell and GHC/Haskell is Haskell. Adding new extension to GHC adds new extension to Haskell. So I'd like the process to enforce separation between experimental extensions (not recommended in production code) and language improvements. I'd like the process to specify how the GHC Committee is going to communicate and share powers with the Language Committee. Thanks, Yuras. > > That's all. Again, feel free to reply either on the GitHub pull > request > [1] or this thread if you would prefer. Your response needn't be > long; > we just want to get a sense of how much of the community feels that > 1) > this effort is worth undertaking, and 2) that the proposal before us > is > in fact an improvement over the current state of affairs. > > Thanks for your help! > > Cheers, > > - Ben > > > [1] https://github.com/ghc-proposals/ghc-proposals/pull/1 > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-user > s From iavor.diatchki at gmail.com Wed Jul 20 16:25:49 2016 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Wed, 20 Jul 2016 09:25:49 -0700 Subject: Proposal process status In-Reply-To: <87mvlc1wi0.fsf@smart-cactus.org> References: <87mvlc1wi0.fsf@smart-cactus.org> Message-ID: Hello Ben, I posted this when you originally asked for feed-back, but perhaps it got buried among the rest of the e-mails. I think the proposal sounds fairly reasonable, but it is hard to say how well it will work in practice until we try it, and we should be ready to change it if needs be. Some clarifying questions on the intended process: 1. After submitting the initial merge request, is the person making the proposal to wait for any kind of acknowledgment, or just move on to step 2? 2. Is the discussion going to happen on one of the mailing lists, if so which? Is it the job of the proposing person to involve/notify the committee about the discussion? If so, how are they to find out who is on the committee? 3. How does one actually perform step 3, another pull request or simply an e-mail to someone? Typo: two separate bullets in the proposal are labelled as 4. Cheers, -Iavor On Wed, Jul 20, 2016 at 2:36 AM, Ben Gamari wrote: > > Hello everyone, > > As you hopefully know, a few weeks ago we proposed a new process [1] for > collecting, discussing, and deciding upon changes to GHC and its Haskell > superset. While we have been happy to see a small contingent of > contributors join the discussion, the number is significantly smaller > than the set who took part in the earlier Reddit discussions. > > In light of this, we are left a bit uncertain of how to proceed. So, > we would like to ask you to let us know your feelings regarding the > proposed process: > > * Do you feel the proposed process is an improvement over the status > quo? > > * Why? (this needn't be long, just a sentence hitting the major points) > > * What would you like to see changed in the proposed process, if > anything? > > That's all. Again, feel free to reply either on the GitHub pull request > [1] or this thread if you would prefer. Your response needn't be long; > we just want to get a sense of how much of the community feels that 1) > this effort is worth undertaking, and 2) that the proposal before us is > in fact an improvement over the current state of affairs. > > Thanks for your help! > > Cheers, > > - Ben > > > [1] https://github.com/ghc-proposals/ghc-proposals/pull/1 > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ben at well-typed.com Wed Jul 20 16:37:38 2016 From: ben at well-typed.com (Ben Gamari) Date: Wed, 20 Jul 2016 18:37:38 +0200 Subject: Proposal process status In-Reply-To: <1469014951.4633.2.camel@gmail.com> References: <87mvlc1wi0.fsf@smart-cactus.org> <1469014951.4633.2.camel@gmail.com> Message-ID: <874m7k1d0t.fsf@smart-cactus.org> Yuras Shumovich writes: > Looks like reddit is a wrong place, so I'm replicating my comment here: > Thanks for your comments Yuras! >>   * Do you feel the proposed process is an improvement over the >> status quo? > > Yes, definitely. The existing process is too vague, so formalizing it > is a win in any case. > Good to hear. >>   * What would you like to see changed in the proposed process, if >>     anything? > > The proposed process overlaps with the Language Committee powers. In > theory the Committee works on language standard, but de facto Haskell > is GHC/Haskell and GHC/Haskell is Haskell. Adding new extension to GHC > adds new extension to Haskell. So I'd like the process to enforce > separation between experimental extensions (not recommended in > production code) and language improvements. I'd like the process to > specify how the GHC Committee is going to communicate and share powers > with the Language Committee. > To clarify I think Language Committee here refers to the Haskell Prime committee, right? I think these two bodies really do serve different purposes. Historically the Haskell Prime committee has been quite conservative in the sorts of changes that they standardized; as far as I know almost all of them come from a compiler. I would imagine that the GHC Committee would be a gate-keeper for proposals entering GHC and only some time later, when the semantics and utility of the extension are well-understood, would the Haskell Prime committee consider introducing it to the Report. As far as I understand it, this is historically how things have worked in the past, and I don't think this new process would change that. Of course, let me know if I'm off-base here. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From ben at well-typed.com Wed Jul 20 16:45:05 2016 From: ben at well-typed.com (Ben Gamari) Date: Wed, 20 Jul 2016 18:45:05 +0200 Subject: Proposal process status In-Reply-To: References: <87mvlc1wi0.fsf@smart-cactus.org> Message-ID: <871t2o1coe.fsf@smart-cactus.org> Iavor Diatchki writes: > Hello Ben, > > I posted this when you originally asked for feed-back, but perhaps it > got buried among the rest of the e-mails. > Indeed it seems that way. Sorry about that! > I think the proposal sounds fairly reasonable, but it is hard to say how > well it will work in practice until we try it, and we should be ready to > change it if needs be. > Right. I fully expect that we will have to iterate on it. > Some clarifying questions on the intended process: > 1. After submitting the initial merge request, is the person making the > proposal to wait for any kind of acknowledgment, or just move on to step 2? > The discussion phase can happen asynchronously from any action by the Committee. Of course, the Committee should engauge in discussion early, but I don't think any sort of acknowledgement is needed. An open pull request should be taken to mean "let's discuss this idea." > 2. Is the discussion going to happen on one of the mailing lists, if so > which? Is it the job of the proposing person to involve/notify the > committee about the discussion? If so, how are they to find out who is on > the committee? The proposed process places the discussion in a pull request. The idea here is to use well-understood and widely-used code review tools to faciliate the conversation. The Committee members will be notified of the open pull request by the usual event notification mechanism (e.g. in GitHub one can subscribe to a repository). > 3. How does one actually perform step 3, another pull request or simply > an e-mail to someone? > The opening of the pull request would mark the beginning of the discussion period. When the author feels that the discussion has come to something of a conclusion, they will request that the GHC Committee consider the proposal for acceptable by leaving a comment on the pull request. > Typo: two separate bullets in the proposal are labelled as 4. > I believe this should be fixed now. Thanks! Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From alexander at plaimi.net Wed Jul 20 16:47:54 2016 From: alexander at plaimi.net (Alexander Berntsen) Date: Wed, 20 Jul 2016 18:47:54 +0200 Subject: Proposal process status In-Reply-To: <87mvlc1wi0.fsf@smart-cactus.org> References: <87mvlc1wi0.fsf@smart-cactus.org> Message-ID: <578FAB3A.1070800@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512 On 20/07/16 11:36, Ben Gamari wrote: > * What would you like to see changed in the proposed process, if > anything? No GitHub. In order to fully utilise GitHub, one needs to run proprietary programs. Additionally, GitHub is proprietary software server-side. While I don't feel too strongly about which of the proposed alternatives are chosen, since they are both free software, augmenting Phabricator would probably be the best choice, since this avoids adding another piece of infrastructure to use and administer. - -- Alexander alexander at plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2 iQIcBAEBCgAGBQJXj6s4AAoJENQqWdRUGk8BI9oP/RCV14jmpHpbJ1Cr42Nr+yam cXrjSmKGfHNDGbBRqfORBTaAGkRbXvVJAWYiaUXddl1FUmB40JWg+sDQ/a2PVp28 10QB361+FzqSir+7wkJd27GH3mki1Hmsm/wKHISDal2P40QWSRVKZh8xr1vvWzje MVL42AvBV/P9nF40bEI+axO11A7/PnkHCzQqspK/DdtwRWLZ5ny3XYI1owH/zy9m Roo2+Zw0jIxKL18l6edLoPEiunsj7B9iHwf+TglODgyBbIdqAndxuQuJinOYEz+q FooDD3Qv+qhrRAUnTXXQ+pXO7hYqXTLqeEQKekhaj8zgo2OqzY96RM7Q2OQ0xuaR mYDe99Bg9SC5fqYZX4yVSr8anw+dGqT2FDeqWg3OBg0wDH+QZ7mhlqXbdXENaFcx 0TtIEYTf7QGZioE3B21DcfQSoXoWOPvEWE7qityPLBIln/FcA/B0obtBVNooErdA c2WM7BdNnE6+nBuxMC39FhX1Tr61Ao3BtGKJJyeANcLxefrGu+6T1udM7IsKfPAC obZllRLNrTTR9xyD/8ebVpI8wstxcjmaGCFN8kA74byMwoX/fMN/Ol7N47Ee3BWE l4OqPSxAACZrwkRLoovX/PhulOxX5E/go4aio9fDZT8i5HKxocb66GmixBxALejA Vjegvti1Nfj6cAAWmNT1 =apBk -----END PGP SIGNATURE----- From rae at cs.brynmawr.edu Wed Jul 20 17:00:59 2016 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Wed, 20 Jul 2016 13:00:59 -0400 Subject: Proposal process status In-Reply-To: <578FAB3A.1070800@plaimi.net> References: <87mvlc1wi0.fsf@smart-cactus.org> <578FAB3A.1070800@plaimi.net> Message-ID: <8CA5F8E4-D376-49E1-9E06-C71E2AE9575F@cs.brynmawr.edu> > On Jul 20, 2016, at 12:47 PM, Alexander Berntsen wrote: > > On 20/07/16 11:36, Ben Gamari wrote: >> * What would you like to see changed in the proposed process, if >> anything? > No GitHub. In order to fully utilise GitHub, one needs to run > proprietary programs. Additionally, GitHub is proprietary software > server-side. While I indeed sympathize with your desire to avoid proprietary, closed software, I'd like to point out that avoiding GitHub because it's closed has a real cost: * It requires more work (a very limited resource) to maintain our own instance of whatever alternate solution we come up with. * GitHub is very current in our community. Moving away from GitHub may increase barriers to contributions. Of course, our use of GitHub would appear to increase barriers to those who avoid closed software. This fact means that we need to balance the desires of some potential contributors (who prefer to avoid closed software) with other potential contributors (who prefer to use GitHub). To be clear, I'm not trying to shoot down Alexander's point -- just trying to point out that there are shades of gray here. Also, what proprietary programs are needed to fully utilize GitHub? I just use git and ssh, both pieces of free software. Richard From ben at well-typed.com Wed Jul 20 17:04:57 2016 From: ben at well-typed.com (Ben Gamari) Date: Wed, 20 Jul 2016 19:04:57 +0200 Subject: Proposal process status In-Reply-To: <578FAB3A.1070800@plaimi.net> References: <87mvlc1wi0.fsf@smart-cactus.org> <578FAB3A.1070800@plaimi.net> Message-ID: <87vb00z1dy.fsf@smart-cactus.org> Alexander Berntsen writes: > -----BEGIN PGP SIGNED MESSAGE----- > Hash: SHA512 > > On 20/07/16 11:36, Ben Gamari wrote: >> * What would you like to see changed in the proposed process, if >> anything? > No GitHub. In order to fully utilise GitHub, one needs to run > proprietary programs. Additionally, GitHub is proprietary software > server-side. > I know, it's rather frustrating. I also have fairly strong feelings about open-source purity, but in this case I just don't see any way to improve the current situation under this constraint. I agree that Phabricator is the logical choice for self-hosting in our situation, but sadly it just doesn't have the features at the moment to make the process convenient and accessible (which is the motivation for the change in the first place). > While I don't feel too strongly about which of the proposed > alternatives are chosen, since they are both free software, augmenting > Phabricator would probably be the best choice, since this avoids > adding another piece of infrastructure to use and administer. The Phabricator developers already do a fair amount for us without charging for their time. We can ask them to add the features that we need but this will take time, if it happens at all, unless we put money on the table. Unless someone is willing to put money down I'm not sure Phabricator will be an option in the foreseeable future. It does look like Gitlab is an impressive option but really then we are back to the problem of fragmented development tools. Using Trac, Phabricator, Gitlab, and mailing lists all in one project seems a bit silly. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From alexander at plaimi.net Wed Jul 20 17:05:22 2016 From: alexander at plaimi.net (Alexander Berntsen) Date: Wed, 20 Jul 2016 19:05:22 +0200 Subject: Proposal process status In-Reply-To: <8CA5F8E4-D376-49E1-9E06-C71E2AE9575F@cs.brynmawr.edu> References: <87mvlc1wi0.fsf@smart-cactus.org> <578FAB3A.1070800@plaimi.net> <8CA5F8E4-D376-49E1-9E06-C71E2AE9575F@cs.brynmawr.edu> Message-ID: <578FAF52.6080708@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512 On 20/07/16 19:00, Richard Eisenberg wrote: > While I indeed sympathize with your desire to avoid proprietary, > closed software, I'd like to point out that avoiding GitHub > because it's closed has a real cost I don't value those points over my freedom. But those who don't value their freedom might value them, so thanks for listing them. > Also, what proprietary programs are needed to fully utilize GitHub? > I just use git and ssh, both pieces of free software. For proposals, we'll be doing lots of discussions and review. Those parts of GitHub rely heavily on proprietary client-side JavaScript. - -- Alexander alexander at plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2 iQIcBAEBCgAGBQJXj69RAAoJENQqWdRUGk8Bnv8P+wc2CV4CEifkebXniGte7oOm yJ3fB/wOhm5sgGVOOAVNiv3VfvQb8t3qsouFkYyaVJXfLMGhK1PehC3Y38mI28HU NA1FK9CVyBU3YHQmyyqegJGyjj+DEVrN/rmydgU3xCPCRflB/gvMdv0PMUhlIj8v 2tTjXguElLxAncnsU4YIVWcmvN+Wssikv8H/FWksJTsuZdFXkC1VzLbGJHGc0plt s8v6OWWFxXqv3ujFy1e4yTv+VoBeKEbEVPhsxGvU7q4IkrVGLUOEnR0LPV3+H+Um 1XWez8VIBMIobnDE/0ZR++6AXc08iOhTR1Cgd+6YW0SGDP54HqG/Oj1Hop7kdAy6 7j62Csr8DAjUOfJyWng+vmIOd66g/Cu3OxQlmtiznjnStDQKmPpLTe3srYWC2w0T iIR8sKqmFb4QnohDH6bG4JPCtwVIM2RXg8xzcfbHMihqa1DZqS8DCrtx80Ga5UHP Ln0/j6ig5erQFJU7XM5CvnUDIMu0wQp8bP4VbTqRM4dvFVoBxOk8D9vZFh2LlSNM /sYkD0oRHeFFoXRiL5XuTLufntA/BR+n/fFGoHL2ZtLEWk+Phe70PvLT/vqXJtZk AtwlNXCr1uD/4rhCxdNAoVuV8o+8F+Iq0l4kFGqtH8hZdRN9+HpISWO3HgaeyIVD tJbo1M5Eo3+Ky7o25uiQ =cPxT -----END PGP SIGNATURE----- From alexander at plaimi.net Wed Jul 20 17:07:59 2016 From: alexander at plaimi.net (Alexander Berntsen) Date: Wed, 20 Jul 2016 19:07:59 +0200 Subject: Proposal process status In-Reply-To: <87vb00z1dy.fsf@smart-cactus.org> References: <87mvlc1wi0.fsf@smart-cactus.org> <578FAB3A.1070800@plaimi.net> <87vb00z1dy.fsf@smart-cactus.org> Message-ID: <578FAFEF.30101@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512 On 20/07/16 19:04, Ben Gamari wrote: > I know, it's rather frustrating. I also have fairly strong feelings > about open-source purity, but in this case I just don't see any > way to improve the current situation under this constraint. I don't think that starting to rely on proprietary software *is* an improvement, but the opposite. > It does look like Gitlab is an impressive option but really then > we are back to the problem of fragmented development tools. Using > Trac, Phabricator, Gitlab, and mailing lists all in one project > seems a bit silly. I don't understand why using GitLab is more silly than using GitHub, when considering fragmentation. - -- Alexander alexander at plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2 iQIcBAEBCgAGBQJXj6/uAAoJENQqWdRUGk8Bk4UP/RsWT2YjFTxFR0mPxx0gQgFd jq9lp8DlJsZJ33I7OF4kuFLxjbMoybRDRbr9rDSWXVhor25mxogXa+5VU6/PXj5I IKsh495k8BZDDajlUuPPvC0jymHtJI2urVWls9Da/uVOu/xeuutK+fvuosLsuPAh 0AaoncvDV9LaGDYxOEGIQa5ucEiDwE5k+PbPyxH9lCWXH8ULKGG+tPIh+0/wCCbx pxoQhire9LLWUXtkMQ654mgurQ76BD97b4Hab42ommtwNwFnxS4Oqw/Q7n2dzmdc WSiHu6S8twcWgqiJNr+OVcNuXcRHmFHYnS0VvI9tTYvvE5cZAenjJrXE1ncyoZkh yTPulCx18GxNafzEsGxw7LYSmMIb2/QKWEkRDh7kkP+fOFvXPTl7QhUjz5RGJ90s RgbDD9M17fRJ96yGwogFSzSVZP1KTiYCOMnqk8KjDQgwXOqQFCDKUS1dawpeARCi M6zJsVkuVjJCsb/lKzlq71w1yJuOMS6gO92SajqRFfJ+j8q+GTP6/DnY+vUDvoxq klNAhqQGJKLgvy47fS6MN9hv8K4yj4NmDY8vSruOOJ1RBlruNiUoEXFKSfRZVwpk FjEZYar7/rdOIVsI5W7Tt4Qip3LGnpqzdHH3lehxWaDtWgwrV0hnMToVapOsm0Rs n2OTI95HXi21nm7jYV+X =I8EH -----END PGP SIGNATURE----- From amindfv at gmail.com Wed Jul 20 17:38:41 2016 From: amindfv at gmail.com (amindfv at gmail.com) Date: Wed, 20 Jul 2016 13:38:41 -0400 Subject: Proposal process status In-Reply-To: <871t2o1coe.fsf@smart-cactus.org> References: <87mvlc1wi0.fsf@smart-cactus.org> <871t2o1coe.fsf@smart-cactus.org> Message-ID: > El 20 jul 2016, a las 12:45, Ben Gamari escribió: > > Iavor Diatchki writes: > >> Hello Ben, >> >> I posted this when you originally asked for feed-back, but perhaps it >> got buried among the rest of the e-mails. > Indeed it seems that way. Sorry about that! > >> I think the proposal sounds fairly reasonable, but it is hard to say how >> well it will work in practice until we try it, and we should be ready to >> change it if needs be. > Right. I fully expect that we will have to iterate on it. > >> Some clarifying questions on the intended process: >> 1. After submitting the initial merge request, is the person making the >> proposal to wait for any kind of acknowledgment, or just move on to step 2? > The discussion phase can happen asynchronously from any action by the > Committee. Of course, the Committee should engauge in discussion early, > but I don't think any sort of acknowledgement is needed. An open pull > request should be taken to mean "let's discuss this idea." > >> 2. Is the discussion going to happen on one of the mailing lists, if so >> which? Is it the job of the proposing person to involve/notify the >> committee about the discussion? If so, how are they to find out who is on >> the committee? > > The proposed process places the discussion in a pull request. The idea > here is to use well-understood and widely-used code review tools to > faciliate the conversation. This part runs strongly against the grain of what I'd prefer: email is lightweight, decentralized, standard, and has many clients. We can read discussion of Haskell proposals any way we like. Github on the other hand only allows us to read issues by going to Github, and using whatever interface Github has given us (which personally I find very annoying, esp. on mobile). In addition, reading proposals offline becomes very difficult. Many of us read discussion when commuting, where, e.g. in NYC, there isn't cell service. For reviewing code that implements a proposal, I'm a lot more flexible (although again I'm not a fan of Github) For the people who like having history tracked with git: gitit is a possibility, and is written in Haskell. Tom > The Committee members will be notified of the open pull request by the > usual event notification mechanism (e.g. in GitHub one can subscribe to > a repository). > >> 3. How does one actually perform step 3, another pull request or simply >> an e-mail to someone? > The opening of the pull request would mark the beginning of the > discussion period. When the author feels that the discussion has come to > something of a conclusion, they will request that the GHC Committee > consider the proposal for acceptable by leaving a comment on the pull > request. > >> Typo: two separate bullets in the proposal are labelled as 4. > I believe this should be fixed now. Thanks! > > Cheers, > > - Ben > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users From metaniklas at gmail.com Wed Jul 20 19:39:22 2016 From: metaniklas at gmail.com (Niklas Larsson) Date: Wed, 20 Jul 2016 21:39:22 +0200 Subject: Proposal process status In-Reply-To: References: <87mvlc1wi0.fsf@smart-cactus.org> <871t2o1coe.fsf@smart-cactus.org> Message-ID: <6E758950-7FD9-4243-9F9E-75358DAF131E@gmail.com> > 20 juli 2016 kl. 19:38 skrev amindfv at gmail.com: > > > >> El 20 jul 2016, a las 12:45, Ben Gamari escribió: >> >> Iavor Diatchki writes: >> >>> Hello Ben, >>> >>> I posted this when you originally asked for feed-back, but perhaps it >>> got buried among the rest of the e-mails. >> Indeed it seems that way. Sorry about that! >> >>> I think the proposal sounds fairly reasonable, but it is hard to say how >>> well it will work in practice until we try it, and we should be ready to >>> change it if needs be. >> Right. I fully expect that we will have to iterate on it. >> >>> Some clarifying questions on the intended process: >>> 1. After submitting the initial merge request, is the person making the >>> proposal to wait for any kind of acknowledgment, or just move on to step 2? >> The discussion phase can happen asynchronously from any action by the >> Committee. Of course, the Committee should engauge in discussion early, >> but I don't think any sort of acknowledgement is needed. An open pull >> request should be taken to mean "let's discuss this idea." >> >>> 2. Is the discussion going to happen on one of the mailing lists, if so >>> which? Is it the job of the proposing person to involve/notify the >>> committee about the discussion? If so, how are they to find out who is on >>> the committee? >> >> The proposed process places the discussion in a pull request. The idea >> here is to use well-understood and widely-used code review tools to >> faciliate the conversation. > > This part runs strongly against the grain of what I'd prefer: email is lightweight, decentralized, standard, and has many clients. We can read discussion of Haskell proposals any way we like. Github on the other hand only allows us to read issues by going to Github, and using whatever interface Github has given us (which personally I find very annoying, esp. on mobile). In addition, reading proposals offline becomes very difficult. Many of us read discussion when commuting, where, e.g. in NYC, there isn't cell service. > > For reviewing code that implements a proposal, I'm a lot more flexible (although again I'm not a fan of Github) > > For the people who like having history tracked with git: gitit is a possibility, and is written in Haskell. > > Tom > It's possible both follow and contribute to issues in a github repo via email. I do it all the time for Idris. // Niklas > > >> The Committee members will be notified of the open pull request by the >> usual event notification mechanism (e.g. in GitHub one can subscribe to >> a repository). >> >>> 3. How does one actually perform step 3, another pull request or simply >>> an e-mail to someone? >> The opening of the pull request would mark the beginning of the >> discussion period. When the author feels that the discussion has come to >> something of a conclusion, they will request that the GHC Committee >> consider the proposal for acceptable by leaving a comment on the pull >> request. >> >>> Typo: two separate bullets in the proposal are labelled as 4. >> I believe this should be fixed now. Thanks! >> >> Cheers, >> >> - Ben >> >> _______________________________________________ >> Glasgow-haskell-users mailing list >> Glasgow-haskell-users at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users From ben at well-typed.com Wed Jul 20 19:56:45 2016 From: ben at well-typed.com (Ben Gamari) Date: Wed, 20 Jul 2016 21:56:45 +0200 Subject: Proposal process status In-Reply-To: <578FAFEF.30101@plaimi.net> References: <87mvlc1wi0.fsf@smart-cactus.org> <578FAB3A.1070800@plaimi.net> <87vb00z1dy.fsf@smart-cactus.org> <578FAFEF.30101@plaimi.net> Message-ID: <8760s0ytfm.fsf@smart-cactus.org> Alexander Berntsen writes: > On 20/07/16 19:04, Ben Gamari wrote: >> I know, it's rather frustrating. I also have fairly strong feelings >> about open-source purity, but in this case I just don't see any >> way to improve the current situation under this constraint. > > I don't think that starting to rely on proprietary software *is* an > improvement, but the opposite. > This is a bit of a judgement call. I know this is a long-contested issue, but personally for me it puts me at ease if, * the proprietary code is running on someone else's machine * I can use the application with open tools (a web browser of your choice, git, and an email client) * I can get my data out if needed >> It does look like Gitlab is an impressive option but really then >> we are back to the problem of fragmented development tools. Using >> Trac, Phabricator, Gitlab, and mailing lists all in one project >> seems a bit silly. > > I don't understand why using GitLab is more silly than using GitHub, > when considering fragmentation. When put this way my argument does indeed sound a bit silly. :-) Perhaps it's not. I think the difference is that we would be consolidating on a platform which much of the Haskell community already uses in their non-GHC development. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From acfoltzer at gmail.com Wed Jul 20 21:16:27 2016 From: acfoltzer at gmail.com (Adam Foltzer) Date: Wed, 20 Jul 2016 14:16:27 -0700 Subject: Proposal process status In-Reply-To: <8760s0ytfm.fsf@smart-cactus.org> References: <87mvlc1wi0.fsf@smart-cactus.org> <578FAB3A.1070800@plaimi.net> <87vb00z1dy.fsf@smart-cactus.org> <578FAFEF.30101@plaimi.net> <8760s0ytfm.fsf@smart-cactus.org> Message-ID: I really appreciate you putting so much work into this. It is very important, and I believe could do much to increase awareness of and participation in these processes. I've left most of my thoughts as line comments on the proposal document, but since discussion of platform choice is taking place here, I'll quote the Motivations section: 1. Higher than necessary barrier-to-entry. For the purposes of this proposal, whether we would prefer a competing alternative is secondary to the fact that a Github account has become a very low common denominator for people wishing to participate in the development of open source projects. If we decide to proceed with a non-Github platform, we need to make a compelling case that the alternate choice does not raise the barrier to entry, or else we need to decide that we have different priorities for this effort. Thanks, Adam On Wed, Jul 20, 2016 at 12:56 PM, Ben Gamari wrote: > Alexander Berntsen writes: > > > On 20/07/16 19:04, Ben Gamari wrote: > >> I know, it's rather frustrating. I also have fairly strong feelings > >> about open-source purity, but in this case I just don't see any > >> way to improve the current situation under this constraint. > > > > I don't think that starting to rely on proprietary software *is* an > > improvement, but the opposite. > > > This is a bit of a judgement call. I know this is a long-contested > issue, but personally for me it puts me at ease if, > > * the proprietary code is running on someone else's machine > > * I can use the application with open tools (a web browser of your > choice, git, and an email client) > > * I can get my data out if needed > > > >> It does look like Gitlab is an impressive option but really then > >> we are back to the problem of fragmented development tools. Using > >> Trac, Phabricator, Gitlab, and mailing lists all in one project > >> seems a bit silly. > > > > I don't understand why using GitLab is more silly than using GitHub, > > when considering fragmentation. > > When put this way my argument does indeed sound a bit silly. :-) > > Perhaps it's not. I think the difference is that we would > be consolidating on a platform which much of the Haskell community > already uses in their non-GHC development. > > Cheers, > > - Ben > > _______________________________________________ > Glasgow-haskell-users mailing list > Glasgow-haskell-users at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jackhill at jackhill.us Wed Jul 20 21:41:39 2016 From: jackhill at jackhill.us (Jack Hill) Date: Wed, 20 Jul 2016 17:41:39 -0400 (EDT) Subject: Proposal process status In-Reply-To: References: <87mvlc1wi0.fsf@smart-cactus.org> <578FAB3A.1070800@plaimi.net> <87vb00z1dy.fsf@smart-cactus.org> <578FAFEF.30101@plaimi.net> <8760s0ytfm.fsf@smart-cactus.org> Message-ID: On Wed, 20 Jul 2016, Adam Foltzer wrote: > 1. Higher than necessary barrier-to-entry. > For the purposes of this proposal, whether we would prefer a competing alternative is secondary to the fact that a Github account has become a very low > common denominator for people wishing to participate in the development of open source projects. If we decide to proceed with a non-Github platform, we > need to make a compelling case that the alternate choice does not raise the barrier to entry, or else we need to decide that we have different priorities > for this effort. Hi all, I'm a bit of an outsider here as I'm not involved in GHC development (but I am interested in how it goes). I've struggled with my own desire to avoid using proprietary software like GitHub, and the desire to work with those who favor it, so I am interested in how these competing desires can be addressed. Would the barrier to entry to a non-GitHub system be reduced by using GitHub for user authentication/accounts (like http://exercism.io/ ), or is knowing how to use other software too much of a barrier (I guess that would depend on the software…)? Thanks, Jack From alexander at plaimi.net Wed Jul 20 21:43:23 2016 From: alexander at plaimi.net (Alexander Berntsen) Date: Wed, 20 Jul 2016 23:43:23 +0200 Subject: Proposal process status In-Reply-To: References: <87mvlc1wi0.fsf@smart-cactus.org> <578FAB3A.1070800@plaimi.net> <87vb00z1dy.fsf@smart-cactus.org> <578FAFEF.30101@plaimi.net> <8760s0ytfm.fsf@smart-cactus.org> Message-ID: <578FF07B.9070907@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512 On 20/07/16 23:41, Jack Hill wrote: > Would the barrier to entry to a non-GitHub system be reduced by > using GitHub for user authentication/accounts For what it's worth, GitLab supports this[0]. You can also use Twitter, or whatever. [0] - -- Alexander alexander at plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2 iQIcBAEBCgAGBQJXj/B7AAoJENQqWdRUGk8BJZcQAJQc/v7UWFdFEVVHlE9Mp/PR ddlT5ngNJEagxzv5vZpEAk3oVTq2jyMaHP/KM+RGwR8l025jdP/groZ73g2X1qTn EMLg+orKO5SGMeHK0jdypBQCMEhwNI3kDvh/Nu3ZOdM2yBWHbHHkW/3CD6T4n+zo UpSDfmlkpOXfOtssqngjlnYJ0/roldrJGY1RCGmtrljFmvWTlmBBTTA/HqxB1mQy doA9uJnwI8Cr7MTpoV7W8yOzv8IkfiOgO7Q3kUv8rrRtij7uN4wqM0+/eyFEmapO BGMWM5RixmffjIyKILFUr0WkgYk8WtgXfqA8+kcYYeKQB+er7Jppbzw+IeSdyJ0g UyM7140uBtLAqHUCpvXx8Yp36qRmEtf5Bqscz9+4oQoAWLeYAvHWaIcifj1fqtUd HQuMdES0Pm1PcXPBu1WNd31QUeb0UsM7N1STvgAv/Iwi2SH/OFk4JyPgjSrtPDc+ KoD5LunsWBotipZr1reia7pW0mjhwPf8e6rI7FOhZjNFyNesoQWxIDFTp3IBxSYZ oyz7bdGRP1H1MsxwBeVpPN5IzWA4EkCiWKcCb6lGFvg9lqSFfFY36HGwoHehkvo/ cSV9agY4V4ZSl0wIp3sy5eCPcUmaBR/JHCiDrhpVl+x8kRaYVbjvoS09Kty0J3nj upaF1qaI20+1Jdv0pyab =n/aA -----END PGP SIGNATURE----- From ben at smart-cactus.org Wed Jul 20 21:50:39 2016 From: ben at smart-cactus.org (Ben Gamari) Date: Wed, 20 Jul 2016 23:50:39 +0200 Subject: Proposal process status In-Reply-To: References: <87mvlc1wi0.fsf@smart-cactus.org> <578FAB3A.1070800@plaimi.net> <87vb00z1dy.fsf@smart-cactus.org> <578FAFEF.30101@plaimi.net> <8760s0ytfm.fsf@smart-cactus.org> Message-ID: <87vb00x9lc.fsf@smart-cactus.org> Jack Hill writes: > Hi all, > > I'm a bit of an outsider here as I'm not involved in GHC development (but > I am interested in how it goes). I've struggled with my own desire to > avoid using proprietary software like GitHub, and the desire to work with > those who favor it, so I am interested in how these competing desires can > be addressed. > > Would the barrier to entry to a non-GitHub system be reduced by using > GitHub for user authentication/accounts (like http://exercism.io/ ), or is > knowing how to use other software too much of a barrier (I guess that > would depend on the software…)? > To some extent. The size of the barrier posed by an alternate system isn't a discrete quantity and is highly dependent upon one's frame of reference. Many people won't wander from GitHub at all; other won't even register for a GitHub account. People vary widely in their preferences, which is what makes this problem so difficult. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 472 bytes Desc: not available URL: From carter.schonwald at gmail.com Thu Jul 21 02:13:22 2016 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 20 Jul 2016 22:13:22 -0400 Subject: Proposal process status In-Reply-To: <874m7k1d0t.fsf@smart-cactus.org> References: <87mvlc1wi0.fsf@smart-cactus.org> <1469014951.4633.2.camel@gmail.com> <874m7k1d0t.fsf@smart-cactus.org> Message-ID: On Wednesday, July 20, 2016, Ben Gamari wrote: > Yuras Shumovich > writes: > > > Looks like reddit is a wrong place, so I'm replicating my comment here: > > > Thanks for your comments Yuras! > > >> * Do you feel the proposed process is an improvement over the > >> status quo? > > > > Yes, definitely. The existing process is too vague, so formalizing it > > is a win in any case. > > > Good to hear. > > >> * What would you like to see changed in the proposed process, if > >> anything? > > > > The proposed process overlaps with the Language Committee powers. In > > theory the Committee works on language standard, but de facto Haskell > > is GHC/Haskell and GHC/Haskell is Haskell. Adding new extension to GHC > > adds new extension to Haskell. So I'd like the process to enforce > > separation between experimental extensions (not recommended in > > production code) and language improvements. I'd like the process to > > specify how the GHC Committee is going to communicate and share powers > > with the Language Committee. > > > To clarify I think Language Committee here refers to the Haskell Prime > committee, right? > > I think these two bodies really do serve different purposes. > Historically the Haskell Prime committee has been quite conservative in > the sorts of changes that they standardized; as far as I know almost all > of them come from a compiler. I would imagine that the GHC Committee > would be a gate-keeper for proposals entering GHC and only some time > later, when the semantics and utility of the extension are > well-understood, would the Haskell Prime committee consider introducing > it to the Report. As far as I understand it, this is historically how > things have worked in the past, and I don't think this new process would > change that. > > Of course, let me know if I'm off-base here. As one of the 20 members of the Haskell (Prime) 2020 committee id like to interject on this front: the preliminary discussions the committee has had thus far had a clear agreement that we shall aim to be a bit more progressive about what shall be included in the standard. The main bar will be the extent to which features or capabilities can be articulated without over specifying implementation details and can tractably have compatible but different compilers for the standard. I think some of the other prime committee members can articulate this a bit better than I, so don't hold me to this precise phrasing ;) > > Cheers, > > - Ben > -------------- next part -------------- An HTML attachment was scrubbed... URL: From svenpanne at gmail.com Thu Jul 21 08:59:24 2016 From: svenpanne at gmail.com (Sven Panne) Date: Thu, 21 Jul 2016 10:59:24 +0200 Subject: Proposal process status In-Reply-To: References: <87mvlc1wi0.fsf@smart-cactus.org> <578FAB3A.1070800@plaimi.net> <87vb00z1dy.fsf@smart-cactus.org> <578FAFEF.30101@plaimi.net> <8760s0ytfm.fsf@smart-cactus.org> Message-ID: 2016-07-20 23:16 GMT+02:00 Adam Foltzer : > [...] I'll quote the Motivations section: > > 1. Higher than necessary barrier-to-entry. > > For the purposes of this proposal, whether we would prefer a competing > alternative is secondary to the fact that a Github account has become a > very low common denominator for people wishing to participate in the > development of open source projects. If we decide to proceed with a > non-Github platform, we need to make a compelling case that the alternate > choice does not raise the barrier to entry, or else we need to decide that > we have different priorities for this effort. > +1 for that. Just to give a few numbers, just gathered from Hackage by some grep/sed/wc "technology": 6799 of the 9946 packages (i.e. 68%) use GitHub. The numbers are even higher when one considers the top 100 downloaded packages only: 92% of them use GitHub. So like it or not, the Haskell community already relies *heavily* on GitHub, and it seems that most people don't have a problem with that or consider the alternatives inferior. As Ben already said, using some proprietary SW is no real problem as long as you can get all your data out of it (in a non-proprietary format). And I don't understand the point about "proprietary client-side JavaScript" at all: Should we stop using 99% of the Internet because some server sends us some JavaScript we have no license for? And what about all those routers/switches/etc. in between which connect you to the rest of the world: They definitely run proprietary SW, and nobody cares (for a good reason). Don't get me wrong: I'm very much for Open Source, but let's not go over the top here. Let's use a tool basically everybody knows and focus on the content, not on the technology. -------------- next part -------------- An HTML attachment was scrubbed... URL: From shumovichy at gmail.com Thu Jul 21 12:51:01 2016 From: shumovichy at gmail.com (Yuras Shumovich) Date: Thu, 21 Jul 2016 15:51:01 +0300 Subject: Proposal process status In-Reply-To: <874m7k1d0t.fsf@smart-cactus.org> References: <87mvlc1wi0.fsf@smart-cactus.org> <1469014951.4633.2.camel@gmail.com> <874m7k1d0t.fsf@smart-cactus.org> Message-ID: <1469105461.4633.21.camel@gmail.com> On Wed, 2016-07-20 at 18:37 +0200, Ben Gamari wrote: > Yuras Shumovich writes: > > > Looks like reddit is a wrong place, so I'm replicating my comment > > here: > > > Thanks for your comments Yuras! > > > >   * Do you feel the proposed process is an improvement over the > > > status quo? > > > > Yes, definitely. The existing process is too vague, so formalizing > > it > > is a win in any case. > > > Good to hear. > > > >   * What would you like to see changed in the proposed process, > > > if > > >     anything? > > > > The proposed process overlaps with the Language Committee powers. > > In > > theory the Committee works on language standard, but de facto > > Haskell > > is GHC/Haskell and GHC/Haskell is Haskell. Adding new extension to > > GHC > > adds new extension to Haskell. So I'd like the process to enforce > > separation between experimental extensions (not recommended in > > production code) and language improvements. I'd like the process to > > specify how the GHC Committee is going to communicate and share > > powers > > with the Language Committee. > > > To clarify I think Language Committee here refers to the Haskell > Prime > committee, right? Yes, Herbert used "Haskell Prime 2020 committee" and "Haskell Language committee" interchangeable in the original announcement https://mail.ha skell.org/pipermail/haskell-prime/2016-April/004050.html > > I think these two bodies really do serve different purposes. > Historically the Haskell Prime committee has been quite conservative > in > the sorts of changes that they standardized; as far as I know almost > all > of them come from a compiler. I would imagine that the GHC Committee > would be a gate-keeper for proposals entering GHC and only some time > later, when the semantics and utility of the extension are > well-understood, would the Haskell Prime committee consider > introducing > it to the Report. As far as I understand it, this is historically how > things have worked in the past, and I don't think this new process > would > change that. I think it is what the process should change. It makes sense to have two committees only if we have multiple language implementations, but it is not the case. Prime committee may accept or reject e.g. GADTs, but it will change nothing because people will continue using GADTs regardless, and any feature accepted by the Prime committee will necessary be compatible with GADTs extension. The difference between standard and GHC-specific extensions is just a question of formal specification, interesting mostly for language lawyer. (But it is good to have such formal specification even for GHC- specific extensions, right?) Probably it is time to return -fglasgow-exts back to separate standard feature from experimental GHC-specific ones. > > Of course, let me know if I'm off-base here. > > Cheers, > > - Ben From alexander at plaimi.net Thu Jul 21 13:29:47 2016 From: alexander at plaimi.net (Alexander Berntsen) Date: Thu, 21 Jul 2016 15:29:47 +0200 Subject: Proposal process status In-Reply-To: References: <87mvlc1wi0.fsf@smart-cactus.org> <578FAB3A.1070800@plaimi.net> <87vb00z1dy.fsf@smart-cactus.org> <578FAFEF.30101@plaimi.net> <8760s0ytfm.fsf@smart-cactus.org> Message-ID: <5790CE4B.9000904@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA512 I'm replying to this to clarify that I object to GitHub in order to have a clear conscience, not because I think GitHub is a "bad tool". Attempting to shoot down my arguments against GitHub with arguments for convenience or it being a "a good tool", or popular, or whatever, do not work. To me, GitHub is not even an alternative to begin with. Of course, I don't expect most (or even any) devs here to agree with my position, but I wanted to elucidate it nonetheless, so that you may understand it better. On 21/07/16 10:59, Sven Panne wrote: > like it or not, the Haskell community already relies *heavily* on > GitHub, and it seems that most people don't have a problem with > that or consider the alternatives inferior. Just because other people are doing The Wrong Thing, it does not mean that you need to do it too, nor does it excuse your doing it. > And I don't understand the point about "proprietary client-side > JavaScript" at all: Should we stop using 99% of the Internet > because some server sends us some JavaScript we have no license > for? If you value your freedom: yes. It's proprietary software executed on your computer, just like any other proprietary software executed on your computer[0]. > And what about all those routers/switches/etc. in between which > connect you to the rest of the world: They definitely run > proprietary SW, and nobody cares (for a good reason). Those do not execute proprietary software on your computer, so that's not comparable. > Don't get me wrong: I'm very much for Open Source, but let's not > go over the top here. Let's use a tool basically everybody knows > and focus on the content, not on the technology. I am not in favour of open source at all, I am in favour of free software. The issue is ethical, not technological, and saying "let's not go over the top" does not make sense to me, as it is an ethical position. [0] - -- Alexander alexander at plaimi.net https://secure.plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2 iQIcBAEBCgAGBQJXkM5KAAoJENQqWdRUGk8BncsP/24efH2arxRIriK0YankfO9W D1OT1Vfh4AtMfcBDV0dutMpLWcrllUcd/pvR2cR9uJTbA6t33LfQmhv6clqsHZ97 ZLQ7CoerfLNxCUA8i+H00YSz9JKMvGMpRJhFM/VAn1oF3OMpakCB9ZjeXXf/uwAT LVYWh/HCHRULOMnnQZe2N7IrcxUwuw+/Iy0163zWkeMVlOwmVNYj/mMFNfIuZCcK 6hxUMqNQkhL7Ipm2SSGIvZONboYsFQG7dwmAQH/A1Sj6U3oV0lmKF9Nf2gjhZq6+ FEtEDjQzMrIKtMOX0mNKuYc6i6f5N+LTMfsFddJkITMWkqkwOjbAtgStv/i6wFb7 43SIoYcFMivQ980miy3VVLVdkiFlx5/1wxz1YRaM+ieA9oF2Nl0wVU/+6mLFIUaL q1cyI+o9lywTaMr8zPzr5jSm1BNthQCgwsn4zdno7VCjbzmlsKcX9X6qMPlyAIRn AnvNhe36z2gCJzz75sqJKMmAiJKIa4bYo2/a/uB2aO1LPWrVHxgUiusQ1sGr7gB5 oCIsWyLg9u5alnv/nGKzCbtnvnn2VxRnMiRtywZXN5H7HKiMpBKjBeYt+B9udrKu WFtwWQSPM5UjTbjp5tIEZEu9BlrSGPfO+rfCRrj6IWQIAchqfs8x1OADxX3z92UJ VuJe9cRAtRGtL3/CAM/K =d4lZ -----END PGP SIGNATURE----- From gershomb at gmail.com Thu Jul 21 14:32:18 2016 From: gershomb at gmail.com (Gershom B) Date: Thu, 21 Jul 2016 10:32:18 -0400 Subject: Proposal process status In-Reply-To: <1469105461.4633.21.camel@gmail.com> References: <87mvlc1wi0.fsf@smart-cactus.org> <1469014951.4633.2.camel@gmail.com> <874m7k1d0t.fsf@smart-cactus.org> <1469105461.4633.21.camel@gmail.com> Message-ID: On July 21, 2016 at 8:51:15 AM, Yuras Shumovich (shumovichy at gmail.com) wrote: > > I think it is what the process should change. It makes sense to have > two committees only if we have multiple language implementations, but > it is not the case. Prime committee may accept or reject e.g. GADTs, > but it will change nothing because people will continue using GADTs > regardless, and any feature accepted by the Prime committee will > necessary be compatible with GADTs extension. I disagree. By the stated goals of the H2020 Committee, if it is successful, then by 2020 it will still for the most part have only standardized ony a _portion_ of the extentions that now exist today. There’s always been a barrier between implementation and standard in the Haskell language, that’s precisely one of the things that _keeps_ it from having become entirely implementation-defined despite the prevelance of extensions. Having two entirely different processes here (though obviously not without communication between the individuals involved) helps maintain that. —Gershom From rae at cs.brynmawr.edu Thu Jul 21 14:40:13 2016 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Thu, 21 Jul 2016 10:40:13 -0400 Subject: Proposal process status In-Reply-To: References: <87mvlc1wi0.fsf@smart-cactus.org> <1469014951.4633.2.camel@gmail.com> <874m7k1d0t.fsf@smart-cactus.org> <1469105461.4633.21.camel@gmail.com> Message-ID: <2157B2C8-F46A-4FFC-9CFC-9CC033DF4034@cs.brynmawr.edu> > On Jul 21, 2016, at 10:32 AM, Gershom B wrote: > > On July 21, 2016 at 8:51:15 AM, Yuras Shumovich (shumovichy at gmail.com) wrote: >> >> It makes sense to have >> two committees only if we have multiple language implementations, but >> it is not the case. > I disagree. By the stated goals of the H2020 Committee, if it is successful, then by 2020 it will still for the most part have only standardized ony a _portion_ of the extentions that now exist today. +1 to Gershom's comment. From shumovichy at gmail.com Thu Jul 21 15:29:21 2016 From: shumovichy at gmail.com (Yuras Shumovich) Date: Thu, 21 Jul 2016 18:29:21 +0300 Subject: Proposal process status In-Reply-To: References: <87mvlc1wi0.fsf@smart-cactus.org> <1469014951.4633.2.camel@gmail.com> <874m7k1d0t.fsf@smart-cactus.org> <1469105461.4633.21.camel@gmail.com> Message-ID: <1469114961.4633.48.camel@gmail.com> On Thu, 2016-07-21 at 10:32 -0400, Gershom B wrote: > On July 21, 2016 at 8:51:15 AM, Yuras Shumovich (shumovichy at gmail.com > ) wrote: > > > > I think it is what the process should change. It makes sense to > > have > > two committees only if we have multiple language implementations, > > but > > it is not the case. Prime committee may accept or reject e.g. > > GADTs, > > but it will change nothing because people will continue using GADTs > > regardless, and any feature accepted by the Prime committee will > > necessary be compatible with GADTs extension. > > I disagree. By the stated goals of the H2020 Committee, if it is > successful, then by 2020 it will still for the most part have only > standardized ony a _portion_ of the extentions that now exist today. Yes, I know. But don't you see how narrow the responsibility of the H2020 Committee is? GHC Committee makes all important decisions, and H2020 just collects some of GHC extensions into a set of "standard" ones. It is useful only when "nonstandard" extensions are not widely used (e.g. marked as experimental, and are not recommended for day-to- day use). > > There’s always been a barrier between implementation and standard in > the Haskell language, that’s precisely one of the things that _keeps_ > it from having become entirely implementation-defined despite the > prevelance of extensions. Unfortunately Haskell *is* implementation-defined language. You can't compile any nontrivial package from Hackage using Haskell2010 GHC. And the same will be true for Haskell2020. We rely on GHC-specific extensions everywhere, directly or indirectly. If the goal of the Haskell Prime is to change that, then the GHC-specific extensions should not be first class citizens in the ecosystem. Otherwise there is no sense in two committees. We can continue pretending that Haskell is standard-defined language, but it will not help to change the situation.  > > Having two entirely different processes here (though obviously not > without communication between the individuals involved) helps > maintain that. > > —Gershom > > From rae at cs.brynmawr.edu Thu Jul 21 17:25:58 2016 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Thu, 21 Jul 2016 13:25:58 -0400 Subject: Proposal process status In-Reply-To: <1469114961.4633.48.camel@gmail.com> References: <87mvlc1wi0.fsf@smart-cactus.org> <1469014951.4633.2.camel@gmail.com> <874m7k1d0t.fsf@smart-cactus.org> <1469105461.4633.21.camel@gmail.com> <1469114961.4633.48.camel@gmail.com> Message-ID: > On Jul 21, 2016, at 11:29 AM, Yuras Shumovich wrote: > > Unfortunately Haskell *is* implementation-defined language. You can't > compile any nontrivial package from Hackage using Haskell2010 GHC. Sadly, I agree with this statement. And I think this is what we're trying to change. > And > the same will be true for Haskell2020. We rely on GHC-specific > extensions everywhere, directly or indirectly. If the goal of the > Haskell Prime is to change that, then the GHC-specific extensions > should not be first class citizens in the ecosystem. My hope is that Haskell2020 will allow us to differentiate between standardized extensions and implementation-defined ones. A key part of this hope is that we'll get enough extensions in the first set to allow a sizeable portion of our ecosystem to used only standardized extensions. > > We can continue pretending that Haskell is standard-defined language, > but it will not help to change the situation. But writing a new standard that encompasses prevalent usage will help to change the situation. And that's the process I'm hoping to contribute to. Richard From shumovichy at gmail.com Thu Jul 21 18:25:53 2016 From: shumovichy at gmail.com (Yuras Shumovich) Date: Thu, 21 Jul 2016 21:25:53 +0300 Subject: Proposal process status In-Reply-To: References: <87mvlc1wi0.fsf@smart-cactus.org> <1469014951.4633.2.camel@gmail.com> <874m7k1d0t.fsf@smart-cactus.org> <1469105461.4633.21.camel@gmail.com> <1469114961.4633.48.camel@gmail.com> Message-ID: <1469125553.4633.68.camel@gmail.com> On Thu, 2016-07-21 at 13:25 -0400, Richard Eisenberg wrote: > > > > On Jul 21, 2016, at 11:29 AM, Yuras Shumovich > > wrote: > > > > Unfortunately Haskell *is* implementation-defined language. You > > can't > > compile any nontrivial package from Hackage using Haskell2010 GHC. > > Sadly, I agree with this statement. And I think this is what we're > trying to change. And I'd like it to be changed too. I'm paid for writing SW in Haskell, and I want to have a standard. At the same time I'm (probably unusual) Haskell fan, so I want new cool features. Don't you see a conflict of interests? https://www.reddit.com/r/haskell/comments/4oyxo2/blog_contributing_to_ghc/d4iaz5t > > > And > > the same will be true for Haskell2020. We rely on GHC-specific > > extensions everywhere, directly or indirectly. If the goal of the > > Haskell Prime is to change that, then the GHC-specific extensions > > should not be first class citizens in the ecosystem. > > My hope is that Haskell2020 will allow us to differentiate between > standardized extensions and implementation-defined ones. A key part > of this hope is that we'll get enough extensions in the first set to > allow a sizeable portion of our ecosystem to used only standardized > extensions. It is hopeless. Haskell2020 will not include TemplateHaskell, GADTs, etc. Haskell Prime committee will never catch up if GHC will continue adding new extensions. In 2020 everybody will use pattern synonyms, overloaded record fields and TypeInType, so the standard will be as far from practice as it is now. The whole idea of language extensions, as it is right now, works against Haskell Prime. https://www.reddit.com/r/haskell/comments/46jq4i/what_is_the_eventual_fate_of_all_of_these_ghc/d05q9no I abandoned my CStructures proposal because of that. I don't want to increase entropy. https://phabricator.haskell.org/D252 > > > > We can continue pretending that Haskell is standard-defined > > language, > > but it will not help to change the situation.  > > But writing a new standard that encompasses prevalent usage will help > to change the situation. And that's the process I'm hoping to > contribute to. I see only one real way to change the situation -- standardize all widely used extensions and declare anything new as experimental unless accepted by the Haskell Prime Committee. Probably there are other ways, but we need to cleanup the mess ASAP. New extensions only contribute to the mess -- that is my point. > > Richard From rae at cs.brynmawr.edu Thu Jul 21 18:38:56 2016 From: rae at cs.brynmawr.edu (Richard Eisenberg) Date: Thu, 21 Jul 2016 14:38:56 -0400 Subject: Proposal process status In-Reply-To: <1469125553.4633.68.camel@gmail.com> References: <87mvlc1wi0.fsf@smart-cactus.org> <1469014951.4633.2.camel@gmail.com> <874m7k1d0t.fsf@smart-cactus.org> <1469105461.4633.21.camel@gmail.com> <1469114961.4633.48.camel@gmail.com> <1469125553.4633.68.camel@gmail.com> Message-ID: <2BDA9BCD-85CE-4989-9DB8-C425B5C9514D@cs.brynmawr.edu> > On Jul 21, 2016, at 2:25 PM, Yuras Shumovich wrote: > > It is hopeless. Haskell2020 will not include TemplateHaskell, GADTs, > etc. Why do you say this? I don't think this is a forgone conclusion. I'd love to see these standardized. My own 2¢ on these are that we can standardize some subset of TemplateHaskell quite easily. GADTs are harder because (to my knowledge) no one has ever written a specification of type inference for GADTs. (Note that the OutsideIn paper admits to failing at this.) Perhaps we can nail it, but perhaps not. Even so, we can perhaps standardize much of the behavior around GADTs (but with pattern matches requiring lots of type annotations) and say that an implementation is free to do better. Maybe we can do even better than this, but I doubt we'll totally ignore this issue. > Haskell Prime committee will never catch up if GHC will continue > adding new extensions. Of course not. But I believe some libraries also refrain from using new extensions for precisely the same reason -- that the new extensions have yet to fully gel. > In 2020 everybody will use pattern synonyms, > overloaded record fields and TypeInType, so the standard will be as far > from practice as it is now. Pattern synonyms, now with a published paper behind them, may actually be in good enough shape to standardize by 2020. I don't know anything about overloaded record fields. I'd be shocked if TypeInType is ready to standardize by 2020. But hopefully we'll get to it. > > The whole idea of language extensions, as it is right now, works > against Haskell Prime. I heartily disagree here. Ideas that are now standard had to have started somewhere, and I really like (in theory) the way GHC/Haskell does this. The (in theory) parenthetical is because the standardization process has been too, well, dead to be useful. Is that changing? Perhaps. I'd love to see more action on that front. I'm hoping to take on a more active role in the committee after my dissertation is out the door (2 more weeks!). > > I see only one real way to change the situation -- standardize all > widely used extensions and declare anything new as experimental unless > accepted by the Haskell Prime Committee. Agreed here. I think that's what we're trying to do. If you have a good specification for GADT type inference, that would help us. :) Richard From shumovichy at gmail.com Thu Jul 21 19:52:23 2016 From: shumovichy at gmail.com (Yuras Shumovich) Date: Thu, 21 Jul 2016 22:52:23 +0300 Subject: Proposal process status In-Reply-To: <2BDA9BCD-85CE-4989-9DB8-C425B5C9514D@cs.brynmawr.edu> References: <87mvlc1wi0.fsf@smart-cactus.org> <1469014951.4633.2.camel@gmail.com> <874m7k1d0t.fsf@smart-cactus.org> <1469105461.4633.21.camel@gmail.com> <1469114961.4633.48.camel@gmail.com> <1469125553.4633.68.camel@gmail.com> <2BDA9BCD-85CE-4989-9DB8-C425B5C9514D@cs.brynmawr.edu> Message-ID: <1469130743.4633.95.camel@gmail.com> On Thu, 2016-07-21 at 14:38 -0400, Richard Eisenberg wrote: > > > > On Jul 21, 2016, at 2:25 PM, Yuras Shumovich > > wrote: > > > > It is hopeless. Haskell2020 will not include TemplateHaskell, > > GADTs, > > etc. > > Why do you say this? I don't think this is a forgone conclusion. I'd > love to see these standardized. Because I'm a pessimist :) We even can't agree to add `text` to the standard library. > > My own 2¢ on these are that we can standardize some subset of > TemplateHaskell quite easily. GADTs are harder because (to my > knowledge) no one has ever written a specification of type inference > for GADTs. (Note that the OutsideIn paper admits to failing at this.) > Perhaps we can nail it, but perhaps not. Even so, we can perhaps > standardize much of the behavior around GADTs (but with pattern > matches requiring lots of type annotations) and say that an > implementation is free to do better. Maybe we can do even better than > this, but I doubt we'll totally ignore this issue. > > > Haskell Prime committee will never catch up if GHC will continue > > adding new extensions. > > Of course not. But I believe some libraries also refrain from using > new extensions for precisely the same reason -- that the new > extensions have yet to fully gel. And you are an optimist. We are lazy, so we'll use whatever is convenient. There are three ways to force people to refrain from using new extensions: - mature alternative compiler exists, so nobody will use your library unless it uses only the common subset of features; - the standard covers all usual needs (I don't think it will be possible in near future, and existence of this email thread proves that.) - new features are not first class citizens; e.g. `cabal check` issues an error (or warning) when you are uploading a package with immature extension used. > > > In 2020 everybody will use pattern synonyms, > > overloaded record fields and TypeInType, so the standard will be as > > far > > from practice as it is now. > > Pattern synonyms, now with a published paper behind them, may > actually be in good enough shape to standardize by 2020. I don't know > anything about overloaded record fields. I'd be shocked if TypeInType > is ready to standardize by 2020. But hopefully we'll get to it. > > > > > The whole idea of language extensions, as it is right now, works > > against Haskell Prime. > > I heartily disagree here. Ideas that are now standard had to have > started somewhere, and I really like (in theory) the way GHC/Haskell > does this. I'm not against language extensions completely. But using them should be a real pain to prevent people from using then everywhere. Ideally you should have to compile GHC manually to get a particular extension enabled :) > > The (in theory) parenthetical is because the standardization process > has been too, well, dead to be useful. Is that changing? Perhaps. I'd > love to see more action on that front. I'm hoping to take on a more > active role in the committee after my dissertation is out the door (2 > more weeks!). > > > > I see only one real way to change the situation -- standardize all > > widely used extensions and declare anything new as experimental > > unless > > accepted by the Haskell Prime Committee. > > Agreed here. Great. So I propose to split section "9. GHC Language Features" of the user manual into "Stable language extensions" and "Experimental language extensions", move all the recently added extensions into the latter one, explicitly state in the proposed process that all new extensions go to the "Experimental" subsection initially and specify when they go to the "Stable" subsection. > I think that's what we're trying to do. If you have a good > specification for GADT type inference, that would help us. :) I'd personally prefer to mark GADT and TH as experimental. The difficulties with their standardizing is a sign of immaturity. I regret about each time I used them in production code. > > Richard