Use of typechecker plugin erroneously triggers "unbound implicit parameter" error
To document this bug, we're going to need a typechecker plugin to test it with. I've built a dummy plugin for this purpose, so we can be sure it is not interference from a particular plugin.
dummy-plugin/dummy-plugin.cabal
name: dummy-plugin
version: 0.1.0.0
category: Development
build-type: Simple
cabal-version: >=1.10
library
hs-source-dirs: .
exposed-modules: DummyPlugin
build-depends: base, ghc
default-language: Haskell2010
GHC-options: -Wall -O2
dummy-plugin/DummyPlugin.hs
module DummyPlugin(plugin) where
import TcRnMonad ( TcPlugin(..), TcPluginResult(..) )
import Plugins ( defaultPlugin, Plugin(..), CommandLineOption )
plugin :: Plugin
plugin = defaultPlugin { tcPlugin = Just . thePlugin }
thePlugin :: [CommandLineOption] -> TcPlugin
thePlugin opts = TcPlugin
{ tcPluginInit = return ()
, tcPluginSolve = \_ _ _ _ -> return $ TcPluginOk [] []
, tcPluginStop = \_ -> return ()
}
Bug.hs
{-# OPTIONS_GHC -fplugin=DummyPlugin #-}
module Bug where
impossible :: a
impossible = undefined
First, compile the dummy plugin. From its directory, run cabal install
to install the plugin.
Then, from the main directory, run ghc Bug.hs
.
Expected result: the file compiles. Actual result:
Bug.hs:6:14: error:
• Unbound implicit parameter ?callStack::GHC.Stack.Types.CallStack
arising from a use of implicit parameter ‘?callStack’
• In the expression: undefined
In an equation for ‘impossible’: impossible = undefined
Further, observe that commenting out the line which invokes the type-checker plugin (the pragma on line 1) causes the file to compile correctly.
Trac metadata
Trac field | Value |
---|---|
Version | 7.10.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | high |
Resolution | Unresolved |
Component | Compiler (Type checker) |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |