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))
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Reply via email to