[GHC] #10843: Allow do blocks without dollar signs as arguments

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- I would like the following to be valid Haskell code: {{{#!hs main = when True do putStrLn "Hello!" }}} Instead of requiring a dollar sign before the "do". This would parse as {{{#!hs main = when True (do putStrLn "Hello!") }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by agibiansky): I have an experimental implementation: https://phabricator.haskell.org/D1219 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by agibiansky: Old description:
I would like the following to be valid Haskell code:
{{{#!hs main = when True do putStrLn "Hello!" }}}
Instead of requiring a dollar sign before the "do". This would parse as
{{{#!hs main = when True (do putStrLn "Hello!") }}}
New description: I would like the following to be valid Haskell code: {{{#!hs main = when True do putStrLn "Hello!" }}} Instead of requiring a dollar sign before the "do". This would parse as {{{#!hs main = when True (do putStrLn "Hello!") }}} Similarly, allow lambdas in the same way {{{#!hs main = forM values \value -> print value }}} parses as {{{#!hs main = forM values (\value -> print value) }}} One possible question: does this also do the same thing for LambdaCase? It's an option but I would say no. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Nice idea. Of course I am also annoyed by the `$`, but I sheepishly always assumed that there is a good reason for this. Is there code that is valid with and without your extension, but with different semantics? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by agibiansky: Old description:
I would like the following to be valid Haskell code:
{{{#!hs main = when True do putStrLn "Hello!" }}}
Instead of requiring a dollar sign before the "do". This would parse as
{{{#!hs main = when True (do putStrLn "Hello!") }}}
Similarly, allow lambdas in the same way {{{#!hs main = forM values \value -> print value }}}
parses as
{{{#!hs main = forM values (\value -> print value) }}}
One possible question: does this also do the same thing for LambdaCase? It's an option but I would say no.
New description: I would like the following to be valid Haskell code: {{{#!hs main = when True do putStrLn "Hello!" }}} Instead of requiring a dollar sign before the "do". This would parse as {{{#!hs main = when True (do putStrLn "Hello!") }}} Similarly, allow lambdas in the same way {{{#!hs main = forM values \value -> print value }}} parses as {{{#!hs main = forM values (\value -> print value) }}} One possible question: does this also do the same thing for LambdaCase? I think that since people expect lambda case to just be a simple desugaring it should also work, so then {{{#!hs main = forM values \case Just x -> print x Nothing -> print y }}} parses as {{{#!hs main = forM values (\case Just x -> print x Nothing -> print y) }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by mpickering): How about case, if and let expressions? I personally found it a bit inconsistent that `id Record {..}` parsed correctly so this does bring the other expression types in line with that behaviour. On the other hand, I think the `$` is useful for the reader to indicate that what follows is the final single argument. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by agibiansky): I don't see a common usecase for `case`, `if`, and `let`, and think we should not include them. The motivation for this change is that `do` and lambdas are very commonly used in custom control structures (`when`, `unless`, `for`, `forM`, `with*`, and so on). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Rufflewind):
I don't see a common usecase for case, if, and let
I've certainly written code like this: {{{#!hs foo x = pure $ case x of Just _ -> True Nothing -> False }}} Personally I never understood why `$` was required to begin with. There's no sensible way to interpret `runST do …` except as `runST (do …)`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:3 nomeata]:
Is there code that is valid with and without your extension, but with different semantics?
To me, this is the key question. I can't think of any. But let's dig deeper. I'm looking at the [https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-220003 Haskell 2010 Report] for parsing these sorts of things. Here's the relevant bit: {{{ exp → infixexp :: [context =>] type (expression type signature) | infixexp infixexp→ lexp qop infixexp (infix operator application) | - infixexp (prefix negation) | lexp lexp → \ apat1 … apatn -> exp (lambda abstraction, n ≥ 1) | let decls in exp (let expression) | if exp [;] then exp [;] else exp (conditional) | case exp of { alts } (case expression) | do { stmts } (do expression) | fexp fexp → [fexp] aexp (function application) aexp → qvar (variable) | gcon (general constructor) | literal | ( exp ) (parenthesized expression) | ( exp1 , … , expk ) (tuple, k ≥ 2) | [ exp1 , … , expk ] (list, k ≥ 1) | [ exp1 [, exp2] .. [exp3] ] (arithmetic sequence) | [ exp | qual1 , … , qualn ] (list comprehension, n ≥ 1) | ( infixexp qop ) (left section) | ( qop⟨-⟩ infixexp ) (right section) | qcon { fbind1 , … , fbindn } (labeled construction, n ≥ 0) | aexp⟨qcon⟩ { fbind1 , … , fbindn } (labeled update, n ≥ 1) }}} From this grammar, I was inspired to try the following silliness: {{{ {-# LANGUAGE Haskell2010 #-} instance Num (IO ()) where negate = id main = - do putStrLn "hi" }}} (Note the `-` after the `main =`.) This fails with a parse error. I'd love for someone else to check this against the grammar and see if I should report a separate bug. How does this work in the patch supplied? In any case, even looking at the grammar, it looks like you've found a spot free in the grammar. How many shift/reduce conflicts does the grammar have? At last check, GHC's parser had 47. This isn't great, but we don't want to increase this number! Thanks for submitting a patch! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by agibiansky): @goldfire: The GHC parser (when I cloned master) had 48 shift/reduce conflicts, and this change introduces no new ones (there are still 48). (Actually I just went back to master and recompiled and checked, because I didn't check back when I cloned.) Anyway, this patch introduces no new shift/reduce conflicts. The code {{{ main = - do putStrLn "Hello" }}} causes a parse error with my patch as before, with or without -XArgumentDo enabled. {{{ parse error on input do }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1219 -------------------------------------+------------------------------------- Changes (by simonpj): * differential: => Phab:D1219 Comment: I'm not against this, but not wildly in favour either. It might be convenient, but it's another small wrinkle. Some thoughts * Haskell allows {{{ f MkT { x = 3 } y z }}} meaning {{{ f (MkT {x = 3}) y z }}} which I have always thought of as a bit of a mistake. The former looks (to my eye) too much like a function call with four argument. However, you could argue that the `do` version is less harmful, because the initial `do` signals the start of a `do` block, whereas the initial `MkT` could be a bare constructor argument. * What do you intend for {{{ f x do { blarg } y z }}} Is that equivalent to this? {{{ f x (do { blarg }) y z }}} If so, better to say so. * Also give an example with layout. So perhaps {{{ f x do p <- ps return (p+1) z z }}} is equivalent to {{{ f x (do { p <- ps; return (p+1) }) y z }}} I think lambda-case is similar. * Lambda is different because it does not start implicit layout. So perhaps an un-parenthesised lambda can only appear as the last argument. Better say so. * If you allow lambda, why not `if`? And I suppose `case`? {{{ f x if this then that else the_other }}} means {{{ f x (if this then that else the_other }}} I suspect that this is a bridge too far, but I think it poses no more parsing difficulty than Lambda. Right? * What about infix functions? I.e. is this ok? {{{ f >>> do blarg }}} Presumably the `do` binds more tightly than any operator? I suggest that you make a wiki page on the GHC Trac to describe the extension, along with examples to cover these corner cases, and advertise it on the ghc-users list. That might elicit some info about whether people would find this useful or not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1219 -------------------------------------+------------------------------------- Comment (by thomie): There was a giant (>75 email) discussion about this ticket here: https://mail.haskell.org/pipermail/haskell-cafe/2015-September/121217.html Is there a summary/conclusion somewhere? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1219 -------------------------------------+------------------------------------- Comment (by bgamari): I tried to count the +1s and -1s but it seems to be fairly evenly split. Moreover, it seems like many users are fairly ambivalent on the matter. Andrew's message from Sept 7 nicely reviews the various arguments for and against the proposal. I'll reproduce it and a few other notable points here, == Pro == - It's easier to read than the alternative. - This extension removes syntactic noise. - This makes basic `do`-syntax more approachable to newbies; it is a commonly asked question as to why the `$` is necessary. - This simplifies the resulting AST, potentially making it simpler for editors and other tools to do refactoring. - It's something that belongs in the main language, and if its something we'd consider for a mythical Haskell', it has to start as an extension. - It gets rid of some cases where using `$` doesn't work because `$` interacts with other infix operators being used in the same expression. - This would make do blocks consistent with record creation, where parentheses are skipped, allowing things such as `return R { x = y}` - This does not change the meaning of any old programs, only allows new ones that were previously forbidden. - This gets rid of the need for a specially-typed `$` allowing `runSt $ do ...` - Richard Eisenberg points out that the proposal arguably makes the language **more** consistent, not less, > I think that it makes the language *more* regular, not less: Look at https://www.haskell.org/onlinereport/haskell2010/haskellch3.html#x8-220003, the Haskell 2010 Report on expression syntax. This proposal (if we include `if`, `let`, and `case`, along with `\` and `do`, which would seem to make it more consistent) amounts to dropping the /lexp/ nonterminal and combining it with /aexp/. == Con == - 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. - More and more syntactic "improvements" just fragment the language. - Although this is consistent with record syntax, record syntax without parents was a mistake originally. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: => #11706 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * cc: akio (added) Comment: I would love this. Is there a way to move this forward? Write a wiki page? Or is this proposal abandoned? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): I suspect, in practice, it will involve finding someone with commit bits to champion the change, and then making sure all the loose bits and bobs from the original PR are tied up. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Would this allow {{{#!hs foo = do liftIO do putStrLn do "hello" ++ "world" }}} meaning {{{#!hs foo = do liftIO $ do putStrLn $ do "hello" ++ "world" }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Old use case from [http://www.diss.fu- berlin.de/docs/servlets/MCRFileNodeServlet/FUDOCS_derivate_000000000279/tr-b-95-01.pdf A Concurrency Monad Based on Constructor Primitives, or, Being First-Class is not Enough]: {{{#!hs addUpMain :: Process addUpMain = OwnPid $ \self -> Fork (addUp self) $ \server -> Send server (ListInt [1..20]) $ \() -> Receive $ \(Int n) -> End }}} as {{{#!hs addUpMain :: Process addUpMain = OwnPid \self -> Fork (addUp self) \server -> Send server (ListInt [1..20]) \() -> Receive \case Int n -> End }}} {{{#!hs addUpMain :: Process addUpMain = OwnPid \self -> Fork (addUp self) \server -> Send server (ListInt [1..20]) \() -> Receive \case Int n -> End }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Examples from EDSL [https://hackage.haskell.org/package/esqueleto-2.4.3/docs/Database- Esqueleto.html Esqueleto]: {{{#!hs -- select $ -- from $ \p -> do -- where_ (p ^. PersonName ==. val "John") -- return p select do from \p -> do where_ (p ^. PersonName ==. val "John") return p }}} {{{#!hs -- select $ -- from $ \person -> do -- where_ $ exists $ -- from $ \post -> do -- where_ (post ^. BlogPostAuthorId ==. person ^. PersonId) -- return person select do from \person -> do where_ do exists do from \post -> where_ (post ^. BlogPostAuthorId ==. person ^. PersonId) return person }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Generally sympathetic to this change, less parenthesis are good. For lambdas it looks a bit unusual, but I think I’d quickly adjust to parsing that. Minor comment: In the wiki page you include `{-# SCC #-}` and `{-# CORE #-}`. I’d doubtful about them. I mentally parse them not as control structures, but as if they were normal functions (which happen to only work when used fully applied), and would be surprised if `f a b {-# SCC #-} d e` turn into `f a b ({-# SCC #-} d e)`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- @@ -46,0 +46,2 @@ + + Wiki page: [wiki:ArgumentDo] New description: I would like the following to be valid Haskell code: {{{#!hs main = when True do putStrLn "Hello!" }}} Instead of requiring a dollar sign before the "do". This would parse as {{{#!hs main = when True (do putStrLn "Hello!") }}} Similarly, allow lambdas in the same way {{{#!hs main = forM values \value -> print value }}} parses as {{{#!hs main = forM values (\value -> print value) }}} One possible question: does this also do the same thing for LambdaCase? I think that since people expect lambda case to just be a simple desugaring it should also work, so then {{{#!hs main = forM values \case Just x -> print x Nothing -> print y }}} parses as {{{#!hs main = forM values (\case Just x -> print x Nothing -> print y) }}} Wiki page: [wiki:ArgumentDo] -- Comment (by simonpj): Akio has made a wiki page to specify the feature: [wiki:ArgumentDo] -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Generally sympathetic to this change, less parenthesis are good. For lambdas it looks a bit unusual, but I think I’d quickly adjust to parsing
#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): Replying to [comment:19 nomeata]: that.
Minor comment: In the wiki page you include `{-# SCC #-}` and `{-# CORE
#-}`. I’d doubtful about them. I mentally parse them not as control structures, but as if they were normal functions (which happen to only work when used fully applied), and would be surprised if `f a b {-# SCC #-} d e` turn into `f a b ({-# SCC #-} d e)`. Yes, I think that makes sense. Thank you for pointing it out. I just moved `SCC` and `CORE` from the main proposal to the "Design Space" section. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm one of those who thinks that the fact that `f R { x = e }` means `f (R { x = e })` is a mistake :-). But I appreciate the wiki page, which makes the proposal much more concrete. If there is a reasonable level of support (which seems to be the case) I won't object. I think it's be worth an email to ghc-users to draw attention to the wiki page and invite support or other feedback. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): I don't think parsing `f a b {-# SCC #-} d e` as `f a b ({-# SCC #-} d e)` is even an option, really, since these pragmas must be ignorable by compilers that don't understand them. Also, I think/hope this proposal does not change the parsing of any program that currently parses, right? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I'm intrigued by [https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo#Multipleblockarguments multiple block arguments] {{{#!hs f do x do y }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): Replying to [comment:23 rwbarton]:
I don't think parsing `f a b {-# SCC #-} d e` as `f a b ({-# SCC #-} d e)` is even an option, really, since these pragmas must be ignorable by compilers that don't understand them.
Also, I think/hope this proposal does not change the parsing of any
Agreed. program that currently parses, right? I believe this is the case, although I don't have a proof. My rough argument is: 1. This extension doesn't introduce any new conflict in the parser (shift/reduce or reduce/reduce) 2. By chasing the new grammar you can see that `do`, lambda, etc. continue to parse as a `lexp`. So if there is any change in the parsing of any currently-valid program, then it must be a result of somehow triggering an existing ambiguity in the grammar, but this seems unlikely. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): Replying to [comment:24 Iceland_jack]:
**Edit**: Will it let you write
Yes, your examples should be fine, and my preliminary implementation successfully parses them. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:22 simonpj]:
I'm one of those who thinks that the fact that `f R { x = e }` means `f (R { x = e })` is a mistake :-).
I agree with you here, but I think the proposal in this ticket is still sensible, given that the perhaps-unexpected parsing started with a keyword. In the record update case, the perhaps-unexpected parsing isn't known until the open-brace, even though your brain has to parse the preceding space differently. To me, that's the real problem with the parsing of record-update: it's not left-to-right. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Replying to [comment:22 simonpj]:
I'm one of those who thinks that the fact that `f R { x = e }` means `f (R { x = e })` is a mistake :-).
I agree with you here, but I think the proposal in this ticket is still sensible, given that the perhaps-unexpected parsing started with a keyword. In the record update case, the perhaps-unexpected parsing isn't known until the open-brace, even though your brain has to parse the
#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by maeder): Replying to [comment:27 goldfire]: preceding space differently. To me, that's the real problem with the parsing of record-update: it's not left-to-right. I fully agree, too! The record syntax is unrelated to this proposal. Curly record braces are sort of a strong binding postfix operator and are thus different from plain parentheses. @aiko I would omit the point "This would make do blocks consistent with record creation ..." under Pros on https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo. Record creation is only another kind of a more "non-atomic" aexp in the grammar. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by maeder): @aiko I also agree fully with Richard Eisenberg and do not understand your objection. Therefore I would like if you could add "it makes the language more regular" under Pros, omitted your last paragraph, and really simplified the proposed grammar rules accordingly (namely without lexp and openexp) on ArgumentDo. (For a discussion/omission of group A and group B constructs I refer to https://mail.haskell.org/pipermail/glasgow-haskell- users/2016-July/026299.html) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by maeder): By saying "curly record braces are sort of a strongly binding postfix operator" I suggest that it would also possible to allow, i.e. "R {...} {...}" as nested record updates (but that would be a different issues). The keywords, do, \, case, etc. in this proposal, however, are IMHO best characterized as weakly binding prefix operators (and I completely ignore curly layout braces here on purpose - I hardly use them). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by maeder): @aiko The Cons point "You can already get rid of the $ by just adding parentheses" is only an argument against "$" (or the title of this issue) but not against ArgumentDo. It is actually a Pros point: Allow to get rid of parentheses without using the $-workaround. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Lambda motivation {{{#!hs -- phoas :: Phoas v (x -> y -> x) -- phoas = PLam (\x -> PLam (\y -> PVar x)) phoas :: Phoas v (x -> y -> x) phoas = PLam \x -> PLam \y -> PVar x }}} {{{#!hs -- ex = λ (\x -> λ (\y -> x)) ex = λ \x -> λ \y -> x }}} Would this parse? {{{#!hs ex = λ\ x -> λ\ y -> x }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:32 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by maeder): Replying to [comment:32 Iceland_jack]: [...]
-- ex = λ (\x -> λ (\y -> x))
ex = λ \x -> λ \y -> x }}}
Would this parse?
{{{#!hs ex = λ\ x -> λ\ y -> x }}}
Surely, this is a lexical issue. No space is needed between symbols (like "\") and (unicode) letters (like x, y, or λ), although I recommend to always leave a space, i.e. "f λ\ ..." would be parsed as "(f λ)\ ...". -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:33 maeder]:
Replying to [comment:32 Iceland_jack]: Surely, this is a lexical issue. No space is needed between symbols (like "\") and (unicode) letters (like x, y, or λ), although I recommend to always leave a space, i.e. "f λ\ ..." would be parsed as "(f λ)\ ...".
I was wondering if we could mimic the upper-case lambda `Λ` by using a lower-case `l` for lambda {{{#!hs ex' = l\ x -> l\ y -> x }}} `l\` look like a malformed lambda! (don't) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:34 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): The recent [https://github.com/koengit/KeyMonad/blob/9bcf22d3f5fb08ff0bfb6b6db7c179d8675... ''Key'' monad] lets us mimic Arrow notation in user code {{{#!hs -- addA :: Arrow a => a b Int -> a b Int -> a b Int -- addA f g = proc $ \z -> do -- x <- f -< z -- y <- g -< z -- return $ (+) <$> x <*> y addA :: Arrow a => a b Int -> a b Int -> a b Int addA f g = proc \z -> do x <- f -< z y <- g -< z return $ (+) <$> x <*> y }}} compared to {{{#!hs addA :: Arrow a => a b Int -> a b Int -> a b Int addA f g = procb z -> do x <- f -< z y <- g -< z returnA -< x + y }}} ---- In an alternative universe with idiom brackets {{{#!hs addA :: Arrow a => a b Int -> a b Int -> a b Int addA f g = proc \z -> do x <- f -< z y <- g -< z return [| x + y |] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:35 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): [https://gist.github.com/Icelandjack/5bdaea3692891a1ca3fbe6b7bbfd4cef gist] with examples -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:36 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mentheta): * cc: mentheta (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:37 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Is anyone still pursuing this? I was just tossing the idea in my head of proposing multiple block arguments akin to {{{ foo • one complex argument • second complex argument even on multiple lines • third complex argument }}} (with maybe not precisely this syntax), but if we had `ArgumentDo` I could smiply write, as was pointed out in [https://ghc.haskell.org/trac/ghc/wiki/ArgumentDo#Multipleblockarguments The wiki proposal], {{{ foo do one complex argument do second complex argument even on multiple lines do third complex argument }}} and I would have no need for a separate proposal… -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:38 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): Thank you for reminding me! I was waiting for the proposal process to start working and then forgot about this. I'll make a proposal shortly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:39 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by mentheta): Akio, did you get around to submitting a proposal? I'd be interested in being able to use this extension. Also, could I be of help somehow? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:40 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): Oh yes, oops. I have forgot about this. I have a half-written proposal. I'll finish it and submit it before the next week. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:41 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): Submitted a proposal: https://github.com/ghc-proposals/ghc- proposals/pull/90. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:42 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by mentheta): Thank you akio! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:43 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: akio Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * owner: agibiansky => akio Comment: The proposal has been approved. I'll work on the implementation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:44 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: akio Type: feature request | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219, Wiki Page: | Phab:D4260 -------------------------------------+------------------------------------- Changes (by akio): * status: new => patch * differential: Phab:D1219 => Phab:D1219, Phab:D4260 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:45 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments
-------------------------------------+-------------------------------------
Reporter: agibiansky | Owner: akio
Type: feature request | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.2
(Parser) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #11706 | Differential Rev(s): Phab:D1219,
Wiki Page: | Phab:D4260
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: akio Type: feature request | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 7.10.2 (Parser) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219, Wiki Page: | Phab:D4260 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 Comment: Thanks Akio! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:47 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: akio Type: feature request | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 7.10.2 (Parser) | Resolution: fixed | Keywords: GHCProposal Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219, Wiki Page: | Phab:D4260 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => GHCProposal -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10843#comment:48 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC