Skip to content
Snippets Groups Projects
Commit f04fd0ae authored by Zubin's avatar Zubin Committed by Marge Bot
Browse files

driver: Ensure we run driverPlugin for staticPlugins (#25217)

driverPlugins are only run when the plugin state changes. This meant they were
never run for static plugins, as their state never changes.

We need to keep track of whether a static plugin has been initialised to ensure
we run static driver plugins at least once. This necessitates an additional field
in the `StaticPlugin` constructor as this state has to be bundled with the plugin
itself, as static plugins have no name/identifier we can use to otherwise reference
them
parent c50d29be
No related branches found
No related tags found
No related merge requests found
Pipeline #100704 canceled
......@@ -244,6 +244,8 @@ data ExternalPlugin = ExternalPlugin
data StaticPlugin = StaticPlugin
{ spPlugin :: PluginWithArgs
-- ^ the actual plugin together with its commandline arguments
, spInitialised :: Bool
-- ^ has this plugin been initialised (i.e. driverPlugin has been run)
}
lpModuleName :: LoadedPlugin -> ModuleName
......
......@@ -121,14 +121,15 @@ initializePlugins hsc_env
, external_plugins <- externalPlugins (hsc_plugins hsc_env)
, check_external_plugins external_plugins (externalPluginSpecs dflags)
-- FIXME: we should check static plugins too
-- ensure we have initialised static plugins
, all spInitialised (staticPlugins (hsc_plugins hsc_env))
= return hsc_env -- no change, no need to reload plugins
| otherwise
= do (loaded_plugins, links, pkgs) <- loadPlugins hsc_env
external_plugins <- loadExternalPlugins (externalPluginSpecs dflags)
let plugins' = (hsc_plugins hsc_env) { staticPlugins = staticPlugins (hsc_plugins hsc_env)
let plugins' = (hsc_plugins hsc_env) { staticPlugins = map (\sp -> sp{ spInitialised = True }) $ staticPlugins (hsc_plugins hsc_env)
, externalPlugins = external_plugins
, loadedPlugins = loaded_plugins
, loadedPluginDeps = (links, pkgs)
......
module Main where
import Control.Monad.IO.Class
import GHC
import GHC.Driver.Monad
import GHC.Plugins
import System.Environment
main = do
libdir:args <- getArgs
defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
-- we need to LinkInMemory otherwise `setTarget [] >> load LoadAllTargets`
-- below will fail.
setSessionDynFlags dflags { ghcLink = LinkInMemory}
liftIO $ putStrLn "loading with driver plugin"
loadWithPlugins [StaticPlugin (PluginWithArgs plugin []) False]
where
loadWithPlugins the_plugins = do
-- first unload (like GHCi :load does)
GHC.setTargets []
_ <- GHC.load LoadAllTargets
target <- guessTarget "static-plugins-module.hs" Nothing Nothing
setTargets [target]
modifySession $ \hsc_env ->
let old_plugins = hsc_plugins hsc_env
in hsc_env { hsc_plugins = old_plugins { staticPlugins = the_plugins } }
dflags <- getSessionDynFlags
setSessionDynFlags dflags { outputFile_ = Nothing }
load LoadAllTargets
liftIO (putStrLn "loading done")
plugin =
defaultPlugin { driverPlugin = \_ env -> liftIO (putStrLn "driver plugin ran") >> pure env }
loading with driver plugin
driver plugin ran
loading done
......@@ -200,6 +200,15 @@ test('static-plugins',
compile_and_run,
['-package ghc -isimple-plugin/ -j1'])
test('T25217',
[extra_files(['static-plugins-module.hs']),
unless(config.have_RTS_linker, skip),
expect_broken_for(16803, prof_ways),
extra_run_opts('"' + config.libdir + '"'),
],
compile_and_run,
['-package ghc -j1'])
test('T15858',
[extra_files(['plugin-recomp/', 'plugin-recomp-test.hs']),
#
......
......@@ -35,23 +35,23 @@ main = do
-- Start with a pure plugin, this should trigger recomp.
liftIO $ putStrLn "==pure.0"
loadWithPlugins [StaticPlugin $ PluginWithArgs plugin0_pure []]
loadWithPlugins [StaticPlugin (PluginWithArgs plugin0_pure []) False]
-- The same (or a different) pure plugin shouldn't trigger recomp.
liftIO $ putStrLn "==pure.1"
loadWithPlugins [StaticPlugin $ PluginWithArgs plugin0_pure []]
loadWithPlugins [StaticPlugin (PluginWithArgs plugin0_pure []) False]
-- Next try with a fingerprint plugin, should trigger recomp.
liftIO $ putStrLn "==fp0.0"
loadWithPlugins [StaticPlugin $ PluginWithArgs plugin_fp0 []]
loadWithPlugins [StaticPlugin (PluginWithArgs plugin_fp0 []) False]
-- With the same fingerprint plugin, should not trigger recomp.
liftIO $ putStrLn "==fp0.1"
loadWithPlugins [StaticPlugin $ PluginWithArgs plugin_fp0 []]
loadWithPlugins [StaticPlugin (PluginWithArgs plugin_fp0 []) False]
-- Change the plugin fingerprint, should trigger recomp.
liftIO $ putStrLn "==fp1"
loadWithPlugins [StaticPlugin $ PluginWithArgs plugin_fp1 []]
loadWithPlugins [StaticPlugin (PluginWithArgs plugin_fp1 []) False]
-- TODO: this currently doesn't work, patch pending
-- -- Even though the plugin is now pure we should still recomp since we
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment