[GHC] #10420: "Care with plugin imports" is wrong / orphan RULE visibility

#10420: "Care with plugin imports" is wrong / orphan RULE visibility -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.11 (Type checker) | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- A module loaded by a plugin poisons the module cache, so we never load an orphan RULE or instance even if we legitimately should do so. The way to test this is a bit convoluted, but it goes something like this: plugins07.hs {{{ module Main where import Plugins07a import RuleDefiningPlugin {-# NOINLINE x #-} x = "foo" main = putStrLn (show x) }}} Plugins07a.hs {{{ --{-# OPTIONS_GHC -fplugin RuleDefiningPlugin #-} module Plugins07a where }}} RuleDefiningPlugin.hs, in ANOTHER PACKAGE (otherwise, EPT rules don't apply) {{{ module RuleDefiningPlugin where import GhcPlugins {-# RULES "unsound" forall x. show x = "SHOWED" #-} plugin :: Plugin plugin = defaultPlugin }}} I'll commit the full test. Here's what happens: * Building `Plugins07a` results in `loadPluginInterface` on `RuleDefiningPlugin`. We load the `ModIface` but only add its types to the environment because of the "Care with plugin imports" special case. * Building `plugins07.hs` results in a normal source level import for `RuleDefiningPlugin`, but `ModIface` is already in the cache so we don't load anything. RULE is not loaded, disaster! Admittedly, actually triggering this bug requires a convoluted chain of events. But really this problem arose because the "Care with plugin imports" fix is just completely nonsense. Here's what we should do: * We should apply the same fix from #2182 on orphan instances to orphan rules too. This way, we can safely load RULEs into the EPS without accidentally bringing them into scope when they shouldn't be. * Loading an interface should unconditionally suck in the instances and rules. The result is more correct and simpler, so it seems worth fixing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10420 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10420: "Care with plugin imports" is wrong / orphan RULE visibility -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by ezyang: Old description:
A module loaded by a plugin poisons the module cache, so we never load an orphan RULE or instance even if we legitimately should do so. The way to test this is a bit convoluted, but it goes something like this:
plugins07.hs {{{ module Main where
import Plugins07a import RuleDefiningPlugin
{-# NOINLINE x #-} x = "foo"
main = putStrLn (show x) }}}
Plugins07a.hs {{{ --{-# OPTIONS_GHC -fplugin RuleDefiningPlugin #-} module Plugins07a where }}}
RuleDefiningPlugin.hs, in ANOTHER PACKAGE (otherwise, EPT rules don't apply) {{{ module RuleDefiningPlugin where
import GhcPlugins
{-# RULES "unsound" forall x. show x = "SHOWED" #-}
plugin :: Plugin plugin = defaultPlugin }}}
I'll commit the full test.
Here's what happens:
* Building `Plugins07a` results in `loadPluginInterface` on `RuleDefiningPlugin`. We load the `ModIface` but only add its types to the environment because of the "Care with plugin imports" special case.
* Building `plugins07.hs` results in a normal source level import for `RuleDefiningPlugin`, but `ModIface` is already in the cache so we don't load anything. RULE is not loaded, disaster!
Admittedly, actually triggering this bug requires a convoluted chain of events. But really this problem arose because the "Care with plugin imports" fix is just completely nonsense. Here's what we should do:
* We should apply the same fix from #2182 on orphan instances to orphan rules too. This way, we can safely load RULEs into the EPS without accidentally bringing them into scope when they shouldn't be.
* Loading an interface should unconditionally suck in the instances and rules.
The result is more correct and simpler, so it seems worth fixing.
New description: A module loaded by a plugin poisons the module cache, so we never load an orphan RULE or instance even if we legitimately should do so. The way to test this is a bit convoluted, but it goes something like this: plugins07.hs {{{ module Main where import Plugins07a import RuleDefiningPlugin {-# NOINLINE x #-} x = "foo" main = putStrLn (show x) }}} Plugins07a.hs {{{ {-# OPTIONS_GHC -fplugin RuleDefiningPlugin #-} module Plugins07a where }}} RuleDefiningPlugin.hs, in ANOTHER PACKAGE (otherwise, EPT rules don't apply) {{{ module RuleDefiningPlugin where import GhcPlugins {-# RULES "unsound" forall x. show x = "SHOWED" #-} plugin :: Plugin plugin = defaultPlugin }}} I'll commit the full test. Here's what happens: * Building `Plugins07a` results in `loadPluginInterface` on `RuleDefiningPlugin`. We load the `ModIface` but only add its types to the environment because of the "Care with plugin imports" special case. * Building `plugins07.hs` results in a normal source level import for `RuleDefiningPlugin`, but `ModIface` is already in the cache so we don't load anything. RULE is not loaded, disaster! Admittedly, actually triggering this bug requires a convoluted chain of events. But really this problem arose because the "Care with plugin imports" fix is just completely nonsense. Here's what we should do: * We should apply the same fix from #2182 on orphan instances to orphan rules too. This way, we can safely load RULEs into the EPS without accidentally bringing them into scope when they shouldn't be. * Loading an interface should unconditionally suck in the instances and rules. The result is more correct and simpler, so it seems worth fixing. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10420#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10420: "Care with plugin imports" is wrong / orphan RULE visibility
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner: ezyang
Type: bug | Status: new
Priority: low | Milestone:
Component: Compiler (Type | Version: 7.11
checker) | Keywords:
Resolution: | Architecture:
Operating System: Unknown/Multiple | Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Edward Z. Yang

#10420: "Care with plugin imports" is wrong / orphan RULE visibility -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: plugins07 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by ezyang): * testcase: => plugins07 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10420#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10420: "Care with plugin imports" is wrong / orphan RULE visibility -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: patch Priority: low | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: plugins07 Blocked By: | Blocking: 10294 Related Tickets: | Differential Revisions: Phab:D950 -------------------------------------+------------------------------------- Changes (by ezyang): * status: new => patch * differential: => Phab:D950 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10420#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10420: "Care with plugin imports" is wrong / orphan RULE visibility -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: plugins07 Blocked By: | Blocking: 10294 Related Tickets: | Differential Revisions: Phab:D950 -------------------------------------+------------------------------------- Changes (by ezyang): * priority: low => normal Comment: Marking higher since this can affect non-orphan instances too, see #10294 for an example. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10420#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10420: "Care with plugin imports" is wrong / orphan RULE visibility
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner: ezyang
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler (Type | Version: 7.11
checker) | Keywords:
Resolution: | Architecture:
Operating System: Unknown/Multiple | Unknown/Multiple
Type of failure: None/Unknown | Test Case: plugins07
Blocked By: | Blocking: 10294
Related Tickets: | Differential Revisions: Phab:D950
-------------------------------------+-------------------------------------
Comment (by Edward Z. Yang

#10420: "Care with plugin imports" is wrong / orphan RULE visibility -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: fixed | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: plugins07 Blocked By: | Blocking: 10294 Related Tickets: | Differential Revisions: Phab:D950 -------------------------------------+------------------------------------- Changes (by ezyang): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10420#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10420: "Care with plugin imports" is wrong / orphan RULE visibility -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.11 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: plugins07 Blocked By: | Blocking: 10294 Related Tickets: | Differential Rev(s): Phab:D950 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Phyx-): This and other plugin tests are failing on Windows and I can't really figure out why. It Seems like a `cabal` bug. {{{ Tamar@CI MINGW64 /c/TeamCity/buildAgent/work/28754042a1be6052/testsuite/tests/plugins/plugins07.run /rule-defining-plugin $ make -C . package.plugins07 TOP=C:/TeamCity/buildAgent/work/28754042a1be6052/testsuite/ make: Entering directory '/c/TeamCity/buildAgent/work/28754042a1be6052/testsuite/tests/plugins/plugins07.run /rule-defining-plugin' make -s --no-print-directory clean.plugins07 mkdir pkg.plugins07 "/c/TeamCity/buildAgent/work/28754042a1be6052/inplace/bin/ghc-stage2.exe" -outputdir pkg.plugins07 --make -v0 -o pkg.plugins07/setup Setup.hs "/c/TeamCity/buildAgent/work/28754042a1be6052/inplace/bin/ghc-pkg.exe" init pkg.plugins07/local.package.conf pkg.plugins07/setup configure --distdir pkg.plugins07/dist -v0 --enable- library-vanilla --disable-shared --prefix="/c/TeamCity/buildAgent/work/28754042a1be6052/testsuite/tests/plugins/plugins07.run /rule-defining-plugin/pkg.plugins07/install" --with- compiler="/c/TeamCity/buildAgent/work/28754042a1be6052/inplace/bin/ghc- stage2.exe" --with-hc- pkg="/c/TeamCity/buildAgent/work/28754042a1be6052/inplace/bin/ghc-pkg.exe" --package-db=pkg.plugins07/local.package.conf pkg.plugins07/setup build --distdir pkg.plugins07/dist -v0 pkg.plugins07/setup install --distdir pkg.plugins07/dist -v3 /bin/sh: setup: command not found make: *** [Makefile:18: package.plugins07] Error 127 make: Leaving directory '/c/TeamCity/buildAgent/work/28754042a1be6052/testsuite/tests/plugins/plugins07.run /rule-defining-plugin' }}} My guess is that `cabal` is expecting `setup.exe` to be in the same folder as the `.cabal` file. Which these tests don't do. If this is the case, how can they be working on linux? the install partially works until dies. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10420#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC