[GHC] #16104: Plugin name lookup behavior change from GHC 8.4 series

#16104: Plugin name lookup behavior change from GHC 8.4 series -------------------------------------+------------------------------------- Reporter: lerkok | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 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'm trying to port a core plugin to GHC 8.6.3, which was last working fine with GHC 8.4 series. Unfortunately, I'm running into issues. Wondering if pluging programming requirements have changed, or is this a regression in GHC itself. I boiled it down to the following example and would like some guidance on how to make this work: I have the following in file `TestPlugin.hs`: {{{#!hs {-# LANGUAGE TemplateHaskell #-} module TestPlugin (plugin) where import GhcPlugins import Data.Bits plugin :: Plugin plugin = defaultPlugin {installCoreToDos = install} where install _ todos = return (test : todos) test = CoreDoPluginPass "Test" check check :: ModGuts -> CoreM ModGuts check m = do mbN <- thNameToGhcName 'complement case mbN of Just _ -> liftIO $ putStrLn "Found complement!" Nothing -> error "Failed to locate complement" return m }}} And I have a very simple `Test.hs` file: {{{#!hs {-# OPTIONS_GHC -fplugin TestPlugin #-} main :: IO () main = return () }}} With GHC-8.4.2, I have: {{{ $ ghc-8.4.2 --make -package ghc -c TestPlugin.hs [1 of 1] Compiling TestPlugin ( TestPlugin.hs, TestPlugin.o ) $ ghc-8.4.2 -package ghc -c Test.hs Found complement! }}} But with GHC 8.6.3, I get: {{{ $ ghc-8.6.3 --make -package ghc -c TestPlugin.hs [1 of 1] Compiling TestPlugin ( TestPlugin.hs, TestPlugin.o ) $ ghc-8.6.3 -package ghc -c Test.hs ghc: panic! (the 'impossible' happened) (GHC version 8.6.3 for x86_64-apple-darwin): Failed to locate complement }}} The problem goes away if I change `Test.hs` to: {{{#!hs {-# OPTIONS_GHC -fplugin TestPlugin #-} import Data.Bits -- Should not be required in the client code! main :: IO () main = return () }}} That is, if I explicitly import `Data.Bits`. But this is quite undesirable, since `Test.hs` is client code and the users of the plugin have no reason to import all bunch of modules the plugin might need for its own purposes. (In practice, this would require clients to import a whole bunch of irrelevant modules; quite unworkable and not maintainable.) Should I be coding my plugin differently? Or is this a GHC regression? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16104 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16104: Plugin name lookup behavior change from GHC 8.4 series -------------------------------------+------------------------------------- Reporter: lerkok | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 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 mpickering): One work around might be to define the plugin in a package, install it in the package database and then use it. This standalone support for plugins has caused a number of issues. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16104#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16104: Plugin name lookup behavior change from GHC 8.4 series -------------------------------------+------------------------------------- Reporter: lerkok | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 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 lerkok): Thanks Matt. Unfortunately that doesn't work either: Here's the original plugin registered: {{{#!hs $ ghc-pkg list sbvPlugin /usr/local/lib/ghc-8.6.3/package.conf.d (no packages) /Users/LeventErkok/.ghc/x86_64-darwin-8.6.3/package.conf.d sbvPlugin-0.11 }}} Example test file: {{{#!hs $ cat T11.hs {-# OPTIONS_GHC -fplugin=Data.SBV.Plugin #-} module T11 where import Data.SBV.Plugin h :: Integer -> Integer h x = x - 1 g :: Integer -> Integer g x = if x < 12 then x+1 else h x {-# ANN f theorem #-} f :: Integer -> Bool f x = g x < g (x+1) }}} And I still get: {{{#!hs $ ghci T11.hs GHCi, version 8.6.3: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling T11 ( T11.hs, interpreted ) *** Exception: [SBV] Impossible happened, while trying to locate GHC name for: Data.Bits.complement CallStack (from HasCallStack): error, called at ./Data/SBV/Plugin/Env.hs:380:30 in sbvPlugin-0.11-9tpp46BgzL09G1cUaUExU2:Data.SBV.Plugin.Env }}} Exactly the same issue. It's the same problem whether I load it in `ghci` or compile with `ghc`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16104#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16104: Plugin name lookup behavior change from GHC 8.4 series -------------------------------------+------------------------------------- Reporter: lerkok | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 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 mpickering): No I don't know why this is happening. In my plugins [https://github.com/ocharles/assert- explainer/blob/master/plugin/AssertExplainer.hs#L81 I would use] the `lookupOrig` function so that I can be precise about what module a definition is in. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16104#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16104: Plugin name lookup behavior change from GHC 8.4 series -------------------------------------+------------------------------------- Reporter: lerkok | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 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 michaelpj): I think we're also observing this. I think this is not the intended behaviour. Looking at the documentation of `thNameToGhcName` it says: "Qualified or unqualified TH names will be dynamically bound to names in the module being compiled, if possible." My interpretation of this was: if you can import the name qualified in the module being compiled when the core plugin triggers, then the name lookup should succeed. This seems to no longer be true. I can also confirm that adding (unused) imports for the modules whose names are being accessed makes the lookup work again. In our case the plugin *is* registered via a separate package and we're still seeing this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16104#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16104: Plugin name lookup behavior change from GHC 8.4 series -------------------------------------+------------------------------------- Reporter: lerkok | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.3 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): In GHC 8.4 we have {{{ thNameToGhcName th_name = do hsc_env <- getHscEnv liftIO $ initTcForLookup hsc_env (lookupThName_maybe th_name) }}} `lookupThName` ends up calling `lookupGlobalOccRn_maybe`; and (since I think we have an `Orig` at this point) thence `lookupExactOrOrig`, and thence `IfaceEnv.lookupOrig`. The latter * Looks up in the original-name cache * If the lookup fails, it makes a fresh external `Name`, updates the orig- name cache, and returns the `Name`. But in 8.6 we have {{{ thNameToGhcName th_name = do { names <- mapMaybeM lookup (thRdrNameGuesses th_name) -- Pick the first that works -- E.g. reify (mkName "A") will pick the class A in preference -- to the data constructor A ; return (listToMaybe names) } where lookup rdr_name | Just n <- isExact_maybe rdr_name -- This happens in derived code = return $ if isExternalName n then Just n else Nothing | Just (rdr_mod, rdr_occ) <- isOrig_maybe rdr_name = do { cache <- getOrigNameCache ; return $ lookupOrigNameCache cache rdr_mod rdr_occ } | otherwise = return Nothing }}} See: it looks up in the orig-name cache, but doesn't extend it on failure. That's what's going wrong. We just need to do what `lookupOrig` does. In HEAD some more refactoring has happened, which makes it easier. We want `thNameToGhcName` to call something very like `IfaceEnv.lookupOrigIO`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16104#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16104: Plugin name lookup behavior change from GHC 8.4 series
-------------------------------------+-------------------------------------
Reporter: lerkok | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.3
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 Ben Gamari

#16104: Plugin name lookup behavior change from GHC 8.4 series -------------------------------------+------------------------------------- Reporter: lerkok | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.3 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 bgamari): * status: new => patch * milestone: => 8.8.1 Comment: Fixed in https://gitlab.haskell.org/ghc/ghc/merge_requests/148. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16104#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16104: Plugin name lookup behavior change from GHC 8.4 series -------------------------------------+------------------------------------- Reporter: lerkok | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.4 Component: Compiler | Version: 8.6.3 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 bgamari): * milestone: 8.8.1 => 8.6.4 Comment: Actually, we can even get this in to 8.6.4. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16104#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16104: Plugin name lookup behavior change from GHC 8.4 series -------------------------------------+------------------------------------- Reporter: lerkok | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.4 Component: Compiler | Version: 8.6.3 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 michaelpj): Getting this into 8.6.4 would be fantastic! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16104#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16104: Plugin name lookup behavior change from GHC 8.4 series -------------------------------------+------------------------------------- Reporter: lerkok | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.4 Component: Compiler | Version: 8.6.3 Resolution: fixed | 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 bgamari): * status: patch => closed * resolution: => fixed Comment: comment:7 merged to `master` with 0d9f105ba423af4f2ca215a18d04d4c8e2c372a8. comment:6 merged to `ghc-8.6` with 8c2dbc161572b59498a9d7abe444e65973069ef7, comment:7 with 5abfd982f55287b24fd71a5d60a2e3d0e361e47e. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16104#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16104: Plugin name lookup behavior change from GHC 8.4 series
-------------------------------------+-------------------------------------
Reporter: lerkok | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.6.4
Component: Compiler | Version: 8.6.3
Resolution: fixed | 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 Ben Gamari

#16104: Plugin name lookup behavior change from GHC 8.4 series
-------------------------------------+-------------------------------------
Reporter: lerkok | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone: 8.6.4
Component: Compiler | Version: 8.6.3
Resolution: fixed | 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 Ben Gamari
participants (1)
-
GHC