[GHC] #10249: GHCi leaky abstraction: error message mentions `ghciStepIO`
GHC
ghc-devs at haskell.org
Wed Sep 5 11:09:38 UTC 2018
#10249: GHCi leaky abstraction: error message mentions `ghciStepIO`
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.2.1
Component: GHCi | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: Incorrect | Test Case:
warning at compile-time | ghci/scripts/T10249
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1527,
Wiki Page: | Phab:D1528
-------------------------------------+-------------------------------------
Comment (by simonpj):
Gah. I had a quick look, and it's fiddly. When you write
{{{
a <- e
}}}
at the prompt, we get into `TcRnDriver.tcUserStmt`; in the second equation
(i.e. not the `BodyStmt` case).
It does this
{{{
; let gi_stmt
| (L loc (BindStmt ty pat expr op1 op2)) <- rn_stmt
= L loc $ BindStmt ty pat (nlHsApp ghciStep expr) op1
op2
| otherwise = rn_stmt
}}}
which transforms the Stmt to
{{{
a <- (ghciStepIO :: forall a. M a -> IO a) e
}}}
where `M` is the currently-in-force GHCi monad.
Apparently, via `TcRnMonad.getGHCiMonad` and `setGHCiMonad`, it is
possible to change the monad in which GHCi bindings are understood, using
the library class
{{{
module GHC.Ghci where
class (Monad m) => GHCiSandboxIO m where
ghciStepIO :: m a -> IO a
}}}
to mediate.
I can't see this documented in the user manual, or indeed anywhere else.
Sigh.
Anyway it's this `ghcStepIO` call that the typechecker is complaining
about.
I can see various ways to avoid this leakage
* Typecheck `e` all by iself, checking that it has type `M <something>`,
before attempting to typecheck `a <- ghcStepIO e`. This is a bit similar
to what happens in "Plan C" of the `BodyStmt` case of `tcUserStmt` (see
`This two-step story is very clunky, alas`).
* Some how avoid adding the error contexts in `tcExpr` for generated code.
Neither of these seems particularly easy.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10249#comment:12>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list