
#10112: Desugaring of do-syntax intros unification var with -XRebindableSyntax -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- When compiling below snippet with GHC 7.8.x (and I believe v7.10.x) {{{ {-# LANGUAGE RankNTypes, RebindableSyntax #-} import qualified Prelude as P (>>=) :: a -> ((forall b . b) -> c) -> c a >>= f = f P.undefined return a = a fail s = P.undefined t1 = 'd' >>= (\_ -> 'k') t2 = do _ <- 'd' 'k' main = P.putStrLn [t1, t2] }}} we get this error: {{{ Ztest.hs:12:9: Cannot instantiate unification variable `t0` with a type involving foralls: forall b. b Perhaps you want ImpredicativeTypes In a stmt of a 'do' block: _ <- 'd' In the expression: do { _ <- 'd'; 'k' } In an equation for `t2`: t2 = do { _ <- 'd'; 'k' } Failed, modules loaded: none. }}} In GHC HEAD (and v7.6.x) the error does not appear. Nevertheless I'll file this bug for addition of a regression test. Discussion here: https://mail.haskell.org/pipermail/ghc- devs/2015-February/008383.html -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10112 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler