[GHC] #11706: Increase precedence of statements (if-then-else, case-of, do)

#11706: Increase precedence of statements (if-then-else, case-of, do) -------------------------------------+------------------------------------- Reporter: YoYoYonnY | Owner: Type: feature | Status: new request | Priority: lowest | Milestone: ⊥ Component: Compiler | Version: (Parser) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Warning: Skip to the {{{TL; DR}}}, and maybe the {{{How it works}}} section; You don't want to read this. (I've warned you.) == The problem == We do it all the time: Writing that one dollar sign just before our expressions, just because Haskell can't parse it: {{{#!hs f x = g $ if x then {- ... -} else {- ... -} f x = g $ case x of {- ... -} f x = g $ do {- ... -} }}} However, we programmers are lazy and want to type as few characters as possible. Think about the precious characters we would save if we could write code this way: {{{#!hs f x = g if x then {- ... -} else {- ... -} f x = g case x of {- ... -} f x = g do {- ... -} }}} Wow, our productivity just shot up by a whopping 6%! However, this code looks ugly, noone would ever write this... Right? There has to be some way to catagorize this feature with others people would never use... == Pragmas to the rescue! == The {{{LANGUAGE}}} pragma! Of course! We can add a syntactic extension to enable above syntax! But how should we name it... {{{InlineStatements}}}? {{{InfixStatements}}}? {{{ParenthesizedStatements}}}? {{{IncreasedStatementPrecedence}}}? {{{StatementsWithoutParenthesis}}}? I don't know. I am [1] not the parents who might one day give birth to this feature. I am merely the one who conceptualized it. [1] (probably, unless this request remains unnoticed for another 20 years or so) == How it works == * Implicit parenthesis will be put around ''all'' statements, according to the following rules: 1. Parenthesis will be opened at the start of the statement. 2. Parenthesis will be closed at the end of the statement. The end of the statement is determined by 1. The curly brackets around the statement, or; 2. The indentation of the statement Basically, these are the rule Haskell already uses. Sorry if this is obvious, but some people seemed to get confused, so here's some examples: === (Correct) Examples === Examples are in the form: {{{#!hs implicitParenthesis -- New syntax explicitParenthesis -- Old syntax }}} Call {{{idM :: Monad m => m a -> m a}}} as {{{idM :: IO String -> IO String}}}. {{{#!hs idM do putStrLn "What's my name?" getLine idM (do { putStrLn "What's my name?"; getLine; }) }}} Create function {{{whatsMyName :: Maybe String -> String}}}. {{{#!hs whatsMyName x = id case x of Just name = "My name is " ++ name Nothing = "What's my name?" whatsMyName x = id (case x of { Just name = "My name is " ++ name; Nothing = "What's my name?"; }) }}} Another example using {{{let}}} and {{{if-then-else}}}. {{{#!hs main = putStrLn (++) "I've been tryna work it out... The square root of 69 is 8 something, right? " let eight_something = 8.306623862918075 in if sqrt 69 == eight_something then "Yeah" else "Oh na na" main = putStrLn ((++) "I've been tryna work it out... The square root of 69 is 8 something, right? " (let eight_something = 8.306623862918075 in (if sqrt 69 == eight_something then "Yeah" else "Oh na na")) }}} === Incorrect examples === {{{#!hs f do putStrLn "This won't work..." True f (do { putStrLn "This won't work..."; True; }) }}} {{{#!hs f do putStrLn "This won't work..." True -- Indented by extra space f (do { putStrLn "This won't work..."; True; }) }}} == TL; DR == What there is: {{{#!hs main = when $ do putStrLn "Parenthesis..." main = when True (do putStrLn "Parenthesis...") }}} What I want: {{{#!hs when (doBlocksNeedParenthesis) do putStrLn "This code is invalid." when (doBlocksNeedParenthesis) $ do putStrLn "This code is valid." when (doBlocksNeedParenthesis) (do putStrLn "This code is valid aswell.") when (thisIsImplemented) do putStrLn "These are all equal" when (thisIsImplemented) (do putStrLn "These are all equal") when (thisIsImplemented) $ do putStrLn "These are all equal" }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11706 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11706: Increase precedence of statements (if-then-else, case-of, do) -------------------------------------+------------------------------------- Reporter: YoYoYonnY | Owner: Type: feature request | Status: infoneeded Priority: lowest | Milestone: ⊥ Component: Compiler | Version: (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => infoneeded Comment: Thanks for writing this up. Indeed you are not the first one to propose some variant on this idea (see, e.g., #10843). Not so long ago there was a rather lengthy discussion on this matter, which I summarized in ticket:10843#comment:12. I'll admit that don't believe that too-many-dollar-signs is the greatest of our problems and am skeptical that this sort of pragma would pull its weight. That being said, I'm happy to help you work through the details of this proposal. To begin, I think we should clear up a few nits, * the definition of "statement" being used here contradicts that defined by the Report (which defines it as being a monadic action in a `do` block). The `if` and `case` constructs are merely parts of the expression grammar. * several of your examples use `=` to delimit the sides of a case branch where you likely meant `->`. * what about `let` expressions? It seems rather odd that they are excluded here. * lambdas are a bit different from the other constructs here, but still worth thinking about * how does the binding of these expressions compare with that of infix functions? For instance, what does `(+1) <$> do return 42` mean? Our grammar is already very complex; any proposal to add further complexity needs to be carefully specified. If you would like to see this feature (and think that your proposal differs significantly from that of #10843) could you start a Wiki page describing precisely how your proposed parsing scheme differs from that described in Report? Also, keep in mind that this may interact with other syntactic extensions; be sure to consider how these interactions may play out. I would guess that you want to start by looking at [[https://www.haskell.org/onlinereport/haskell2010/haskellch10.html#x17-17800010.3|layout]] section. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11706#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11706: Increase precedence of lexps (if-then-else, case-of, do, lambda and let-in) -------------------------------------+------------------------------------- Reporter: YoYoYonnY | Owner: Type: feature request | Status: infoneeded Priority: lowest | Milestone: ⊥ Component: Compiler | Version: (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by YoYoYonnY: @@ -1,2 +1,1 @@ - Warning: Skip to the {{{TL; DR}}}, and maybe the {{{How it works}}} - section; You don't want to read this. (I've warned you.) + == Intro == @@ -4,41 +3,2 @@ - == The problem == - - We do it all the time: Writing that one dollar sign just before our - expressions, just because Haskell can't parse it: - - {{{#!hs - f x = g $ if x then {- ... -} else {- ... -} - f x = g $ case x of {- ... -} - f x = g $ do {- ... -} - }}} - - However, we programmers are lazy and want to type as few characters as - possible. Think about the precious characters we would save if we could - write code this way: - - {{{#!hs - f x = g if x then {- ... -} else {- ... -} - f x = g case x of {- ... -} - f x = g do {- ... -} - }}} - - Wow, our productivity just shot up by a whopping 6%! - - However, this code looks ugly, noone would ever write this... Right? - There has to be some way to catagorize this feature with others people - would never use... - - == Pragmas to the rescue! == - - The {{{LANGUAGE}}} pragma! Of course! We can add a syntactic extension to - enable above syntax! But how should we name it... - - {{{InlineStatements}}}? {{{InfixStatements}}}? - {{{ParenthesizedStatements}}}? {{{IncreasedStatementPrecedence}}}? - {{{StatementsWithoutParenthesis}}}? - - I don't know. I am [1] not the parents who might one day give birth to - this feature. I am merely the one who conceptualized it. - - [1] (probably, unless this request remains unnoticed for another 20 years - or so) + For readability, the intro is now available [http://pastebin.com/8Fsh7pAE + here]. @@ -48,1 +8,1 @@ - * Implicit parenthesis will be put around ''all'' statements, according + * Implicit parenthesis will be put around ''all'' {{{lexps}}}, according @@ -50,5 +10,5 @@ - 1. Parenthesis will be opened at the start of the statement. - 2. Parenthesis will be closed at the end of the statement. The end of - the statement is determined by - 1. The curly brackets around the statement, or; - 2. The indentation of the statement + 1. Parenthesis will be opened at the start of the {{{lexp}}}. + 2. Parenthesis will be closed at the end of the {{{lexp}}}. The end of + the {{{lexp}}} is determined by + 1. The curly brackets around the {{{lexp}}} (If possible), or; + 2. The indentation of the {{{lexp}}} @@ -58,2 +18,5 @@ - Sorry if this is obvious, but some people seemed to get confused, so - here's some examples: + As for the Context-Free Syntax found at + https://www.haskell.org/onlinereport/haskell2010/haskellch10.html#x17-17800010.3|layout, + {{{lexp}}} would have to be moved up, dropped out of {{{infixexp}}}, and + added into {{{exp}}} (As well as a few other places in {{{aexp}}} and + {{{guard}}}) @@ -61,1 +24,1 @@ - === (Correct) Examples === + == Motivation == @@ -63,1 +26,2 @@ - Examples are in the form: + As for my personal motivation, I think that, with all the other syntactic + extensions already implemented, this feature is definitly missing. @@ -65,2 +29,4 @@ - {{{#!hs - implicitParenthesis -- New syntax + As Richard Eisenberg already pointed out (See + [https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12 in this + comment]); combining {{{lexp}}} with {{{aexp}}} would make the Haskell + syntax more consistent. @@ -68,2 +34,2 @@ - explicitParenthesis -- Old syntax - }}} + bgamari listed above argument and quite a few other pros and cons + [https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12 here]. @@ -71,2 +37,1 @@ - Call {{{idM :: Monad m => m a -> m a}}} as {{{idM :: IO String -> IO - String}}}. + A few arguments not listed there: @@ -74,4 +39,8 @@ - {{{#!hs - idM do - putStrLn "What's my name?" - getLine + * If the Haskell community ever decides to implement this feature in the + main language, we will already be prepared. + * Similairly, if this feature ever gives problems or adds new interesting + possibilities to the language, we will be prepared. + * Yet another syntactical extension means yet another thing to look out + for; + * However, this also means people will become more aware of LANGUAGE + pragmas. @@ -79,2 +48,1 @@ - idM (do { putStrLn "What's my name?"; getLine; }) - }}} + == Naming == @@ -82,1 +50,1 @@ - Create function {{{whatsMyName :: Maybe String -> String}}}. + Here follow a few suggestions for the name of this extension: @@ -84,4 +52,5 @@ - {{{#!hs - whatsMyName x = id case x of - Just name = "My name is " ++ name - Nothing = "What's my name?" + * InlineStatements + * InfixStatements + * ParenthesizedStatements + * IncreasedStatementPrecedence + * StatementsWithoutParenthesis @@ -89,3 +58,2 @@ - whatsMyName x = id (case x of { Just name = "My name is " ++ name; Nothing - = "What's my name?"; }) - }}} + Here are some more, taken from [https://mail.haskell.org/pipermail + /haskell-cafe/2015-September/121217.html over here]. @@ -93,1 +61,2 @@ - Another example using {{{let}}} and {{{if-then-else}}}. + * ArgumentBlock + * ArgumentDo @@ -95,10 +64,1 @@ - {{{#!hs - main = putStrLn - (++) - "I've been tryna work it out... The square root of 69 is 8 - something, right? " - let - eight_something = 8.306623862918075 - in if sqrt 69 == eight_something - then "Yeah" - else "Oh na na" + == Examples == @@ -106,4 +66,1 @@ - main = putStrLn ((++) "I've been tryna work it out... The square root of - 69 is 8 something, right? " (let eight_something = 8.306623862918075 in - (if sqrt 69 == eight_something then "Yeah" else "Oh na na")) - }}} + Examples can now be found [http://pastebin.com/6kLQvKs9 here]. @@ -111,1 +68,1 @@ - === Incorrect examples === + == Resources == @@ -113,40 +70,6 @@ - {{{#!hs - f do - putStrLn "This won't work..." - True - - f (do { putStrLn "This won't work..."; True; }) - }}} - - {{{#!hs - f - do - putStrLn "This won't work..." - True -- Indented by extra space - - f (do { putStrLn "This won't work..."; True; }) - }}} - - == TL; DR == - - What there is: - - {{{#!hs - - main = when $ do putStrLn "Parenthesis..." - main = when True (do putStrLn "Parenthesis...") - - }}} - - What I want: - - {{{#!hs - - when (doBlocksNeedParenthesis) do putStrLn "This code is invalid." - when (doBlocksNeedParenthesis) $ do putStrLn "This code is valid." - when (doBlocksNeedParenthesis) (do putStrLn "This code is valid aswell.") - when (thisIsImplemented) do putStrLn "These are all equal" - when (thisIsImplemented) (do putStrLn "These are all equal") - when (thisIsImplemented) $ do putStrLn "These are all equal" - - }}} + [1] Cheesy intro: http://pastebin.com/8Fsh7pAE + [2] Original examples: [http://pastebin.com/6kLQvKs9] + [3] Pros and Cons: + [https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12] + [4] ArgumentBlock proposal: [https://mail.haskell.org/pipermail/haskell- + cafe/2015-September/121217.html] New description: == Intro == For readability, the intro is now available [http://pastebin.com/8Fsh7pAE here]. == How it works == * Implicit parenthesis will be put around ''all'' {{{lexps}}}, according to the following rules: 1. Parenthesis will be opened at the start of the {{{lexp}}}. 2. Parenthesis will be closed at the end of the {{{lexp}}}. The end of the {{{lexp}}} is determined by 1. The curly brackets around the {{{lexp}}} (If possible), or; 2. The indentation of the {{{lexp}}} Basically, these are the rule Haskell already uses. As for the Context-Free Syntax found at https://www.haskell.org/onlinereport/haskell2010/haskellch10.html#x17-17800010.3|layout, {{{lexp}}} would have to be moved up, dropped out of {{{infixexp}}}, and added into {{{exp}}} (As well as a few other places in {{{aexp}}} and {{{guard}}}) == Motivation == As for my personal motivation, I think that, with all the other syntactic extensions already implemented, this feature is definitly missing. As Richard Eisenberg already pointed out (See [https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12 in this comment]); combining {{{lexp}}} with {{{aexp}}} would make the Haskell syntax more consistent. bgamari listed above argument and quite a few other pros and cons [https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12 here]. A few arguments not listed there: * If the Haskell community ever decides to implement this feature in the main language, we will already be prepared. * Similairly, if this feature ever gives problems or adds new interesting possibilities to the language, we will be prepared. * Yet another syntactical extension means yet another thing to look out for; * However, this also means people will become more aware of LANGUAGE pragmas. == Naming == Here follow a few suggestions for the name of this extension: * InlineStatements * InfixStatements * ParenthesizedStatements * IncreasedStatementPrecedence * StatementsWithoutParenthesis Here are some more, taken from [https://mail.haskell.org/pipermail /haskell-cafe/2015-September/121217.html over here]. * ArgumentBlock * ArgumentDo == Examples == Examples can now be found [http://pastebin.com/6kLQvKs9 here]. == Resources == [1] Cheesy intro: http://pastebin.com/8Fsh7pAE [2] Original examples: [http://pastebin.com/6kLQvKs9] [3] Pros and Cons: [https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12] [4] ArgumentBlock proposal: [https://mail.haskell.org/pipermail/haskell- cafe/2015-September/121217.html] -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11706#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11706: Increase precedence of lexps (if-then-else, case-of, do, lambda and let-in) -------------------------------------+------------------------------------- Reporter: YoYoYonnY | Owner: Type: feature request | Status: infoneeded Priority: lowest | Milestone: ⊥ Component: Compiler | Version: (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by YoYoYonnY): Thanks for linking that ticket, I skimmed over the list of feature requests, but could not find any other requests asking for increased {{{lexp}}} precedence or similair. I suppose I underestimated the priority of this feature request. The typos in the ticket should now be fixed. The ticket is also simplified, the old code examples have been moved to Pastebin [http://pastebin.com/6kLQvKs9 here] (As a permament paste) for readability, and the cheesy intro has been moved to a separate Pastebin too, [http://pastebin.com/8Fsh7pAE here], to save a few clicks. I'll work on making more clean and general examples. I have to say that I agree; the proposal is mostly useless, one or two characters saved won't make a big difference. However, with other similair pragmas already implemented (UnicodeSyntax, RecordWildCards and TupleSections to name a few) I think it is reasonable to implement this feature somewhere in the future, be it with low priority. I think it is fair to refer to {{{if-then-else}}}, {{{case-of}}}, {{{do}}}, {{{lambda}}} and {{{let-in}}} as {{{lexp}}}, following https://www.haskell.org/onlinereport/haskell2010/haskellch10.html#x17-17800010.3|layout, unless of course someone can think of a better term. The set of {{{lexp}}}s could of course also easily be extended with {{{lambda-case}}} and {{{mdo}}} (If this is not already the case). I have added {{{lambda}}} and {{{let-in}}} to the title, as these are part of the proposal. I've also added {{{lambda}}} to the examples, aswell as {{{lambda-case}}}, {{{mdo}}} and infix ones. I will leave the creation of a Wiki up to someone with more experience with the GHC Parser, although I might look into it myself sometime soon. As to if this ticket is diferentiatable from [https://ghc.haskell.org/trac/ghc/ticket/10843 #10843], I would say yes, this ticket is more general, however I would strongly recommend merging this ticket with [https://ghc.haskell.org/trac/ghc/ticket/10843 #10843], if that is in any way possible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11706#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11706: Increase precedence of lexps (if-then-else, case-of, do, lambda and let-in) -------------------------------------+------------------------------------- Reporter: YoYoYonnY | Owner: Type: feature request | Status: infoneeded Priority: lowest | Milestone: ⊥ Component: Compiler | Version: (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by YoYoYonnY: @@ -16,1 +16,1 @@ - Basically, these are the rule Haskell already uses. + Basically, these are the rules Haskell already uses. @@ -30,3 +30,3 @@ - [https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12 in this - comment]); combining {{{lexp}}} with {{{aexp}}} would make the Haskell - syntax more consistent. + [https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12 this comment]); + combining {{{lexp}}} with {{{aexp}}} would make the Haskell syntax more + consistent. @@ -71,0 +71,1 @@ + @@ -72,0 +73,1 @@ + @@ -74,0 +76,1 @@ + New description: == Intro == For readability, the intro is now available [http://pastebin.com/8Fsh7pAE here]. == How it works == * Implicit parenthesis will be put around ''all'' {{{lexps}}}, according to the following rules: 1. Parenthesis will be opened at the start of the {{{lexp}}}. 2. Parenthesis will be closed at the end of the {{{lexp}}}. The end of the {{{lexp}}} is determined by 1. The curly brackets around the {{{lexp}}} (If possible), or; 2. The indentation of the {{{lexp}}} Basically, these are the rules Haskell already uses. As for the Context-Free Syntax found at https://www.haskell.org/onlinereport/haskell2010/haskellch10.html#x17-17800010.3|layout, {{{lexp}}} would have to be moved up, dropped out of {{{infixexp}}}, and added into {{{exp}}} (As well as a few other places in {{{aexp}}} and {{{guard}}}) == Motivation == As for my personal motivation, I think that, with all the other syntactic extensions already implemented, this feature is definitly missing. As Richard Eisenberg already pointed out (See [https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12 this comment]); combining {{{lexp}}} with {{{aexp}}} would make the Haskell syntax more consistent. bgamari listed above argument and quite a few other pros and cons [https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12 here]. A few arguments not listed there: * If the Haskell community ever decides to implement this feature in the main language, we will already be prepared. * Similairly, if this feature ever gives problems or adds new interesting possibilities to the language, we will be prepared. * Yet another syntactical extension means yet another thing to look out for; * However, this also means people will become more aware of LANGUAGE pragmas. == Naming == Here follow a few suggestions for the name of this extension: * InlineStatements * InfixStatements * ParenthesizedStatements * IncreasedStatementPrecedence * StatementsWithoutParenthesis Here are some more, taken from [https://mail.haskell.org/pipermail /haskell-cafe/2015-September/121217.html over here]. * ArgumentBlock * ArgumentDo == Examples == Examples can now be found [http://pastebin.com/6kLQvKs9 here]. == Resources == [1] Cheesy intro: http://pastebin.com/8Fsh7pAE [2] Original examples: [http://pastebin.com/6kLQvKs9] [3] Pros and Cons: [https://ghc.haskell.org/trac/ghc/ticket/10843#comment:12] [4] ArgumentBlock proposal: [https://mail.haskell.org/pipermail/haskell- cafe/2015-September/121217.html] -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11706#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11706: Increase precedence of lexps (if-then-else, case-of, do, lambda and let-in) -------------------------------------+------------------------------------- Reporter: YoYoYonnY | Owner: (none) Type: feature request | Status: infoneeded Priority: lowest | Milestone: ⊥ Component: Compiler | Version: (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): I believe this has been implemented as the `BlockArguments` extension. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11706#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC