[GHC] #10420: "Care with plugin imports" is wrong / orphan RULE visibility
GHC
ghc-devs at haskell.org
Fri May 15 22:10:06 UTC 2015
#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
More information about the ghc-tickets
mailing list