alias
alias

Reputation: 30525

Plugin name lookup behavior change from GHC 8.4 series

[Update: Turns out this was a GHC bug and it is now fixed, slated for the 8.6.4 release: https://ghc.haskell.org/trac/ghc/ticket/16104#comment:8 ]

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:

{-# 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:

{-# 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:

{-# 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 tis 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.)

I've found the following stack-overflow ticket, which seems to suffer from a similar problem: How to replicate the behaviour of 'name in a TH splice However, the answer suggested there is just not OK in this case (and perhaps wasn't really OK there either) since it would require unnecessary changes to client code in my case that is just not reasonable to expect. (Perhaps @JoachimBretner has an idea?) I've also filed this as a GHC ticket (https://ghc.haskell.org/trac/ghc/ticket/16104#ticket), but feedback from the stack-overflow community is greatly appreciated.

Should I be coding my plugin differently? Or is this a GHC regression?

Upvotes: 3

Views: 130

Answers (1)

Joachim Breitner
Joachim Breitner

Reputation: 25782

Not a direct answer, but when I need to “hard-code” a name in a GHC plugin, I don’t use TH. Instead, I use findImportedModule and lookupOrig to look it up, e.g. as in

lookupJDITyCon :: TcPluginM Class
lookupJDITyCon = do
    Found _ md   <- findImportedModule jdiModule Nothing
    jdiTcNm <- lookupOrig md (mkTcOcc "JustDoIt")
    tcLookupClass jdiTcNm
  where
jdiModule = mkModuleName "GHC.JustDoIt"

from the code of my ghc-justdoit plugin.

I use Template Haskell names when the user needs to mention names, e.g. in splices or annotations, that I want to pick up in the plugin. This is what I do in inspection-testing. I discuss this a bit in the appendix of the Inspection Testing paper.

Upvotes: 1

Related Questions