Looking up importDecl and Unique inequality
Moritz Angermann
moritz at lichtzwerge.de
Tue Jan 27 20:55:08 UTC 2015
Hi *,
I'm still trying to get a stage1 compiler with TH support. After some experimenting, I managed to
adjust ghc-7.8 sufficiently to build and not complain about compiling TH code right away. I'm now
stuck with importDecl trying to import Language.Haskell.TH.Lib.ExpQ (as that is referenced in my
sample code I try to compile), but even after loading the TH/Lib.hi file unable to find it due to a
missmatch in the Uniques.
I have a Stage 2, ghc-7.8 (A) compiler for the host, which I use to compile a Stage 1 ghc-7.8 (B) compiler.
Now I want to inject some code (a plugin) into (B), which therefore is compiled with (A) and hence depends
on the packages of (A). But as A and B are the identical version, I hope that I should be able to feed (B)
the same package db.
Given that the plugin was compiled into a cabal package with (A) at (Y) and the package db of (A) is at (X),
I try to compile my sample code with
$ cabal exec B -- path/to/Sample.hs -package-db X -package-db Y -package plugin -fplugin MyPlugin
-- Sample.hs --
{-# LANGUAGE TemplateHaskell #-}
module Main where
main :: IO ()
main = do
let e = $([|Just "Splice!"|]) :: Maybe String
putStrLn . show $ e
-- Sample.hs --
The type checker tries to find Language.Haskell.TH.Lib.ExpQ and loads the lib/TH.hi from (X) with
the declaration, but fails to find it in the eps_PTE after loading the interface.
What I was able to figure out was that Language.Haskell.TH.Lib.ExpQ loaded from lib/TH.hi in (X) obtains the
unique key "rCM", while the unique key that is being looked up is "39S".
Can someone shed some light onto where I am misunderstanding how something is supposed to work?
Cheers,
Moritz
More information about the ghc-devs
mailing list