[GHC] #10892: ApplicativeDo should use *> and <*

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: Type: task | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- From @ekmett: Would it be possible to tweak the generation to use `(<*)` or `(*>)` where appropriate when the result isn't being used? For many Applicatives this can be a massive asymptotic win in terms of sharing and/or computational cost. When desugaring using (<*) you'd just omit any handling of the unused result instead. {{{ (\x y -> ...) <$> foo <* bar <*> baz }}} corresponds to {{{ do x <- foo bar y <- baz return ... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => simonmar -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 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 ekmett): Here's a sketch of how this could work: The current patch for `ApplicativeDo` tracks applicative "chains". This would modify the `Applicative` chains you have to hold a `Maybe` pattern instead of a pattern or you could just check for wildcard patterns. There are basically 3 cases for dealing with the chain of (<*>)'s we use today. If you have a prefix of things that don't have meaningful patterns, you can bind them with `(*>)`, just like we'd bind with (>>) before. {{{ do foo;bar;baz; x <- quux; y <- quaffle; return (xyzzy x y) foo *> bar *> baz *> (xyzzy <$> quux <*> quaffle) }}} Otherwise, once you've seen a pattern that actually matters, any subsequent missing patterns can be dropped by using `(<*)` or `(<$)`. The `(<*)` case is mentioned in the description. The `(<$)` case happens for {{{ foo = do bar return whatever }}} which becomes {{{ foo = whatever <$ bar }}} This desugaring should then favor all the right things. `(*>)` is typically a little cheaper than `(<*)`. `(<$)` and `(*>)` are cheaper than `(<$>)` and `(<*>)` when usable. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 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 simonpj): Could you give a concrete example demonstrating the "massive asymptotic win". That would be highly motivating. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 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 ekmett): Consider `Data.Sequence`. There `(<$>)` is `O(n)`, but `(<$)` is `O(log n)`. For any `Functor` that is representable, which is to say there exists `x` such that that `f a` is isomorphic to `x -> a`, you build a 'zipping' applicative that is isomorphic to reader. For that you can show that `(m *> _ = m)` and `(_ <* m = m)`. So `(<*)` and `(*>)` are `O(1)` while the `(<*>)` pays for every point used. In the case of something like {{{#!hs data Stream a = a :- Stream a }}} which is isomorphic to `Natural -> a`, if we look at the zipping applicative (which behaves like `ZipList`)` such an (*>) operation is O(1), but `(<*>)` incurs an ongoing cost O(n) in the length of the prefix of the result stream you inspect. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 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 simonpj): Interesting. For sequences why would you say {{{ do { ... ; x <- e ; ... } }}} if you were just going to discard `x`? Can you give a particular example of a (plausible) program whose complexity becomes asymptotically better? I bet you have some in mind. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 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 ekmett): You often do have to use {{{#!hs _ <- char ')' }}} just to avoid unused result warnings in things like parsers given a parser like {{{#!hs char :: Char -> Parser Char }}} Also, even if you just have do x; y in the ApplicativeDo encoding, nothing currently says that that will invoke (*>) over a manual expansion involving (<*>). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 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 simonpj): You understand this so much better than me. By "particular" example, I was hoping for an executable program that would run asymptotically faster under one desugaring vs the other. Or more simply, a program using `<*>` that would run asymptotically faster if we replaced that `<*>` with `*>`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 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 sjcjoosten): How about a program that would turn a sequence of characters into a sequence of space-characters of the same length? Such a program could be written as part of a pretty-printer or other template-like code. {{{ asIndentation chars = do{_<-chars;return ' '}::Seq Char }}} This particular example would benefit asymptotically from replacing {{{(\_ -> pure ' ') <$>}}} with {{{pure ' ' <$}}}. On a side note, I ran into this strange (but understandable) behavior, not sure if it should be considered a bug: {{{ Prelude Data.Sequence> :t (\x -> do{_ <- x; return x}) (\x -> do{_ <- x; return x}) :: Functor f => f t -> f (f t) Prelude Data.Sequence> :t (\x -> do{_ <- x; pure x}) (\x -> do{_ <- x; pure x}) :: Monad m => m a -> m (m a) Prelude Data.Sequence> :t (\x -> do{pure x}) (\x -> do{pure x}) :: Applicative f => a -> f a Prelude Data.Sequence> :t (\x -> do{return x}) (\x -> do{return x}) :: Monad m => a -> m a }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 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 rwbarton): Replying to [comment:8 sjcjoosten]:
On a side note, I ran into this strange (but understandable) behavior, not sure if it should be considered a bug: {{{ Prelude Data.Sequence> :t (\x -> do{_ <- x; return x}) (\x -> do{_ <- x; return x}) :: Functor f => f t -> f (f t) Prelude Data.Sequence> :t (\x -> do{_ <- x; pure x}) (\x -> do{_ <- x; pure x}) :: Monad m => m a -> m (m a) Prelude Data.Sequence> :t (\x -> do{pure x}) (\x -> do{pure x}) :: Applicative f => a -> f a Prelude Data.Sequence> :t (\x -> do{return x}) (\x -> do{return x}) :: Monad m => a -> m a }}}
This is #11607. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.11 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 simonmar): Some of it is addressed by #11607, but this one: {{{ Prelude Data.Sequence> :t (\x -> do{return x}) (\x -> do{return x}) :: Monad m => a -> m a }}} remains as it is. Perhaps we should turn that into `pure x`, but it seems like a special case and could be surprising. I'm undecided here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 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): * milestone: 8.0.1 => 8.2.1 Comment: It's unlikely that anything will happen on this front for 8.0. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * blocking: => 12143 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): See #12666 for another request with an example. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * priority: normal => high -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.4.1 Comment: It doesn't sound like this will happen for 8.2. However, feel free to step up if you, the motivated reader, would like to see this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bollu): * owner: simonmar => bollu -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => ApplicativeDo -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * related: => #13309 Comment: We should also use `liftA2` when appropriate, which can as much as halve allocation in some cases. That is ticket #13309. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AaronFriel): @ekmett, @simonpj, @bgamari I am working on this issue and have a preliminary patch that explores the design space for this. For the exploring implementation, I added a new constructor of `ApplicativeArg`, `ApplicativeArgNil`, which lacks a pattern. To explore the design space and verify my type checking, I modified the renamer to use `<$` and `<*` (in place of `fmap` and `<*>`) if and only if every statement in the segment was an `ApplicativeArgNil`: {{{#!hs mkApplicativeStmt ctxt args need_join body_stmts | all isAppArgNil args = do { (replace_op, fvs1) <- lookupStmtName ctxt replaceFName ; (but_op, fvs2) <- lookupStmtName ctxt butAName ... }}} For the sake of faithfully implementing your proposed desugaring, I need to ask about this: {{{#!hs -- Example: f = do foo;bar;baz; x <- quux; y <- quaffle; return (xyzzy x y) -- Desugaring: f' = foo *> bar *> baz *> (xyzzy <$> quux <*> quaffle) }}} Is there a reason that desugaring is strictly better than: {{{#!hs -- Desugaring: f'' = xyzzy <$> (foo *> bar *> baz *> quux) <*> quaffle }}} I don't think it'd be too difficult to move the `*>` "then" operators to the beginning, but it would involve changing more of the existing applicative code to do so. I think that this style is more suited to addressing #13309. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Simon Marlow is the one who should respond here. Let's await his response. Meanwhile, I would ''strongly'' urge you to make a careful description of what you intend to do, using the language and notation of the paper. You could put the result as a sub-page of [wiki:ApplicativeDo]. Thanks for working on this! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): I think they're both equivalent. Can you write down the desugaring rule? It seems to me we can use `*>` for *initial* ApplicativeArgNils in the group, and `<*` for *trailing* ApplicativeArgNils in the group. Anything in the middle will just need to behave like a wildcard pattern. Does that seem reasonable? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Well, I suppose we can do better than that (looking at the example in the description), it should be possible to handle ApplicativeArgNil anywhere in the group. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AaronFriel): Yes, I was wondering about that too. Edward writes: "`(*>)` is typically a little cheaper than `(<*)`.", which suggests using the `*>` everywhere except in the tail, where we would use `<*`. Thus: {{{ do x <- foo bar y <- baz return ... ⇕ (\x y -> ...) <$> foo <*> (bar *> baz) }}} That is, we can merge any `ApplicativeArgNil lhsExpr` with a following `ApplicativeArg? rhsExpr`, by omitting the `ApplicativeArgNil` and creating a new `ApplicativeArg? rhsExpr'`, where `rhsExpr' = lhsExpr *> rhsExpr`. In cases where there is no subsequent statement, we use `<*`. This rewriting has the benefit of neatly addressing adding `liftA2`, as `ApplicativeArgNil` statements will be folded into `ApplicativeArgOne`/`ApplicativeArgMany`. e.g.: {{{ do foo x <- bar baz y <- quux quaffle return (xyzzy x y) ⇕ (\x y -> xyzzy x y) <$> (foo *> bar) <*> (baz *> quux) <* quaffle ⇕ liftAt (\x y -> xyzzy x y) (foo *> bar) (baz *> quux) <* quaffle }}} I'm working on the syntax and desugaring rules to address this and #13309. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Yes, seems like a good plan. Don't forget that you can do this rewriting in the desugarer, but not before that, so getting the typing rules right might be a little tricky. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AaronFriel): Given the size and substance of this change, where should I best submit the proposal? To GHC RFCs on GitHub, Phab, or elsewhere? As well, how formal should the documentation be? Is the EBNF and functional description at the page ApplicativeDo sufficient, or should I write up a paper with a more formal description? (I lack even have undergrad degrees yet - to be completed this summer - so I've little experience actually writing and submitting papers.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Editing the ApplicativeDo wiki page is fine. Thanks for tackling this! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 12143 Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AaronFriel): A user ElvishJerricco on Reddit posted an interesting test case ([[https://www.reddit.com/r/haskell/comments/6c7hen/applicativedo_overhaul_request_for_comments/dhw9po0/?context=3|my analysis here]]). There were two interesting things that popped out. Here's the reduced test case: {{{#!hs {-# LANGUAGE ApplicativeDo #-} foo :: Monad f => f () -> f () foo f = f bar :: Monad f => f () -> f () bar f = do _ <- f foo f }}} Clearly the two statements of `bar` are independent, and so we should use `*>` here too. The interesting thing to me is that this doesn't trigger the `ApplicativeDo` desugaring at all! The desugarer outputs: `bar = f >>= \_ -> foo f`. So this is another thing to make sure my revised rules cover. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <*
-------------------------------------+-------------------------------------
Reporter: simonmar | Owner: bollu
Type: task | Status: new
Priority: high | Milestone: 8.4.1
Component: Compiler | Version: 7.11
Resolution: | Keywords: ApplicativeDo
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking: 12143
Related Tickets: #13309 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Marlow

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: | ApplicativeDo, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: ApplicativeDo => ApplicativeDo, newcomer * priority: high => normal * milestone: 8.4.1 => 8.6.1 Comment: This certainly won't happen for 8.4 but it very well may be done for 8.6 if you, the motivated reader, picks it up! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10892: ApplicativeDo should use *> and <* -------------------------------------+------------------------------------- Reporter: simonmar | Owner: bollu Type: task | Status: new Priority: normal | Milestone: 8.10.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: | ApplicativeDo, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13309 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by danidiaz): * cc: danidiaz (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10892#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC