Determine instance method from class method callsite

Tillmann Vogt tillk.vogt at googlemail.com
Thu Oct 19 17:13:25 UTC 2017


I have the same problem  with a compiler plugin that I am writing.

In GHC Core I need to get from a dict-fun identifier (e.g. 
$fMyClassDouble to the type class instance bindr (starting with $c).

lookupInstEnv from the InstEnv module seemed to do it, but it seems to 
look up the matching key from a set of instEnv keys and not anything 
that contains the instance bindr. Not sure.

Where is the dictionary lookup that gives me the bindr?

What I did so far:

evalExpr :: DynFlags -> ModGuts -> CoreExpr -> Var ->  CoreM NodeType
evalExpr dflags guts (Var iD) v = do

   hsc_env <- getHscEnv
   eps <- liftIO (hscEPS hsc_env)
   let instEnvs = InstEnvs (eps_inst_env     eps)
                           (mg_inst_env     guts)
                           (mkModuleSet (dep_orphs (mg_deps guts)))
   let ty = tyConAppTyCon_maybe (idType iD)
   let cl = fromJust (tyConClass_maybe (fromJust ty))
   let tys = snd (splitTyConApp (idType iD))
   let (matches,_,_) | isDictId iD = lookupInstEnv False instEnvs cl tys
                     | otherwise = ([],[],[])

   let inst = map (nameStableString . varName . is_dfun . fst) matches

   liftIO $ B.appendFile ("debug.txt") (B.pack (show inst))


More information about the ghc-devs mailing list