[GHC] #15016: Referencing a do-bound variable in a rec block with ApplicativeDo results in variable not in scope during type checking
GHC
ghc-devs at haskell.org
Mon Apr 9 09:40:03 UTC 2018
#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
More information about the ghc-tickets
mailing list