[GHC] #11835: ApplicativeDo failed to desugar last line with pure $ <expr>

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Keywords: ApplicativeDo | Operating System: MacOS X Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: #11607 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE ApplicativeDo #-} f m = do x <- m 1 y <- m 2 return $ x + y }}} f should have type (Applicative f, Num a, Num b) => (a -> f b) -> f b but ghc considers f a monad maybe similar with #11607 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => simonmar Comment: Yes, it's another example of #11607. The user manual should state the importance of using `pure` or `return` as the last statement. And point out that you can't use a `$`. Currently it is silent on these points. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): @simonpj, the documentation does say that you need to use `pure` and `return`. I'll add a note about `$`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * status: new => merge * milestone: => 8.0.2 Comment: I updated the documentation: https://phabricator.haskell.org/rGHCd396996298939f647c22b547bc01f1b00e6e2fd9 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by chreekat): Would it possible for the docs to give a brief description of *why* one must follow these syntactic rules? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bernalex): And, by extension, why we can't do better in GHC. Because I'm curious. Why can't we do better? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): GHC translates {{{ do x <- e return (f x) }}} into {{{ (\x -> f x) <$> e }}} So we have to spot `return`, because the transformation removes it. You could invent more rules, say spot `return $ e` for example, but there would always be more examples that you couldn't handle, it's not possible to be completely general here. Consider `return` (or `pure`) as part of the syntax of the `do` expression, like a keyword. Maybe if we were starting from scratch the syntax would be different. Indeed, in Monad Comprehensions, the `return` is always there implicitly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Although it is terrible, I there is precedent for having a special case for `$` (letting it be impredicatively instantiated to handle things like `runST $ ...`). So I don't think it would be unreasonable for there to be a special case here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Phab:D2345 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * differential: => Phab:D2345 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr>
-------------------------------------+-------------------------------------
Reporter: Cosmia | Owner: simonmar
Type: bug | Status: merge
Priority: normal | Milestone: 8.0.2
Component: Compiler | Version: 8.0.1-rc2
Resolution: | Keywords: ApplicativeDo
Operating System: MacOS X | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #11607 | Differential Rev(s): Phab:D2345
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Marlow

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Phab:D2345 Wiki Page: | -------------------------------------+------------------------------------- Comment (by chreekat): Comment 6 provides the rationale for this situation, where the expected behavior isn't really possible because of lower-level concerns. Could that rationale be mentioned in the docs? Something like: {{{ --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -860,7 +860,9 @@ upon the results ``p1...pn`` with either ``return`` or ``pure``. Note: the final statement really must be of the form ``return E`` or ``pure E``, otherwise you get a ``Monad`` constraint. Using ``$`` as -in ``return $ E`` or ``pure $ E`` is also acceptable. +in ``return $ E`` or ``pure $ E`` is also acceptable. This is because we +must spot the ``return`` before `GHC transforms do-syntax into fmap +https://ghc.haskell.org/trac/ghc/ticket/11835?replyto=6#comment:6`_. }}} I've not had much experience contributing to GHC, so I apologize for the unwieldy format of this suggestion. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr>
-------------------------------------+-------------------------------------
Reporter: Cosmia | Owner: simonmar
Type: bug | Status: merge
Priority: normal | Milestone: 8.0.2
Component: Compiler | Version: 8.0.1-rc2
Resolution: | Keywords: ApplicativeDo
Operating System: MacOS X | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #11607 | Differential Rev(s): Phab:D2345
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Marlow

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Phab:D2345 Wiki Page: | -------------------------------------+------------------------------------- Comment (by EyalLotem): Could be interesting to detect pure/return via their type though, rather than name. If you have a function of type: (a -> m a) with up to Monad constraints on the m, then you can consider it a "return". For example, here: ($) return :: Monad m => a -> m a No special casing needed, it's the type of return so it must *be* return. This would currently break down due to fail: const (fail "boo!") :: Monad m => a -> m a But that will be fixed once fail is taken the hell out of Monad. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Phab:D2345 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Interesting idea, but at the point we're doing this, we're in the renamer and we don't have type info. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11835: ApplicativeDo failed to desugar last line with pure $ <expr> -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: fixed | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Phab:D2345 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged comment:11 and comment:9 to `ghc-8.0`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11835#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC