
#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