Determine instance method from class method callsite

Simon Peyton Jones simonpj at microsoft.com
Fri Oct 20 13:42:38 UTC 2017


|  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.

I couldn't understand this.  lookupInstEnv is probably what you want.  It returns a ClsInstLookupResult

type InstMatch = (ClsInst, [DFunInstType])

type ClsInstLookupResult
     = ( [InstMatch]     -- Successful matches
       , [ClsInst]       -- These don't match but do unify
       , [InstMatch] )   -- Unsafe overlapped instances under Safe Haskell
                         -- (see Note [Safe Haskell Overlapping Instances] in
                         -- TcSimplify).

Inside the ClsInst of the InstMatches you'll find a DFunId, which is (I think) what you are after.

Simon

|  -----Original Message-----
|  From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of
|  Tillmann Vogt via ghc-devs
|  Sent: 19 October 2017 18:13
|  To: ghc-devs at haskell.org
|  Subject: Re: Determine instance method from class method callsite
|  
|  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 at haskell.org
|  https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.h
|  askell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
|  devs&data=02%7C01%7Csimonpj%40microsoft.com%7Caa82860ef55a428ab1e908d5
|  1714eb63%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C6364403011206865
|  53&sdata=lpbVMttf5W7p%2FGIs3e5pTd6ZS0w4i%2BHwUr9ysRnuCBE%3D&reserved=0


More information about the ghc-devs mailing list