[GHC] #11462: Use of typechecker plugin erroneously triggers "unbound implicit parameter" error
GHC
ghc-devs at haskell.org
Tue Jan 19 22:33:33 UTC 2016
#11462: Use of typechecker plugin erroneously triggers "unbound implicit parameter"
error
-------------------------------------+-------------------------------------
Reporter: kwf | Owner:
Type: bug | Status: new
Priority: high | Milestone: 8.0.1
Component: Compiler | Version: 7.10.3
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
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}}}
{{{#!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}}}
{{{#!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.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11462>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list