[GHC] #12490: ApplicativeDo and RebindableSyntax do not desugar as expected

#12490: ApplicativeDo and RebindableSyntax do not desugar as expected -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- In a module with -XApplicativeDo, -XRebindableSyntax, and local definitions for everything in the Functor-Applicative-Monad hierarchy, do- notation always desugars to "join (... (return ...))" (or /s/return/pure/). This forces the result to have at least the constraints of join, which in my case is "IxMonad m". {{{#!hs {-# LANGUAGE RebindableSyntax, ApplicativeDo #-} module My where -- straightforward definitions of fmap, pure, (<*>), join, return, (>>=), (>>) and fail in terms of IxFunctor, IxPointed, IxApplicative, IxMonad fPure m = do a <- m b <- m pure (a, b) fReturn m = do a <- m b <- m return (a, b) }}} According to -ddump-ds, these desugar to: {{{#!hs fPure :: IxMonad m => m k1 k1 a -> m k1 k1 (a, a) fPure m = My.join ( My.(<*>) (My.fmap (\a b -> My.pure (a, b)) m) m ) fReturn :: IxMonad m => m k1 k1 a -> m k1 k1 (a, a) fReturn m = My.join ( My.(<*>) (My.fmap (\a b -> My.return (a, b)) m) m ) }}} But I would expect: {{{#!hs fPure m = My.(<*>) (My.fmap (\a b -> (a, b)) m) m fReturn m = -- same }}} It appears that when "return" is not from base, ApplicativeDo only partially desugars to the specification. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12490: ApplicativeDo and RebindableSyntax do not desugar as expected -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by AaronFriel: @@ -13,1 +13,1 @@ - (>>) and fail in terms of IxFunctor, IxPointed, IxApplicative, IxMonad + -- (>>) and fail in terms of IxFunctor, IxPointed, IxApplicative, IxMonad New description: In a module with -XApplicativeDo, -XRebindableSyntax, and local definitions for everything in the Functor-Applicative-Monad hierarchy, do- notation always desugars to "join (... (return ...))" (or /s/return/pure/). This forces the result to have at least the constraints of join, which in my case is "IxMonad m". {{{#!hs {-# LANGUAGE RebindableSyntax, ApplicativeDo #-} module My where -- straightforward definitions of fmap, pure, (<*>), join, return, (>>=), -- (>>) and fail in terms of IxFunctor, IxPointed, IxApplicative, IxMonad fPure m = do a <- m b <- m pure (a, b) fReturn m = do a <- m b <- m return (a, b) }}} According to -ddump-ds, these desugar to: {{{#!hs fPure :: IxMonad m => m k1 k1 a -> m k1 k1 (a, a) fPure m = My.join ( My.(<*>) (My.fmap (\a b -> My.pure (a, b)) m) m ) fReturn :: IxMonad m => m k1 k1 a -> m k1 k1 (a, a) fReturn m = My.join ( My.(<*>) (My.fmap (\a b -> My.return (a, b)) m) m ) }}} But I would expect: {{{#!hs fPure m = My.(<*>) (My.fmap (\a b -> (a, b)) m) m fReturn m = -- same }}} It appears that when "return" is not from base, ApplicativeDo only partially desugars to the specification. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12490: With RebindableSyntax, ApplicativeDo should eliminate return/pure -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by AaronFriel: @@ -45,1 +45,2 @@ - partially desugars to the specification. + partially desugars to the specification, and the final "return" or "pure" + remains in the output. New description: In a module with -XApplicativeDo, -XRebindableSyntax, and local definitions for everything in the Functor-Applicative-Monad hierarchy, do- notation always desugars to "join (... (return ...))" (or /s/return/pure/). This forces the result to have at least the constraints of join, which in my case is "IxMonad m". {{{#!hs {-# LANGUAGE RebindableSyntax, ApplicativeDo #-} module My where -- straightforward definitions of fmap, pure, (<*>), join, return, (>>=), -- (>>) and fail in terms of IxFunctor, IxPointed, IxApplicative, IxMonad fPure m = do a <- m b <- m pure (a, b) fReturn m = do a <- m b <- m return (a, b) }}} According to -ddump-ds, these desugar to: {{{#!hs fPure :: IxMonad m => m k1 k1 a -> m k1 k1 (a, a) fPure m = My.join ( My.(<*>) (My.fmap (\a b -> My.pure (a, b)) m) m ) fReturn :: IxMonad m => m k1 k1 a -> m k1 k1 (a, a) fReturn m = My.join ( My.(<*>) (My.fmap (\a b -> My.return (a, b)) m) m ) }}} But I would expect: {{{#!hs fPure m = My.(<*>) (My.fmap (\a b -> (a, b)) m) m fReturn m = -- same }}} It appears that when "return" is not from base, ApplicativeDo only partially desugars to the specification, and the final "return" or "pure" remains in the output. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12490: With RebindableSyntax, ApplicativeDo should eliminate return/pure -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 simonpj): * owner: => simonmar -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12490: With RebindableSyntax, ApplicativeDo should eliminate return/pure -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 bgamari): For the record, there is actually a TODO in the code describing this exact shortcoming. See `isReturnApp` in `RnExpr` (https://ghc.haskell.org/trac/ghc/browser/ghc/compiler/rename/RnExpr.hs#L1774) I believe that the problem is that the `Applicative` do desugaring happens in the renamer, where we are unable to lookup whether `return` should be the normal `Control.Monad.return` or some rebound alternative. It's not clear to me how to best fix this short of moving the `Applicative` do implementation to the typechecker, but I'll make sure Simon Marlow knows about this when we next meet. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12490: With RebindableSyntax, ApplicativeDo should eliminate return/pure -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 bgamari): My proposed solution here would be to lookup the `Name` of `return` in the environment and compare against it in `isReturnApp`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12490: With RebindableSyntax, ApplicativeDo should eliminate return/pure -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 AaronFriel): Please permit me some additional questions, I would like to know more about the compiler internals. I think I see why you might want to do this in the type checker, to make sure that `return` or `pure` has the right type before performing the transformation? If so, I don't know how important that is, but with `RebindableSyntax` and `ApplicativeDo` I would assume the user is saying, "I know what I'm doing and I want the transformation to be assumed to be lawful." And, as the `ApplicativeDo` desugaring will still contain `join` or `return` in many cases, incorrectly typed `pure` and `return` definitions ought to cause a compiler error sooner or later. Does that line up with your thoughts? When you say "`Name` of `return`", do you mean in case `return` has been aliased by the user? Does `Name` then correspond to what I would call the fully qualified name, e.g.: `Control.Monad.foo`? If I understand your solution correctly, will any top-level `return` or `pure` permit the desugaring I wrote? (Duplicated here.) {{{#!hs fPure m = do a <- m b <- m pure (a, b) -- to: fPure m = My.(<*>) (My.fmap (\a b -> (a, b)) m) m }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12490: With RebindableSyntax, ApplicativeDo should eliminate return/pure -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: simonmar Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2499 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D2499 * milestone: => 8.0.2 Comment: My original concern was that we wouldn't have a environment handy in the renamer to lookup which binding should be used for `return`. As it turns out this concern was ill-founded. I have a fix in Phab:D2499. Happily I think it's even simple enough to include in 8.0.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12490: With RebindableSyntax, ApplicativeDo should eliminate return/pure
-------------------------------------+-------------------------------------
Reporter: AaronFriel | Owner: simonmar
Type: bug | Status: patch
Priority: normal | Milestone: 8.0.2
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2499
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#12490: With RebindableSyntax, ApplicativeDo should eliminate return/pure -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2499 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12490: With RebindableSyntax, ApplicativeDo should eliminate return/pure -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2499 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Merged to `ghc-8.0` as 44755a0cbcb77aea1c28aeba994a4514aec87904. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12490: With RebindableSyntax, ApplicativeDo should eliminate return/pure -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2499 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12490: With RebindableSyntax, ApplicativeDo should eliminate return/pure -------------------------------------+------------------------------------- Reporter: AaronFriel | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2499 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => ApplicativeDo -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12490#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC