|
Plugs OutType checker plugins without the type checking. |
When getting ready to launch, one of the steps is the plugs-out test. Can the spacecraft function on its own without power or fuel from all cables and umbilicals?
When debugging GHC plugins, I’ve added tracing and changed the wiring. Rather than throw those edits away, I’ve collected them in ghc-plugs-out, a package of tests that don’t supply any power or fuel for typechecking. This lightweight multiple library1, multiple test-suite package shows how typechecker plugins interact with GHC depending on how they’re wired up, their purity and whether GHC needs help typechecking.
Wiring Diagram
Here’s a type checker plugin that doesn’t do any solving but instead writes its call count.
{-# LANGUAGE QuasiQuotes, NamedFieldPuns #-}
module CallCount.TcPlugin (callCount) where
import Language.Haskell.Printf (s)
import Data.IORef (IORef)
import IOEnv (newMutVar, readMutVar, writeMutVar)
import TcPluginM (tcPluginIO)
import TcRnTypes (TcPluginResult(..), TcPlugin(..), unsafeTcPluginTcM)
newtype State = State { callref :: IORef Int }
callCount :: TcPlugin
=
callCount TcPlugin
= return . State =<< (unsafeTcPluginTcM $ newMutVar 1)
{ tcPluginInit
= \State{callref = c} _ _ _ -> do
, tcPluginSolve <- unsafeTcPluginTcM $ readMutVar c
n . putStrLn $ [s|>>> GHC-TcPlugin #%d|] n
tcPluginIO $ writeMutVar c (n + 1)
unsafeTcPluginTcM return $ TcPluginOk [] []
= const $ return ()
, tcPluginStop }
Plugins are flagged for recompilation in their pluginRecompile
field.
Let’s now wire up and test the pure CallCount.Pure.Plugin
and the impure
CallCount.Impure.Plugin
. The recommended way to wire up a plugin is with
a pragma, only in source files that need the plugin.
{-# OPTIONS_GHC -fplugin CallCount.Pure.Plugin #-}
module Main where
main :: IO a
= undefined main
The call count prints on first build but not when there’s no work to do.
> cabal build test-wireup-pure-by-pragma
[1 of 1] Compiling Main
>>> GHC-TcPlugin #1
> cabal build test-wireup-pure-by-pragma
Up to date
A plugin can also be wired up with an option, say in a cabal file. This is probably fine if all your modules need a plugin.
test-suite test-wireup-pure-by-option
import: opts
type: exitcode-stdio-1.0
main-is: Main.hs
hs-source-dirs: test-suites/wireup-pure-by-option
ghc-options: -Wall -fplugin CallCount.Pure.Plugin
build-depends: base, call-count-plugin
> cabal build test-wireup-pure-by-option
[1 of 1] Compiling Main
>>> GHC-TcPlugin #1
If you mix and match both ways of doing the wiring you’ll end up with two instances of the plugin in the compilation.
> cabal build test-wireup-pure-by-both
[1 of 1] Compiling Main
>>> GHC-TcPlugin #1
>>> GHC-TcPlugin #1
If your plugin is impure, it’s going to force a recompilation.
> cabal build test-wireup-impure-by-pragma
[1 of 1] Compiling Main
>>> GHC-TcPlugin #1
[1 of 1] Compiling Main [Impure plugin forced recompilation]
>>> GHC-TcPlugin #1
> cabal build test-wireup-impure-by-option
[1 of 1] Compiling Main
>>> GHC-TcPlugin #1
[1 of 1] Compiling Main [Impure plugin forced recompilation]
>>> GHC-TcPlugin #1
> cabal build test-wireup-impure-by-both
[1 of 1] Compiling Main
>>> GHC-TcPlugin #1
>>> GHC-TcPlugin #1
[1 of 1] Compiling Main [Impure plugin forced recompilation]
>>> GHC-TcPlugin #1
>>> GHC-TcPlugin #1
Modularity
GHC compiles modules. We see the counter plugin is called on twice when
functions foo
and bar
are in module Main
.
{-# OPTIONS_GHC -fplugin CallCount.Pure.Plugin #-}
module Main where
foo :: IO a
= undefined
foo
bar :: IO a
= undefined
bar
main :: IO ()
= return () main
> cabal build test-counter-main
[1 of 1] Compiling Main
>>> GHC-TcPlugin #1
>>> GHC-TcPlugin #2
Moving foo
and bar
to module FooBar
and the counter plugin reports
two calls again.
> cabal build test-counter-foobar-main
[1 of 2] Compiling FooBar
>>> GHC-TcPlugin #1
>>> GHC-TcPlugin #2
[2 of 2] Compiling Main
Move these functions into separate modules and we count one call for each module.
> cabal build test-counter-foo-bar-main
[1 of 3] Compiling Bar
>>> GHC-TcPlugin #1
[2 of 3] Compiling Foo
>>> GHC-TcPlugin #1
[3 of 3] Compiling Main
Undefined is not a Function
If your plugin behaves badly it is going to hurt. GHC takes the blame for the panic when any one of the functions required of a type checker plugin is implemented undefined2.
plugin :: Plugin
= mkPureTcPlugin undefSolve
plugin
undefSolve :: TcPlugin
= noOp { tcPluginSolve = \_ _ _ _ -> undefined }
undefSolve
noOp :: TcPlugin
=
noOp TcPlugin
= return ()
{ tcPluginInit = \_ _ _ _ -> return $ TcPluginOk [] []
, tcPluginSolve = const $ return ()
, tcPluginStop
}
mkPureTcPlugin :: TcPlugin -> Plugin
=
mkPureTcPlugin p
defaultPlugin= const $ Just p
{ tcPlugin = purePlugin
, pluginRecompile }
> cabal build test-undefined-solve
[1 of 1] Compiling Undefined.Solve.Plugin
[1 of 1] Compiling Main
ghc: panic! (the 'impossible' happened)
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
I would have liked to use record update syntax for undefSolve as shown above but this is not yet possible3 with GHC when the data type has an existential qualifier and that is how TcPlugin is defined4.
data TcPlugin = forall s. TcPlugin
tcPluginInit :: TcPluginM s
{-- ^ Initialize plugin, when entering type-checker.
tcPluginSolve :: s -> TcPluginSolver
,-- ^ Solve some constraints.
-- TODO: WRITE MORE DETAILS ON HOW THIS WORKS.
tcPluginStop :: s -> TcPluginM ()
,-- ^ Clean up after the plugin, when exiting the type-checker.
}
Care Free
Type checker plugins are of course called on by GHC to resolve constraints.
Some need solving and others don’t. GHC knows that it can get an a
from
undefined
but maybe a plugin can do better so we get called.
{-# OPTIONS_GHC -fplugin Undefined.Solve.Plugin #-}
module Main where
main :: IO a
= undefined main
Going from ()
to ()
needs no further resolution. GHC can handle this
by itself. The test-undefined-*-carefree
test suites have these mains.
The ones without carefree in their name don’t. They have the a
from
undefined
mains.
{-# OPTIONS_GHC -fplugin Undefined.Solve.Plugin #-}
module Main where
main :: IO ()
= return () main
We see that solve may be called but init and stop functions are always called.
+-------------------------------+------------+
| Test Suite | GHC Panics |
+===============================+============+
| test-undefined-init | x |
+-------------------------------+------------+
| test-undefined-init-carefree | x |
+-------------------------------+------------+
| test-undefined-solve | x |
+-------------------------------+------------+
| test-undefined-solve-carefree | |
+-------------------------------+------------+
| test-undefined-stop | x |
+-------------------------------+------------+
| test-undefined-stop-carefree | x |
+-------------------------------+------------+
Takeaways
- We should wire up type checker plugins with pragmas only in modules that need it.
- Don’t forget to flag pure plugins as such.
- If GHC doesn’t need help resolving constraints then it won’t call out to your plugin.
- Modules are the units of compilation.