[GHC] #15016: Referencing a do-bound variable in a rec block with ApplicativeDo results in variable not in scope during type checking

#15016: Referencing a do-bound variable in a rec block with ApplicativeDo results in variable not in scope during type checking -------------------------------------+------------------------------------- Reporter: rjmk | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.3 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: -------------------------------------+------------------------------------- I searched + hope this isn't a dupe. When using both ApplicativeDo and RecursiveDo, referring to a do-bound variable from outside of a rec block causes a GHC internal error. Here's a minimal example: {{{#!hs {-# LANGUAGE ApplicativeDo #-} {-# LANGUAGE RecursiveDo #-} module Lib where import Control.Monad.Fix f :: MonadFix m => m () f = do a <- return () rec let b = a return () }}} The error message I get is {{{ src/Lib.hs:12:13: error: • GHC internal error: ‘a’ is not in scope during type checking, but it passed the renamer tcl_env of environment: [a1pF :-> Type variable ‘m’ = m :: * -> *, r1mX :-> Identifier[f::forall (m :: * -> *). MonadFix m => m (), TopLevelLet [] True]] • In the expression: a In an equation for ‘b’: b = a In a stmt of a 'do' block: rec let b = a | 12 | let b = a | ^ }}} I have reproduced it in 8.2.2 and 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15016 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15016: Referencing a do-bound variable in a rec block with ApplicativeDo results in variable not in scope during type checking -------------------------------------+------------------------------------- Reporter: rjmk | Owner: sighingnow Type: bug | Status: new Priority: normal | Milestone: 8.4.3 Component: Compiler | Version: 8.2.2 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 sighingnow): * owner: (none) => sighingnow Comment: I think the "not is scope" is by design. See more discussion under ticket:4148. When we use `rec` in `do` blocks, rather than `mdo` blocks, the outer variables won't be included into the scope of `rec` block. The real problem is when there's no binding for `a` inside `rec` block, the rhs `a` in `let b = a` will have the same name with the outer `a`. For code: {{{#!hs }}} The rename produces: {{{#!hs Lib.f :: MonadFix m_auv => m_auv () Lib.f = do a_auw <- return () | () <- do rec let b_aux = a_auw return () return () }}} But for code: {{{#!hs f :: MonadFix m => m () f = do a <- return () rec let b = a a = () return () }}} The rename produces: {{{#!hs Lib.f :: MonadFix m_auv => m_auv () Lib.f = do a_auw <- return () | () <- do rec let b_aux = a_auy a_auy = () return () return () }}} Indeed it's a bug. I'm optimistic to assign that to myself :) We also should note this behavior of `rec` in documentation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15016#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15016: Referencing a do-bound variable in a rec block with ApplicativeDo results in variable not in scope during type checking -------------------------------------+------------------------------------- Reporter: rjmk | Owner: sighingnow Type: bug | Status: new Priority: normal | Milestone: 8.4.3 Component: Compiler | Version: 8.2.2 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 rjmk): I'm not sure I understand you correctly when you say
When we use rec in do blocks, rather than mdo blocks, the outer variables won't be included into the scope of rec block.
so this may not be relevant, but removing the ApplicativeDo allows the code to compile. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15016#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15016: Referencing a do-bound variable in a rec block with ApplicativeDo results in variable not in scope during type checking -------------------------------------+------------------------------------- Reporter: rjmk | Owner: sighingnow Type: bug | Status: new Priority: normal | Milestone: 8.4.3 Component: Compiler | Version: 8.2.2 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 sighingnow): I think the code in the description shouldn't be accept even without ApplicativeDo extension. Waiting for experts in this area to comment. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15016#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15016: Referencing a do-bound variable in a rec block with ApplicativeDo results in variable not in scope during type checking -------------------------------------+------------------------------------- Reporter: rjmk | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.4.3 Component: Compiler | Version: 8.2.2 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): * priority: normal => high * owner: sighingnow => simonmar Comment: Simon, might you take a look? GHC should never crash. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15016#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15016: Referencing a do-bound variable in a rec block with ApplicativeDo results in variable not in scope during type checking -------------------------------------+------------------------------------- Reporter: rjmk | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.4.3 Component: Compiler | Version: 8.2.2 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 sighingnow): Indeed it's not a crash, it's just an ordinary error message with description "GHC internal error:". The error is reported in `noFound` method in TcEnv.hs. {{{#!hs _ -> failWithTc $ vcat[text "GHC internal error:" <+> quotes (ppr name) <+> }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15016#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15016: Referencing a do-bound variable in a rec block with ApplicativeDo results in variable not in scope during type checking -------------------------------------+------------------------------------- Reporter: rjmk | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.4.3 Component: Compiler | Version: 8.2.2 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 simonpj): Maybe so, but it still should never happen! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15016#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15016: Referencing a do-bound variable in a rec block with ApplicativeDo results in variable not in scope during type checking -------------------------------------+------------------------------------- Reporter: rjmk | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.4.3 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: ApplicativeDo 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 simonmar): * cc: simonmar (added) * keywords: => ApplicativeDo -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15016#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC