PUBLIC
PUBLIC
Hi,
I’m trying to make a module out of thin air and register it to GHC so that other modules can import it. So far, I have had success with making a ModIface and a ModDetails, and
then registering them using the following function:
registerModule :: (GhcMonad m) => ModIface -> ModDetails -> m ()
registerModule iface details = modifySession $ extendHpt . addModule
where
mod_info = HomeModInfo iface details Nothing
mod = mi_module iface
modOrig = ModOrigin (Just True) [] [] True
addModule = modifyUnitState $ \us -> us
{ moduleNameProvidersMap = M.insert (moduleName mod) (M.singleton mod modOrig) $ moduleNameProvidersMap us
}
extendHpt env = env
{ hsc_unit_env = let ue = hsc_unit_env env in ue
{ ue_hpt = hpt
}
}
where
hpt = addToHpt (hsc_HPT env) (moduleName mod) mod_info
This worked when I was only _declaring_ functions and TyCons in these modules. However, now I would also like to add instances. And I’m hitting a problem here, because
I don’t know where to put the actual definitions of the instance. I’m completely lost here.
Here’s what I’m doing in detail. First, I make a fresh DFunId from a fresh Unique:
let tag = occNameString . getDFunTyKey $ ty
occ = mkDFunOcc (occNameString (getOccName showClass) <> tag) False emptyOccSet
name = mkExternalName uniq mod occ loc
dfun = mkDictFunId name [] [] showClass [ty]
Then, I make a ClsInst that describes my instance:
return ClsInst
{ is_cls_nm = getName showClass
, is_tcs = [KnownTc $ getName tycon]
, is_dfun_name = getName dfun
, is_tvs = []
, is_cls = showClass
, is_tys = [ty]
, is_dfun = dfun
, is_flag = OverlapFlag (NoOverlap NoSourceText) False
, is_orphan = NotOrphan (getOccName $ getName tycon)
}
And then I add ‘AnId dfun’ to my ModDetails’s type env in ‘md_types’,, add the instance to the ‘md_insts’, and fill the ‘mi_decls’ and ‘mi_insts’ of the ModIface accordingly.
This gives me a ModIface/ModDetails pair just like before – but I never said what the definition of ‘dfun’ is!
When I try compiling a real source module that imports this synthetic module and tries to use the instance, it gets as far as the “Desugar (after optimization)” step, and then
fails with:
ghc-mu-core-to-exp: panic! (the 'impossible' happened)
GHC version 9.3.20211130:
lookupIdSubst
$fShowOrderPolicy
InScope {foo mapM_}
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/GHC/Utils/Panic.hs:181:37 in ghc-lib-0.20211130-7QA7vLTw0OYJmMsraoHe3v:GHC.Utils.Panic
pprPanic, called at compiler/GHC/Core/Subst.hs:260:17 in ghc-lib-0.20211130-7QA7vLTw0OYJmMsraoHe3v:GHC.Core.Subst
I’m not surprised that eventually it crashes and burns, because, again, I have only declared my DFunId (‘$fShowOrderPolicy’ in this case), but never defined it. Its definition
would be a CoreExpr, right? So where would I put the pair of ‘(dfun, myCoreExprOfTheRightType)’ for GHC to pick it up? Or is it the case that GHC would only need an ‘Id’s definition if it is trying to inline/specialize it, i.e. should I just attach the definition
to the DFunId as an unfolding? Or is ‘registerModule’ already incomplete and it should put the ‘CoreProgram’ of the module to somewhere deep in the GHC state?
Thanks,
Gergo