Dear GHC-ers,

I'm working on a plugin for GHC that should help compile the library with which 
this plugin is to ship. What this plugin does is traverse the CoreProgram(s) to 
find things of types defined in my library and optimizes them. I have worked 
out how to "find" things, but I was wondering whether the API could be improved 
for plugin-writers.

For the sake of argument, I have the following:
 - module Foo: library for users to import, containing functions, ADTs etc
 - module Foo.Plugin: GhcPlugin that compiles out all uses of things in Foo

> module Foo where
>
> data Foo x = Foo x
>
> runFoo :: Foo x -> x
> runFoo (Foo x) = x


This example is trivial and I imagine GHC will have no trouble eliminating most 
cases of this, but imagine more complex stuff. Now, if I want to traverse the 
CoreProgram in my plugin, I need to find occurrences of these, so somewhere 
there's stuff like:

> pass tcFoo _ _ (NonRec b expr)
>   | varType b `containsTyConAnywhere` tcFoo
>     = {- clever stuff to compile out Foo -}

My problem is "getting" tcFoo in this example. Below is how I do it now. Maybe 
I'm being thick, or maybe there's just no simpler way. This is my 'plugin' 
function in Foo.Plugin:

> plugin = Plugin $ \opts todo -> do
>  hsc <- getHscEnv
>  dfs <- getDynFlags
>  fr  <- liftIO $ findImportedModule hsc (mkModuleName "Foo") Nothing
>  mod <- case fr of
>    Found ml m -> return m
>    _ -> panic "Failed to (unambiguously) find 'Foo' (using 
> findImportedModule)"
>  onc <- getOrigNameCache
>  let nms = lookupWithDefaultModuleEnv nms (panic "No names defined for module 
> 'Foo'") mod
>      find_ d occ fnd nm
>        = maybe
>            (fail $ "Failed to find " ++ d ++ " '" ++ nm ++ "'")
>            fnd
>            (lookupOccEnv nms $ occ nm)
>      tcFind = find_ "TyCon"   mkTcOcc   lookupTyCon
>      dcFind = find_ "DataCon" mkDataOcc lookupDataCon
>      idFind = find_ "Id"      mkVarOcc  lookupId
>  tcFoo    <- tcFind "Foo"
>  dcFoo    <- dcFind "Foo"
>  idRunFoo <- idFind "runFoo"
>  return $ CoreDoPluginPass "Foo optimisation" (pass tcFoo dcFoo idRunFoo) : 
> todo

I have the following questions:

  1) Is this a/the right way to "find" those things in the plugin?
  2) There seems to be a lot to gain with quasi-quoting a la Template Haskell 
for people writing plugins to go with a library that they wrote. Can such QQ be 
done? Has it been considered?
  3) Is findImportedModule the right function to find my starting point to 
begin with?
  4) What is the 'Maybe FastString' argument in findImportedModule for? I've 
been trying to put in the FSs of PackageIDs, but they make the lookup fail. 
This (dumb) example really made me nervous:

>  fr  <- liftIO $ findImportedModule hsc (mkModuleName "Foo") Nothing
>  mod <- case fr of
>    Found ml m -> do
>      fr' <- liftIO $ findImportedModule hsc (moduleName m) (packageIdFS $ 
> packageId m)

Here, fr' should always be a "Found ml' m'" such that ml == ml' and m == m', 
but... it consistently results in NotFound{} for me. Also, I find this 
especially round-about. Shouldn't Paths_Foo.hs (the Cabal-generated file) maybe 
contain variables for every module in the package? In my case it would thus 
contain some "modFoo :: Module"

Comments and suggestions more than welcome!

Regards,
Philip







_______________________________________________
Glasgow-haskell-users mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to