[GHC] #15481: TH fails to recover from reifyFixity with -fexternal-interpreter

#15481: TH fails to recover from reifyFixity with -fexternal-interpreter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Template | Version: 8.4.3 Haskell | Keywords: RemoteGHCi | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- (Originally reported at https://github.com/glguy/th- abstraction/issues/53.) If you compile the following program: {{{#!hs {-# LANGUAGE TemplateHaskell #-} module Bug where import Language.Haskell.TH main :: IO () main = putStrLn $(recover (stringE "reifyFixity failed") (do foo <- newName "foo" _ <- reifyFixity foo stringE "reifyFixity successful")) }}} It will work fine without the use of `-fexternal-interpreter`. However, using `-fexternal-interpreter` will result in an error: {{{ $ /opt/ghc/8.4.3/bin/ghc Bug.hs -fforce-recomp [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) $ /opt/ghc/8.4.3/bin/ghc Bug.hs -fforce-recomp -fexternal-interpreter [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:7:19: error: • The exact Name ‘foo_a3MT’ is not in scope Probable cause: you used a unique Template Haskell name (NameU), perhaps via newName, but did not bind it If that's it, then -ddump-splices might be useful • In the untyped splice: $(recover (stringE "reifyFixity failed") (do foo <- newName "foo" _ <- reifyFixity foo stringE "reifyFixity successful")) | 7 | main = putStrLn $(recover (stringE "reifyFixity failed") | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... Bug.hs:7:19: error: • The exact Name ‘foo_a3MT’ is not in scope Probable cause: you used a unique Template Haskell name (NameU), perhaps via newName, but did not bind it If that's it, then -ddump-splices might be useful • In the untyped splice: $(recover (stringE "reifyFixity failed") (do foo <- newName "foo" _ <- reifyFixity foo stringE "reifyFixity successful")) | 7 | main = putStrLn $(recover (stringE "reifyFixity failed") | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15481 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15481: TH fails to recover from reifyFixity with -fexternal-interpreter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: RemoteGHCi 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 angerman): * cc: angerman (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15481#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15481: TH fails to recover from reifyFixity with -fexternal-interpreter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: RemoteGHCi 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 RyanGlScott): Interestingly, if you invoke `fail` anywhere in the second argument to `recover`: {{{#!hs main :: IO () main = putStrLn $(recover (stringE "reifyFixity failed") (do foo <- newName "foo" _ <- reifyFixity foo fail "wat" stringE "reifyFixity successful")) }}} Then `-fexternal-interpreter` will successfully recover again. Also, there appears to be something specific to `reifyFixity` that triggers this bug. If I replace `reifyFixity` with `reify` or `reifyConStrictness`, then `-fexternal-interpreter` is able to successfully recover from those. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15481#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15481: TH fails to recover from reifyFixity with -fexternal-interpreter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: RemoteGHCi 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 RyanGlScott): I now understand the underlying problem slightly better than before. One of the culprits appears to be whether `addErrTc` is used to accumulate errors (as opposed to `failWithTc`, which throws errors immediately). `reifyFixity` only calls `addErrTc` when used in the program above, whereas if you swap out `reifyFixity` for something like `reify` or `reifyConStrictness`, you'll end up reaching a code path that uses `failWithTc`. (Similarly, adding an explicit use of `fail` will also cause `failWithTc` to be invoked.) For some peculiar reason, `recover` is able to successfully recover from errors added via `failWithTc` when `-fexternal-interpreter` is enabled, but not errors added via `addErrTc`. I don't know why that is the case, however. There is a `Note [TH recover with -fexternal-interpreter]` [http://git.haskell.org/ghc.git/blob/4eebc8016f68719e1ccdf460754a97d1f4d6ef05... here], but I can't glean any nuggets of wisdom from that. Given that `failWithTc` appears to be recovered more reliably than `addErrTc`, one way to fix this bug is to just error more eagerly in `qReifyFixity`, like so: {{{#!diff diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs index c26ba0d..000c84c 100644 --- a/compiler/typecheck/TcSplice.hs +++ b/compiler/typecheck/TcSplice.hs @@ -866,7 +866,7 @@ instance TH.Quasi TcM where qLookupName = lookupName qReify = reify - qReifyFixity nm = lookupThName nm >>= reifyFixity + qReifyFixity nm = checkNoErrs (lookupThName nm) >>= reifyFixity qReifyInstances = reifyInstances qReifyRoles = reifyRoles qReifyAnnotations = reifyAnnotations }}} This makes the original program in this ticket recover successfully, even with `-fexternal-interpreter`. That being said, I'm not sure if it's really the "right" way to fix this bug, since there appears to be some underlying issue in the way `-fexternal-interpreter` interacts with `addErrTc`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15481#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15481: TH fails to recover from reifyFixity with -fexternal-interpreter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: RemoteGHCi 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): * cc: simonmar (added) Comment: Generally, in GHC's type checker monad we can 1. Add an error into a bag of errors to be reported later 2. Raise an exception in the monad (1) and (2) are independent: * You can add an error without raising an exception, via `addErrTc`, thereby allowing multiple errors to be reported. * You can add an error and raise an exception; that's what `failTc` does. * You can raise an exception without adding an error; but that would be very confusing and GHC never does that. The expected behaviour of `Language.Haskell.TH.recover` is, I believe, that it should invoke the recovery action if either (1) or (2) has happened; that is, even if execution finishes without raising an exception, but with errors in the error bag, we should invoke the recovery action. And indeed that is what happens: * `Language.Haskell.TH.recover` invokes `qRecover` in the `Quasi` monad. * The instance for `Quasi TcM` in `TcSplice` has {{{ qRecover recover main = tryTcDiscardingErrs recover main }}} * And indeed `tryTcDiscardingErrors` invokes the recovery action if there are accumulated error messages, even if no exception is raised. So it must be something to do with the external interpreter. Let's fix that, rather than messing with the entirely-innocent `qReifyFixity`. Simon M, any ideas? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15481#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15481: TH fails to recover from reifyFixity with -fexternal-interpreter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: RemoteGHCi 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): * owner: (none) => simonmar Comment: It looks like the external-interpreter implementation of `qRecover` only runs the handler in the exception case, not in the case where an error was added with `addErrTcM`. Probably just a misunderstanding on my part of how it was supposed to work. I'll see if I can fix this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15481#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15481: TH fails to recover from reifyFixity with -fexternal-interpreter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: simonmar Type: bug | Status: patch Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: RemoteGHCi Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5185 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * status: new => patch * differential: => Phab:D5185 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15481#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15481: TH fails to recover from reifyFixity with -fexternal-interpreter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.8.1 Component: Template Haskell | Version: 8.4.3 Resolution: | Keywords: RemoteGHCi Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5185 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * status: patch => merge Comment: Committed in d00c308633fe7d216d31a1087e00e63532d87d6d -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15481#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15481: TH fails to recover from reifyFixity with -fexternal-interpreter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 8.6.2 Component: Template Haskell | Version: 8.4.3 Resolution: fixed | Keywords: RemoteGHCi Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D5185 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.6` in a04ecd7ba8c7f012369eeb5864b813a130e043e3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15481#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC