
#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