
#15034: Desugaring `mdo` moves a `let` where it shouldn't be -------------------------------------+------------------------------------- Reporter: parsonsmatt | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 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: -------------------------------------+------------------------------------- Consider the following program: {{{#!hs {-# LANGUAGE RecursiveDo #-} module Main where a :: String a = "hello" test :: IO () test = mdo putStrLn a let a = 3 :: Int print a }}} With both GHC 8.2.2 and GHC 8.4.1, it fails with the following error: {{{#!hs /home/matt/Projects/ghc-repro/src/Main.hs:10:5: error: • Couldn't match type ‘Int’ with ‘[Char]’ Expected type: String Actual type: Int • In a stmt of an 'mdo' block: rec putStrLn a let a = (3 :: Int) In the expression: mdo rec putStrLn a let a = ... print a In an equation for ‘test’: test = mdo rec putStrLn a let ... print a | 10 | putStrLn a | ^^^^^^^^^^ }}} I would expect it to succeed, with `a` shadowing the top-level definition. The desugared output in the error message tells us what is wrong: it is grouping `putStrLn a; let a = ...` together! If I alter the program to be: {{{#!hs a :: String a = "hello" test :: IO () test = do rec putStrLn a let a = 3 :: Int print a }}} Then it does the Right Thing. Looking at the [https://prime.haskell.org/wiki/RecursiveDo Haskell Prime wiki entry for Recursive Do], this seems to be the relevant bit:
That is, a variable used before it is bound is treated as recursively defined, while in a Haskell 98 do-statement it would be treated as shadowed.
I have a more complicated reproduction involving `ST` types and complaints of skolem type variables escaping scope: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE RecursiveDo #-} module Main where import Control.Monad.ST theThing :: ST s () theThing = pure () weirdlyLocal :: ST s () weirdlyLocal = theThing runSTIO :: (forall s. ST s a) -> IO a runSTIO x = pure (runST x) thisWorks :: IO () thisWorks = mdo let weirdlyLocal = theThing runSTIO weirdlyLocal runSTIO weirdlyLocal thisBreaks :: IO () thisBreaks = mdo runSTIO weirdlyLocal let weirdlyLocal = theThing runSTIO weirdlyLocal thisIsFine :: IO () thisIsFine = mdo runSTIO weirdlyLocal let asdf = theThing runSTIO asdf }}} This demonstrates an even more bizarre behavior! If I move the `let` up to the top, then it no longer gets included in a `rec`, and it compiles fine. If I move it under the first statement, then I get this error: {{{#!hs /home/matt/Projects/ghc-repro/src/Main.hs:25:13: error: • Couldn't match type ‘s0’ with ‘s’ because type variable ‘s’ would escape its scope This (rigid, skolem) type variable is bound by a type expected by the context: forall s. ST s () at src/Main.hs:25:5-24 Expected type: ST s () Actual type: ST s0 () • In the first argument of ‘runSTIO’, namely ‘weirdlyLocal’ In a stmt of an 'mdo' block: runSTIO weirdlyLocal In a stmt of an 'mdo' block: rec runSTIO weirdlyLocal let weirdlyLocal = theThing • Relevant bindings include weirdlyLocal :: ST s0 () (bound at src/Main.hs:26:9) | 25 | runSTIO weirdlyLocal | ^^^^^^^^^^^^ /home/matt/Projects/ghc-repro/src/Main.hs:27:13: error: • Couldn't match type ‘s0’ with ‘s’ because type variable ‘s’ would escape its scope This (rigid, skolem) type variable is bound by a type expected by the context: forall s. ST s () at src/Main.hs:27:5-24 Expected type: ST s () Actual type: ST s0 () • In the first argument of ‘runSTIO’, namely ‘weirdlyLocal’ In a stmt of an 'mdo' block: runSTIO weirdlyLocal In the expression: mdo rec runSTIO weirdlyLocal let weirdlyLocal = ... runSTIO weirdlyLocal • Relevant bindings include weirdlyLocal :: ST s0 () (bound at src/Main.hs:26:9) | 27 | runSTIO weirdlyLocal | ^^^^^^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15034 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler